pads-haskell-0.0.0.1: 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.Source

Contents

Description

 

Synopsis

Documentation

data Source Source #

Input source abstraction

Constructors

Source 

Fields

  • current :: ByteString

    The current input before EOR

  • rest :: ByteString

    The rest of the input after the next EOR

  • loc :: Loc

    The current location Loc in the input

  • bit :: Int

    Bit offset into the current input being parsed

  • disc :: RecordDiscipline

    The record discipline of this input source

  • eorAtEOF :: Bool

    Relevant for seperator-based record disciplines: Single, Multi Set when current record is last record and separtor appeared at end.

Instances

Pretty Source Source # 

Methods

ppr :: Source -> Doc #

pprPrec :: Int -> Source -> Doc #

pprList :: [Source] -> Doc #

data RecordDiscipline Source #

A record discipline specifies the manner by which pads should partition the input into records. Note that the record character gets consumed internally by the parsing monad.

Constructors

Single Word8

Split input based on a single 8-bit unsigned integer (character)

Multi ByteString

Split input based on more than one character

Bytes Int

Split the input into records every Int characters

NoPartition

No partitioning of the input - all input data is in the current field

NoDiscipline

No discipline is currently installed; all input data is in rest field

newline :: RecordDiscipline Source #

Record discipline for Unix newlines

windows :: RecordDiscipline Source #

Record discipline for Windows CRLF newlines

bytes :: Int -> RecordDiscipline Source #

Record discipline for every n characters

none :: RecordDiscipline Source #

No record discipline

data Loc Source #

Source location information.

Constructors

Loc 

Fields

Instances

Eq Loc Source # 

Methods

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

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

Data Loc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc #

toConstr :: Loc -> Constr #

dataTypeOf :: Loc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Loc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) #

gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r #

gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

Ord Loc Source # 

Methods

compare :: Loc -> Loc -> Ordering #

(<) :: Loc -> Loc -> Bool #

(<=) :: Loc -> Loc -> Bool #

(>) :: Loc -> Loc -> Bool #

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

max :: Loc -> Loc -> Loc #

min :: Loc -> Loc -> Loc #

Show Loc Source # 

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Pretty Loc Source # 

Methods

ppr :: Loc -> Doc #

pprPrec :: Int -> Loc -> Doc #

pprList :: [Loc] -> Doc #

data Span Source #

A span in the source input, covering a contiguous range of the Source input. AFAIK there's no distinction between the states where begin == end and where end == Nothing.

Constructors

Span 

Fields

Instances

Eq Span Source # 

Methods

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

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

Data Span Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Span -> c Span #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Span #

toConstr :: Span -> Constr #

dataTypeOf :: Span -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Span) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span) #

gmapT :: (forall b. Data b => b -> b) -> Span -> Span #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQ :: (forall d. Data d => d -> u) -> Span -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Span -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

Ord Span Source # 

Methods

compare :: Span -> Span -> Ordering #

(<) :: Span -> Span -> Bool #

(<=) :: Span -> Span -> Bool #

(>) :: Span -> Span -> Bool #

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

max :: Span -> Span -> Span #

min :: Span -> Span -> Span #

Show Span Source # 

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Pretty Span Source # 

Methods

ppr :: Span -> Doc #

pprPrec :: Int -> Span -> Doc #

pprList :: [Span] -> Doc #

zeroLoc :: Loc Source #

Initial instance of a Loc

zeroSpan :: Span Source #

A span starting at the beginning of the file and containing nothing.

zeroBit :: Int Source #

Parse the most significant bit in a byte first

incRecordNumber :: Loc -> Loc Source #

Increment how many records have been seen in the given Loc

decLineNumber :: Loc -> Loc Source #

Decrement how many records have been seen in the given Loc

incOffset :: Loc -> Loc Source #

Increment the offset of the Loc by one

incOffsetBy :: Loc -> Int -> Loc Source #

Increment the offset of the given Loc by some number

decOffset :: Loc -> Loc Source #

Decrement the offset of the given Loc by one

Source Creation

emptySource :: Source Source #

An empty Source with reasonable defaults for everything.

padsSourceFromString :: String -> Source Source #

Stuff the given String into a Source with a newline discipline by default (see padsSourceFromByteString)

padsSourceFromStringWithDisc :: RecordDiscipline -> String -> Source Source #

Stuff the given String into a Source with the given record discipline

padsSourceFromFileWithDisc :: RecordDiscipline -> FilePath -> IO Source Source #

Read a Source from disk using the given record discipline

padsSourceFromByteString :: ByteString -> Source Source #

Construct a Source from the given ByteString, preparing the first record immediately.

isEOF :: Source -> Bool Source #

Whether or not the Source has consumed all available input

isEOR :: Source -> Bool Source #

Whether or not the Source has consumed all input in the current record

Record Manipulating Functions

Converting Sources to Strings

Operations within a single record

takeHeadStr :: String -> Source -> (Bool, Source) Source #

If the front of the current source input matches the given string then remove it and return the modified source. Otherwise return the original source and a boolean flag indicating that we failed to take the given string off the front of the source input.

scanStr :: String -> Source -> (Maybe String, Source) Source #

Scan the current source input until we find the given string: - If we don't find the string return Nothing and leave source unmodified - If we return (Maybe []), then we found the string at the beginning of the source and removed it. - If we return (Maybe junk), then we found the string somewhere after the first character in the source and we consumed / removed (junk:str).

regexMatch :: RE -> Source -> (Maybe String, Source) Source #

Match the beginning of the source input with a regex, returning a tuple of the matched string and the modified source with that string removed.

regexStop :: RE -> Source -> (Maybe String, Source) Source #

Find the first match of a regex in the source input, returning the contents of the source input *before* the match. * If there's no match return Nothing and leave the source unmodified. * If there's a match, return the string before the match and remove *just* the string before from the source input.

span :: (Word8 -> Bool) -> Source -> ([Word8], Source) Source #

Remove and return the longest prefix of the source input satisfying the given predicate.

whileS :: (Char -> Bool) -> Source -> Maybe (String, Source) Source #

Same as span but for predicates over type Char.

tail :: Source -> Source Source #

Remove the first byte of the input source.

scanTo :: Char -> Source -> (Bool, Source, Span) Source #

Scan the input source until we find the given character. If we don't find the character indicate as such with the boolean (False) and remove all source input from the current record. If we do find the character, return True and consume input up to and including the matched character. The Span in the returned tuple indicates the region in the input that got scanned and removed by this function (whether or not we failed to find the character).

Pretty print sources