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
- data Base_md = Base_md {}
- class Data md => PadsMD md where
- get_md_header :: md -> Base_md
- replace_md_header :: md -> Base_md -> md
- cleanBasePD :: Base_md
- errorBasePD :: String -> String -> Base_md
- mergeBaseMDs :: [Base_md] -> Base_md
- mkErrBasePDfromLoc :: ErrMsg -> Loc -> Base_md
- mkErrBasePD :: ErrMsg -> Maybe Span -> Base_md
- pprBaseMD :: Base_md -> Doc
- myempty :: forall a. Data a => a
Documentation
Base type library support for internal (to Pads) metadata
Instances
Eq Base_md Source # | |
Data Base_md Source # | |
Defined in Language.Pads.MetaData 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 # | |
PadsMD Base_md Source # | The trivial case for when the Pads parser doesn't need to add any metadata. |
Defined in Language.Pads.MetaData | |
Pads1 Int Bytes Bytes_md Source # | |
Pads1 () Char Base_md Source # | |
Pads1 () Double Base_md Source # | |
Pads1 () Float Base_md Source # | |
Pads1 () Int Base_md Source # | |
Pads1 () Integer Base_md Source # | |
Pads1 () String Base_md Source # | |
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 # | |
Defined in Language.Pads.BaseTypes | |
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. |
Defined in Language.Pads.MetaData |
class Data md => PadsMD md where Source #
Meta data type class
get_md_header :: md -> Base_md Source #
replace_md_header :: md -> Base_md -> md Source #
Instances
PadsMD Base_md Source # | The trivial case for when the Pads parser doesn't need to add any metadata. |
Defined in Language.Pads.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. |
Defined in Language.Pads.MetaData |
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
.
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')