Copyright | (c) 2011 Kathleen Fisher <kathleen.fisher@gmail.com> John Launchbury <john.launchbury@gmail.com> |
---|---|
License | MIT |
Maintainer | Karl Cronburg <karl@cs.tufts.edu> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type Char_md = Base_md
- char_parseM :: PadsParser (Char, Base_md)
- char_def :: Char
- int_parseM :: PadsParser (Int, Base_md)
- int_def :: Int
- integer_parseM :: PadsParser (Integer, Base_md)
- integer_def :: Integer
- float_parseM :: PadsParser (Float, Base_md)
- float_def :: Float
- double_parseM :: PadsParser (Double, Base_md)
- double_def :: Double
- digit_parseM :: PadsParser (Digit, Base_md)
- digit_def :: Digit
- string_def :: [Char]
- type StringC = String
- type StringFW = String
- type StringVW = String
- type StringME = String
- type StringSE = String
- type StringP = String
- type StringPESC = String
- data Chunk
- fromChunks :: [Chunk] -> ByteString
- type EOF = ()
- type EOR = ()
- md :: Base_md
Documentation
char_parseM :: PadsParser (Char, Base_md) Source #
Monadic parser for a PADS Char
int_parseM :: PadsParser (Int, Base_md) Source #
Monadic parser for a PADS Int
integer_parseM :: PadsParser (Integer, Base_md) Source #
Monadic parser for a PADS Integer
integer_def :: Integer Source #
Default value inserted by the parser for a PADS Integer
float_parseM :: PadsParser (Float, Base_md) Source #
Monadic parser for a PADS Float, e.g. "-3.1415"
double_parseM :: PadsParser (Double, Base_md) Source #
Monadic parser for a textual PADS Double, e.g. "-3.1415"
double_def :: Double Source #
Default value inserted by the parser for a PADS Float
digit_parseM :: PadsParser (Digit, Base_md) Source #
Monadic parser for a PADS Digit according to isDigit
string_def :: [Char] Source #
Default value inserted by the parser for a PADS String
type StringME = String Source #
string with matching expression. For example:
[pads| type StrME = StringME 'a+' |]
type StringSE = String Source #
string matching given native regex. PADS uses posix regex (from the regex-posix package). For example:
[pads| StringSE <| RE "b|c" |>|]
type StringP = String Source #
string with a predicate. For example:
[pads| type Digits = StringP Char.isDigit |]
type StringPESC = String Source #
string predicate with escape condition
Chunks represent an abstraction of literal data, and allow for easy consumption and concatenation into one ByteString of data, which can be written to disk. Each BinaryChunk represents the value val .&. (2^bits - 1)
fromChunks :: [Chunk] -> ByteString Source #
fromChunks provides a translation from Chunks to a list of bytes. It accomplishes this in time linear to the length of the list of Chunks. It converts each chunk into "bits" (a list of 1's and 0's), then splits that into "bytes" (lists of length 8 each) to simplify combination in non-byte- aligned cases.
Some PADS types, PConstrain for instance, are designed to have access to parsed metadata, stored as the variable md. In parsing, metadata is created and supplied to the constraint at the correct time in the generated parsing functions. However, during generation of generation functions, no metadata exists. Providing this variable assignment prevents compile time errors of functions with predicates that refer to md, and is safe wrt parsing predicates because the md variables in their generated code are bound in lambdas.