aboutsummaryrefslogtreecommitdiff
path: root/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
blob: 19edce04164c376b4bf078c21a6a51a90777bce2 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Documentation.Haddock.Parser.Monad (
  module Documentation.Haddock.Parser.Monad
, Attoparsec.isDigit
, Attoparsec.isDigit_w8
, Attoparsec.isAlpha_iso8859_15
, Attoparsec.isAlpha_ascii
, Attoparsec.isSpace
, Attoparsec.isSpace_w8
, Attoparsec.inClass
, Attoparsec.notInClass
, Attoparsec.isEndOfLine
, Attoparsec.isHorizontalSpace
, Attoparsec.choice
, Attoparsec.count
, Attoparsec.option
, Attoparsec.many'
, Attoparsec.many1
, Attoparsec.many1'
, Attoparsec.manyTill
, Attoparsec.manyTill'
, Attoparsec.sepBy
, Attoparsec.sepBy'
, Attoparsec.sepBy1
, Attoparsec.sepBy1'
, Attoparsec.skipMany
, Attoparsec.skipMany1
, Attoparsec.eitherP
) where

import           Control.Applicative
import           Control.Monad
import           Data.String
import           Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as LB
import qualified Data.Attoparsec.ByteString.Char8 as Attoparsec
import           Data.Word
import           Data.Bits

newtype Parser a = Parser (Attoparsec.Parser a)
  deriving (Functor, Applicative, Alternative, Monad, MonadPlus, IsString)

parseOnly :: Parser a -> ByteString -> Either String a
parseOnly (Parser p) = Attoparsec.parseOnly p

lift :: Attoparsec.Parser a -> Parser a
lift = Parser

char :: Char -> Parser Char
char = lift . Attoparsec.char

char8 :: Char -> Parser Word8
char8 = lift . Attoparsec.char8

anyChar :: Parser Char
anyChar = lift Attoparsec.anyChar

notChar :: Char -> Parser Char
notChar = lift . Attoparsec.notChar

satisfy :: (Char -> Bool) -> Parser Char
satisfy = lift . Attoparsec.satisfy

peekChar :: Parser (Maybe Char)
peekChar = lift Attoparsec.peekChar

peekChar' :: Parser Char
peekChar' = lift Attoparsec.peekChar'

digit :: Parser Char
digit = lift Attoparsec.digit

letter_iso8859_15 :: Parser Char
letter_iso8859_15 = lift Attoparsec.letter_iso8859_15

letter_ascii :: Parser Char
letter_ascii = lift Attoparsec.letter_ascii

space :: Parser Char
space = lift Attoparsec.space

string :: ByteString -> Parser ByteString
string = lift . Attoparsec.string

stringCI :: ByteString -> Parser ByteString
stringCI = lift . Attoparsec.stringCI

skipSpace :: Parser ()
skipSpace = lift Attoparsec.skipSpace

skipWhile :: (Char -> Bool) -> Parser ()
skipWhile = lift . Attoparsec.skipWhile

take :: Int -> Parser ByteString
take = lift . Attoparsec.take

scan :: s -> (s -> Char -> Maybe s) -> Parser ByteString
scan s = lift . Attoparsec.scan s

takeWhile :: (Char -> Bool) -> Parser ByteString
takeWhile = lift . Attoparsec.takeWhile

takeWhile1 :: (Char -> Bool) -> Parser ByteString
takeWhile1 = lift . Attoparsec.takeWhile1

takeTill :: (Char -> Bool) -> Parser ByteString
takeTill = lift . Attoparsec.takeTill

takeByteString :: Parser ByteString
takeByteString = lift Attoparsec.takeByteString

takeLazyByteString :: Parser LB.ByteString
takeLazyByteString = lift Attoparsec.takeLazyByteString

endOfLine :: Parser ()
endOfLine = lift Attoparsec.endOfLine

decimal :: Integral a => Parser a
decimal = lift Attoparsec.decimal

hexadecimal :: (Integral a, Bits a) => Parser a
hexadecimal = lift Attoparsec.hexadecimal

endOfInput :: Parser ()
endOfInput = lift Attoparsec.endOfInput

atEnd :: Parser Bool
atEnd = lift Attoparsec.atEnd