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

Contents

Description

Haskell data types, instances, and helper functions over these types for the syntax of Pads.

Synopsis

Documentation

data PadsDecl Source #

AST form of a pads declaration with four flavors.

Constructors

PadsDeclType String [String] (Maybe Pat) PadsTy (Maybe Exp)

A pads type declaration e.g.:

[pads| type           Foo     x y z   (foo :: Int) = (x, y, z, foo) generator <|gen|> |]
PadsDeclData String [String] (Maybe Pat) PadsData [QString]

A pads data declaration e.g.:

[pads| data           Foo     x y z   (foo :: Int) = Foo (x, y, z, foo) deriving (Eq, Ord, Show) |]
PadsDeclNew String [String] (Maybe Pat) BranchInfo [QString]

A pads newtype declaration e.g.:

[pads| newtype        Foo     x y z   (foo :: Int) = Foo (x, y, z, foo) deriving (Eq, Ord, Show) |]
PadsDeclObtain String [String] PadsTy Exp (Maybe Exp)

A pads declaration for obtaining one type after parsing it from another, e.g.:

[pads| obtain         Foo     x y z   from   Int    using <|(fncn,inverse)|> generator <|gen|> |]
Instances
Eq PadsDecl Source # 
Instance details

Defined in Language.Pads.Syntax

Data PadsDecl Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

toConstr :: PadsDecl -> Constr #

dataTypeOf :: PadsDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PadsDecl Source # 
Instance details

Defined in Language.Pads.Syntax

Generic PadsDecl Source # 
Instance details

Defined in Language.Pads.Syntax

Associated Types

type Rep PadsDecl :: Type -> Type #

Methods

from :: PadsDecl -> Rep PadsDecl x #

to :: Rep PadsDecl x -> PadsDecl #

Lift PadsDecl Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

lift :: PadsDecl -> Q Exp #

Pretty PadsDecl Source # 
Instance details

Defined in Language.Pads.Pretty

Methods

ppr :: PadsDecl -> Doc #

pprPrec :: Int -> PadsDecl -> Doc #

pprList :: [PadsDecl] -> Doc #

type Rep PadsDecl Source # 
Instance details

Defined in Language.Pads.Syntax

type Rep PadsDecl = D1 (MetaData "PadsDecl" "Language.Pads.Syntax" "pads-haskell-0.1.0.0-3ZehAU3aw5R3wNd4fiPXSj" False) ((C1 (MetaCons "PadsDeclType" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Pat)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp))))) :+: C1 (MetaCons "PadsDeclData" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Pat)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsData) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QString]))))) :+: (C1 (MetaCons "PadsDeclNew" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Pat)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BranchInfo) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QString])))) :+: C1 (MetaCons "PadsDeclObtain" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp)))))))

data PadsTy Source #

AST form of a pads type, as notably used to the right hand side of an equals sign in a PadsDecl pads declaration.

Constructors

PConstrain Pat PadsTy Exp

AST form of "constrain Pat :: PadsTy where Exp" e.g.:

[pads| constrain x :: Digit where <|x `mod` 2|> == 0|> |]
PTransform PadsTy PadsTy Exp (Maybe Exp)

AST form of "transform PadsTy => PadsTy using Exp" e.g.:

[pads| transform StringFW 1 => Char using <|(head, list1)|> |]
PList PadsTy (Maybe PadsTy) (Maybe TermCond)

AST form of a list of some PadsTy type, comes with two optional attributes e.g.: "[ PadsTy | PadsTy ] terminator TermCond"

The following PadsTy describes a comma-separated list of integers terminated by the EOF symbol:

[pads| [Int | ','] terminator EOF |]
PPartition PadsTy Exp

AST form of a partitioned type "partition PadsTy using Exp" e.g.:

[pads| partition Entries using <| bytes 6 |> |]

A partitioned type allows for parser extensions to make use of the state of the PADS parser in deciding how to divide up (partition) the input.

PValue Exp PadsTy

AST form of a value constructor "value Exp :: PadsTy" e.g.:

[pads| data Foo = Foo { x :: Int, xIsEven = value <| even x |> :: Bool } |]

This allows you to do the opposite of what BConstr does: bring names into scope which get stored in the output of the parser (rather than having them disappear after the parser finishes.

PApp [PadsTy] (Maybe Exp)

A pads type application like "PadsTy PadsTy PadsTy ... Exp" e.g.

[pads| data Foo      = Foo { x :: Int, Bar x <| x + 1 |> |]
PTuple [PadsTy]

AST form of a pads tuple "( 'PadsTy', 'PadsTy', ... )" e.g.

[pads| (Int, "+", Int) |]
PExpression Exp

An arbitrary Haskell expression as used in a PApp pads type application and in a PSwitch pads switch/case type.

PTycon QString

Pads type constructor with a qualified name

PTyvar String

Pads type variable with a name

Instances
Eq PadsTy Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

Data PadsTy Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

toConstr :: PadsTy -> Constr #

dataTypeOf :: PadsTy -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PadsTy Source # 
Instance details

Defined in Language.Pads.Syntax

Generic PadsTy Source # 
Instance details

Defined in Language.Pads.Syntax

Associated Types

type Rep PadsTy :: Type -> Type #

Methods

from :: PadsTy -> Rep PadsTy x #

to :: Rep PadsTy x -> PadsTy #

Lift PadsTy Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

lift :: PadsTy -> Q Exp #

Pretty PadsTy Source # 
Instance details

Defined in Language.Pads.Pretty

Methods

ppr :: PadsTy -> Doc #

pprPrec :: Int -> PadsTy -> Doc #

pprList :: [PadsTy] -> Doc #

type Rep PadsTy Source # 
Instance details

Defined in Language.Pads.Syntax

type Rep PadsTy = D1 (MetaData "PadsTy" "Language.Pads.Syntax" "pads-haskell-0.1.0.0-3ZehAU3aw5R3wNd4fiPXSj" False) (((C1 (MetaCons "PConstrain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) :+: C1 (MetaCons "PTransform" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp))))) :+: (C1 (MetaCons "PList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PadsTy)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TermCond)))) :+: (C1 (MetaCons "PPartition" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) :+: C1 (MetaCons "PValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy))))) :+: ((C1 (MetaCons "PApp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PadsTy]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp))) :+: C1 (MetaCons "PTuple" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PadsTy]))) :+: (C1 (MetaCons "PExpression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) :+: (C1 (MetaCons "PTycon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QString)) :+: C1 (MetaCons "PTyvar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))

data TermCond Source #

Parser terminator condition

Constructors

LTerm PadsTy

Lexical terminator type: any PadsTy signaling termination

LLen Exp

Lexical length: arbitrary Haskell 'Exp'

Instances
Eq TermCond Source # 
Instance details

Defined in Language.Pads.Syntax

Data TermCond Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

toConstr :: TermCond -> Constr #

dataTypeOf :: TermCond -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TermCond Source # 
Instance details

Defined in Language.Pads.Syntax

Generic TermCond Source # 
Instance details

Defined in Language.Pads.Syntax

Associated Types

type Rep TermCond :: Type -> Type #

Methods

from :: TermCond -> Rep TermCond x #

to :: Rep TermCond x -> TermCond #

Lift TermCond Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

lift :: TermCond -> Q Exp #

Pretty TermCond Source # 
Instance details

Defined in Language.Pads.Pretty

Methods

ppr :: TermCond -> Doc #

pprPrec :: Int -> TermCond -> Doc #

pprList :: [TermCond] -> Doc #

type Rep TermCond Source # 
Instance details

Defined in Language.Pads.Syntax

type Rep TermCond = D1 (MetaData "TermCond" "Language.Pads.Syntax" "pads-haskell-0.1.0.0-3ZehAU3aw5R3wNd4fiPXSj" False) (C1 (MetaCons "LTerm" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PadsTy)) :+: C1 (MetaCons "LLen" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))

data PadsData Source #

Right-hand side of a pads data type declaration

Constructors

PUnion [BranchInfo]

A pads union data type declaration. Syntax: "BranchInfo | BranchInfo | ..."

PSwitch Exp [(Pat, BranchInfo)]

A pads switch-case statement.

Syntax:

   case Exp of
     Pat -> BranchInfo
   | Pat -> BranchInfo
   ...
[pads| case <| tag + 1 |> of
         2 -> Foo
       | 3 -> Bar
|]
Instances
Eq PadsData Source # 
Instance details

Defined in Language.Pads.Syntax

Data PadsData Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

toConstr :: PadsData -> Constr #

dataTypeOf :: PadsData -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PadsData Source # 
Instance details

Defined in Language.Pads.Syntax

Generic PadsData Source # 
Instance details

Defined in Language.Pads.Syntax

Associated Types

type Rep PadsData :: Type -> Type #

Methods

from :: PadsData -> Rep PadsData x #

to :: Rep PadsData x -> PadsData #

Lift PadsData Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

lift :: PadsData -> Q Exp #

Pretty PadsData Source # 
Instance details

Defined in Language.Pads.Pretty

Methods

ppr :: PadsData -> Doc #

pprPrec :: Int -> PadsData -> Doc #

pprList :: [PadsData] -> Doc #

type Rep PadsData Source # 
Instance details

Defined in Language.Pads.Syntax

data BranchInfo Source #

An individual branch of some pads data type, either defining a Haskell record parser or a Haskell constructor parser.

Constructors

BRecord String [FieldInfo] (Maybe Exp)

Branch record with a constructor name, list of record fields, and maybe a boolean 'where' clause.

Syntax: String { FieldInfo, FieldInfo, ... } where 'Exp'

[pads| Foo { x :: Int, y :: Char } where <| x == ord y |>
BConstr String [ConstrArg] (Maybe Exp)

Branch constructor with a constructor name, a list of argument types, and maybe a boolean 'where' clause:

Syntax: String ConstrArg ConstrArg ... where 'Exp'

[pads| Foo (x :: Int) (y :: Char) where <| x == ord y |>

Note that this lets you bring variables into scope during parsing (x and y in the above) *without* saving them into the parse result, effectively making them operate as temporary variables that can be referenced by the Haskell predicates.

Instances
Eq BranchInfo Source # 
Instance details

Defined in Language.Pads.Syntax

Data BranchInfo Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

toConstr :: BranchInfo -> Constr #

dataTypeOf :: BranchInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BranchInfo Source # 
Instance details

Defined in Language.Pads.Syntax

Generic BranchInfo Source # 
Instance details

Defined in Language.Pads.Syntax

Associated Types

type Rep BranchInfo :: Type -> Type #

Lift BranchInfo Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

lift :: BranchInfo -> Q Exp #

Pretty BranchInfo Source # 
Instance details

Defined in Language.Pads.Pretty

type Rep BranchInfo Source # 
Instance details

Defined in Language.Pads.Syntax

type FieldInfo = (Maybe String, ConstrArg, Maybe Exp, Maybe Exp) Source #

Individual field of a pads record, "String :: ConstrArg where Exp"

data PadsStrict Source #

A hold-over resulting from a deprecation moving from an older version of template-haskell.

Constructors

IsStrict 
NotStrict 
Unpacked 
Instances
Eq PadsStrict Source # 
Instance details

Defined in Language.Pads.Syntax

Data PadsStrict Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

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

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

toConstr :: PadsStrict -> Constr #

dataTypeOf :: PadsStrict -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PadsStrict Source # 
Instance details

Defined in Language.Pads.Syntax

Generic PadsStrict Source # 
Instance details

Defined in Language.Pads.Syntax

Associated Types

type Rep PadsStrict :: Type -> Type #

Lift PadsStrict Source # 
Instance details

Defined in Language.Pads.Syntax

Methods

lift :: PadsStrict -> Q Exp #

type Rep PadsStrict Source # 
Instance details

Defined in Language.Pads.Syntax

type Rep PadsStrict = D1 (MetaData "PadsStrict" "Language.Pads.Syntax" "pads-haskell-0.1.0.0-3ZehAU3aw5R3wNd4fiPXSj" False) (C1 (MetaCons "IsStrict" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NotStrict" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Unpacked" PrefixI False) (U1 :: Type -> Type)))

type QString = [String] Source #

Qualified names where [Foo, Bar] means Foo.Bar

hasRep :: PadsTy -> Bool Source #

Whether or not a PadsTy has an underlying Haskell representation

qName :: QString -> String Source #

["Foo", "Bar"] -> "Foo.Bar"

Orphan instances

Lift Exp Source # 
Instance details

Methods

lift :: Exp -> Q Exp #

Lift Pat Source # 
Instance details

Methods

lift :: Pat -> Q Exp #