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.MetaData

Description

 

Synopsis

Documentation

data Base_md Source #

Base type library support for internal (to Pads) metadata

Constructors

Base_md 

Instances

Eq Base_md Source # 

Methods

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

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

Data Base_md Source # 

Methods

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

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

toConstr :: Base_md -> Constr #

dataTypeOf :: Base_md -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Base_md Source # 
Show Base_md Source # 
Pretty Base_md Source # 

Methods

ppr :: Base_md -> Doc #

pprPrec :: Int -> Base_md -> Doc #

pprList :: [Base_md] -> Doc #

PadsMD Base_md Source #

The trivial case for when the Pads parser doesn't need to add any metadata.

Pads1 () Void Base_md Source # 
Pads1 () Binary Base_md Source # 
Pads1 () Text Base_md Source # 
Pads a a_md => Pads1 () (PMaybe a) (PMaybe_md a_md) Source # 

Methods

def1 :: () -> PMaybe a Source #

defaultMd1 :: () -> PMaybe a -> PMaybe_md a_md Source #

parsePP1 :: () -> PadsParser (PMaybe a, PMaybe_md a_md) Source #

printFL1 :: () -> PadsPrinter (PMaybe a, PMaybe_md a_md) Source #

defaultRepMd1 :: () -> (PMaybe a, PMaybe_md a_md) Source #

Data b => PadsMD (Base_md, b) Source #

If we have a 2-tuple where the first thing is of type Base_md, then the tuple itself is a Pads metadata instance.

class Data md => PadsMD md where Source #

Meta data type class

Minimal complete definition

get_md_header, replace_md_header

Instances

PadsMD Base_md Source #

The trivial case for when the Pads parser doesn't need to add any metadata.

Data b => PadsMD (Base_md, b) Source #

If we have a 2-tuple where the first thing is of type Base_md, then the tuple itself is a Pads metadata instance.

cleanBasePD :: Base_md Source #

Default metadata instance with no errors being reported.

errorBasePD :: String -> String -> Base_md Source #

Default metadata instance with a generic "file error" being reported.

mergeBaseMDs :: [Base_md] -> Base_md Source #

Metadata merge

mkErrBasePDfromLoc :: ErrMsg -> Loc -> Base_md Source #

Metadata for a single parse error occuring at some location Loc.

mkErrBasePD :: ErrMsg -> Maybe Span -> Base_md Source #

Metadata for a single parse error occuring at some position Span.

pprBaseMD :: Base_md -> Doc Source #

Pretty printer for the base metadata type.

myempty :: forall a. Data a => a Source #

Fancy Generic magic for defining a function that produces a default value for any type so long as that type is an instance of Data. We do this by selecting the first alternative of algebraic data types and recursively filling in any nested types with default values as well. For instance:

> :set -XDeriveDataTypeable
> type Bar = (Int,Char)
> data Foo = A Bar Bar | B | C deriving (Data, Show)
> myempty :: Foo
A (0,'\NUL') (0,'\NUL')