WIP RFC5234.
This commit is contained in:
parent
125bbd1118
commit
1951d893a9
@ -2,37 +2,41 @@
|
|||||||
-- | This module implements core rules found in appendix B.1.
|
-- | This module implements core rules found in appendix B.1.
|
||||||
module GenericParser.RFC5234 where
|
module GenericParser.RFC5234 where
|
||||||
|
|
||||||
import Prelude (Unit, unit, bind, pure, ($), (<>), (==), (||), between, 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 Data.Either (Either(..))
|
|
||||||
import Data.Maybe (Maybe(..))
|
|
||||||
import Data.String.CodeUnits as CU
|
|
||||||
|
|
||||||
import GenericParser.BaseFunctions (repeat, isHexaDecimal)
|
import GenericParser.BaseFunctions (isHexaDecimal)
|
||||||
|
|
||||||
import GenericParser.Parser (Parser(..)
|
import GenericParser.Parser (Parser, char, sat)
|
||||||
, sat, char , digit , letter, item, many1, tryMaybe
|
|
||||||
, current_input, failureError, parse, rollback, until)
|
|
||||||
|
|
||||||
-- | RFC 5234:
|
-- | RFC 5234:
|
||||||
|
|
||||||
--ALPHA = %x41-5A / %x61-7A ; A-Z / a-z
|
--ALPHA = %x41-5A / %x61-7A ; A-Z / a-z
|
||||||
--
|
|
||||||
--BIT = "0" / "1"
|
--BIT = "0" / "1"
|
||||||
--
|
|
||||||
--CHAR = %x01-7F
|
-- | CHAR (renamed `asciichar` to fix naming conflict with `GenericParser.char`):
|
||||||
-- ; any 7-bit US-ASCII character,
|
-- | any 7-bit US-ASCII character, excluding NUL.
|
||||||
-- ; excluding NUL
|
-- |
|
||||||
--
|
-- | CHAR = %x01-7F
|
||||||
--CR = %x0D
|
asciichar :: forall e. Parser e Char
|
||||||
-- ; carriage return
|
asciichar = sat (\x -> between 1 127 $ C.toCharCode x)
|
||||||
--
|
|
||||||
--CRLF = CR LF
|
-- | CR: carriage return.
|
||||||
-- ; Internet standard newline
|
-- |
|
||||||
--
|
-- | CR = %x0D
|
||||||
|
cr :: forall e. Parser e Unit
|
||||||
|
cr = void $ char '\r'
|
||||||
|
|
||||||
|
-- | CRLF: Internet standard newline.
|
||||||
|
-- |
|
||||||
|
-- | CRLF = CR LF
|
||||||
|
crlf :: forall e. Parser e Unit
|
||||||
|
crlf = do _ <- char '\r'
|
||||||
|
void $ char '\n'
|
||||||
|
|
||||||
--CTL = %x00-1F / %x7F
|
--CTL = %x00-1F / %x7F
|
||||||
-- ; controls
|
-- ; controls
|
||||||
--
|
--
|
||||||
@ -87,9 +91,3 @@ vchar = sat (\x -> between 33 126 $ C.toCharCode x)
|
|||||||
-- | WSP = SP / HTAB
|
-- | WSP = SP / HTAB
|
||||||
wsp :: forall e. Parser e Char
|
wsp :: forall e. Parser e Char
|
||||||
wsp = sp <|> htab
|
wsp = sp <|> htab
|
||||||
|
|
||||||
|
|
||||||
crlf :: forall e. Parser e Unit
|
|
||||||
crlf = do _ <- char '\r'
|
|
||||||
_ <- char '\n'
|
|
||||||
pure unit
|
|
||||||
|
Loading…
Reference in New Issue
Block a user