parser/src/GenericParser/RFC5234.purs

94 lines
2.4 KiB
Plaintext

-- | `RFC5234`, Augmented BNF notation, explains the syntax specification found in many RFCs.
-- | This module implements core rules found in appendix B.1.
module GenericParser.RFC5234 where
import Prelude (Unit, between, bind, void, ($))
import Control.Alt ((<|>))
import Data.Char as C
import GenericParser.BaseFunctions (isHexaDecimal)
import GenericParser.Parser (Parser, char, sat)
-- | RFC 5234:
--ALPHA = %x41-5A / %x61-7A ; A-Z / a-z
--BIT = "0" / "1"
-- | CHAR (renamed `asciichar` to fix naming conflict with `GenericParser.char`):
-- | any 7-bit US-ASCII character, excluding NUL.
-- |
-- | CHAR = %x01-7F
asciichar :: forall e. Parser e Char
asciichar = sat (\x -> between 1 127 $ C.toCharCode x)
-- | CR: carriage return.
-- |
-- | 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
-- ; controls
--
--DIGIT = %x30-39
-- ; 0-9
--
--DQUOTE = %x22
-- ; " (Double Quote)
-- | HEXDIG: hexadecimal.
-- |
-- | HEXDIG = DIGIT / "A" / "B" / "C" / "D" / "E" / "F"
hexdig :: forall e. Parser e Char
hexdig = sat isHexaDecimal
-- | HTAB: horizontal tab.
-- | HTAB = %x09
htab :: forall e. Parser e Char
htab = char '\t'
--LF = %x0A
-- ; linefeed
--
--LWSP = *(WSP / CRLF WSP)
-- ; Use of this linear-white-space rule
-- ; permits lines containing only white
-- ; space that are no longer legal in
-- ; mail headers and have caused
-- ; interoperability problems in other
-- ; contexts.
-- ; Do not use when defining mail
-- ; headers and use with caution in
-- ; other contexts.
--
--OCTET = %x00-FF
-- ; 8 bits of data
--
-- | SP: space.
-- |
-- | SP = %x20
sp :: forall e. Parser e Char
sp = char ' '
-- | VCHAR = %x21-7E
-- |
-- | Visible printing characters.
vchar :: forall e. Parser e Char
vchar = sat (\x -> between 33 126 $ C.toCharCode x)
-- | WSP: white space.
-- |
-- | WSP = SP / HTAB
wsp :: forall e. Parser e Char
wsp = sp <|> htab