RFC5234: done.
parent
8e68099e52
commit
140c7e128c
|
@ -5,11 +5,12 @@ module GenericParser.RFC5234 where
|
||||||
import Prelude (Unit, between, (<<<), (||), (==), bind, void, ($))
|
import Prelude (Unit, between, (<<<), (||), (==), bind, void, ($))
|
||||||
|
|
||||||
import Control.Alt ((<|>))
|
import Control.Alt ((<|>))
|
||||||
|
import Data.Array as A
|
||||||
import Data.Char as C
|
import Data.Char as C
|
||||||
|
|
||||||
import GenericParser.BaseFunctions (isAlpha, isDigit, isHexaDecimal)
|
import GenericParser.BaseFunctions (isAlpha, isDigit, isHexaDecimal)
|
||||||
|
|
||||||
import GenericParser.Parser (Parser, char, sat)
|
import GenericParser.Parser (Parser, char, sat, item)
|
||||||
|
|
||||||
-- | ALPHA: any letter, upper or lower case.
|
-- | ALPHA: any letter, upper or lower case.
|
||||||
-- |
|
-- |
|
||||||
|
@ -51,13 +52,17 @@ ctl = sat cond
|
||||||
where cond x = (between 0 31 $ C.toCharCode x)
|
where cond x = (between 0 31 $ C.toCharCode x)
|
||||||
|| C.toCharCode x == 127
|
|| C.toCharCode x == 127
|
||||||
|
|
||||||
--DIGIT = %x30-39
|
-- | DIGIT: any digit character (from 0 to 9).
|
||||||
-- ; 0-9
|
-- |
|
||||||
|
-- | DIGIT = %x30-39
|
||||||
digit :: forall e. Parser e Char
|
digit :: forall e. Parser e Char
|
||||||
digit = sat isDigit
|
digit = sat isDigit
|
||||||
|
|
||||||
--DQUOTE = %x22
|
-- | DQUOTE: double quote (").
|
||||||
-- ; " (Double Quote)
|
-- |
|
||||||
|
-- | DQUOTE = %x22
|
||||||
|
dquote :: forall e. Parser e Unit
|
||||||
|
dquote = void $ sat (\x -> C.toCharCode x == 34)
|
||||||
|
|
||||||
-- | HEXDIG: hexadecimal.
|
-- | HEXDIG: hexadecimal.
|
||||||
-- |
|
-- |
|
||||||
|
@ -70,23 +75,29 @@ hexdig = sat isHexaDecimal
|
||||||
htab :: forall e. Parser e Char
|
htab :: forall e. Parser e Char
|
||||||
htab = char '\t'
|
htab = char '\t'
|
||||||
|
|
||||||
--LF = %x0A
|
-- | LF: linefeed.
|
||||||
-- ; linefeed
|
-- |
|
||||||
--
|
-- | LF = %x0A
|
||||||
--LWSP = *(WSP / CRLF WSP)
|
lf :: forall e. Parser e Unit
|
||||||
-- ; Use of this linear-white-space rule
|
lf = void $ char '\n'
|
||||||
-- ; permits lines containing only white
|
|
||||||
-- ; space that are no longer legal in
|
-- | LWSP: Use of this linear-white-space rule permits lines containing only white
|
||||||
-- ; mail headers and have caused
|
-- | space that are no longer legal in mail headers and have caused interoperability
|
||||||
-- ; interoperability problems in other
|
-- | problems in other contexts.
|
||||||
-- ; contexts.
|
-- | Do not use when defining mail headers and use with caution in other contexts.
|
||||||
-- ; Do not use when defining mail
|
-- |
|
||||||
-- ; headers and use with caution in
|
-- | LWSP = *(WSP / CRLF WSP)
|
||||||
-- ; other contexts.
|
lwsp :: forall e. Parser e Unit
|
||||||
--
|
lwsp = void $ A.many (wsp <|> (do _ <- crlf
|
||||||
--OCTET = %x00-FF
|
wsp))
|
||||||
-- ; 8 bits of data
|
|
||||||
--
|
|
||||||
|
-- | OCTET: any data on a single byte.
|
||||||
|
-- |
|
||||||
|
-- | OCTET = %x00-FF
|
||||||
|
octet :: forall e. Parser e Char
|
||||||
|
octet = item
|
||||||
|
|
||||||
-- | SP: space.
|
-- | SP: space.
|
||||||
-- |
|
-- |
|
||||||
-- | SP = %x20
|
-- | SP = %x20
|
||||||
|
|
Loading…
Reference in New Issue