pads-haskell-0.1.0.0: PADS data description language for Haskell.

Copyright(c) 2011
Kathleen Fisher <kathleen.fisher@gmail.com>
John Launchbury <john.launchbury@gmail.com>
LicenseMIT
MaintainerKarl Cronburg <karl@cs.tufts.edu>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Language.Pads.CoreBaseTypes

Contents

Description

 
Synopsis

Documentation

type Char_md = Base_md Source #

Metadata type for a PADS Char

char_parseM :: PadsParser (Char, Base_md) Source #

Monadic parser for a PADS Char

char_def :: Char Source #

Default value inserted by the parser for a PADS Char

int_parseM :: PadsParser (Int, Base_md) Source #

Monadic parser for a PADS Int

int_def :: Int Source #

Default value inserted by the 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"

float_def :: Float Source #

Default value inserted by the parser for a PADS Float

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

digit_def :: Digit Source #

Default value inserted by the parser for a PADS Digit

string_def :: [Char] Source #

Default value inserted by the parser for a PADS String

type StringC = String Source #

string with end character. Ex:

StringC ','

type StringFW = String Source #

string of fixed length

type StringVW = String Source #

string of variable length

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

data Chunk Source #

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)

Constructors

CharChunk Char 
BinaryChunk 

Fields

Instances
Eq Chunk Source # 
Instance details

Defined in Language.Pads.CoreBaseTypes

Methods

(==) :: Chunk -> Chunk -> Bool #

(/=) :: Chunk -> Chunk -> Bool #

Show CList Source # 
Instance details

Defined in Language.Pads.CoreBaseTypes

Methods

showsPrec :: Int -> CList -> ShowS #

show :: CList -> String #

showList :: [CList] -> ShowS #

Show Chunk Source # 
Instance details

Defined in Language.Pads.CoreBaseTypes

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

Lift Chunk Source # 
Instance details

Defined in Language.Pads.CoreBaseTypes

Methods

lift :: Chunk -> Q Exp #

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.

type EOF = () Source #

End of File

type EOR = () Source #

End of Record

md :: Base_md Source #

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.

Orphan instances

Pads1 Int Bytes Bytes_md Source # 
Instance details

Pads1 () Char Base_md Source # 
Instance details

Pads1 () Double Base_md Source # 
Instance details

Pads1 () Float Base_md Source # 
Instance details

Pads1 () Int Base_md Source # 
Instance details

Pads1 () Integer Base_md Source # 
Instance details

Pads1 () String Base_md Source # 
Instance details