| 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 | 
Language.Pads.Syntax
Contents
Description
Haskell data types, instances, and helper functions over these types for the syntax of Pads.
Documentation
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
AST form of a pads type, as notably used to the right hand side of an
 equals sign in a  pads declaration.PadsDecl
Constructors
| PConstrain Pat PadsTy Exp | AST form of "constrain  [pads| constrain x :: Digit where <|x `mod` 2|> == 0|> |]  | 
| PTransform PadsTy PadsTy Exp (Maybe Exp) | AST form of "transform  [pads| transform StringFW 1 => Char using <|(head, list1)|> |]  | 
| PList PadsTy (Maybe PadsTy) (Maybe TermCond) | AST form of a list of some  The following  [pads| [Int | ','] terminator EOF |]  | 
| PPartition PadsTy Exp | AST form of a partitioned type "partition  [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  [pads| data Foo = Foo { x :: Int, xIsEven = value <| even x |> :: Bool } |]This allows you to do the opposite of what   | 
| PApp [PadsTy] (Maybe Exp) | A pads type application like " [pads| data Foo      = Foo { x :: Int, Bar x <| x + 1 |> |] | 
| PTuple [PadsTy] | AST form of a pads tuple "(  [pads| (Int, "+", Int) |]  | 
| PExpression Exp | An arbitrary Haskell expression as used in a   | 
| PTycon QString | Pads type constructor with a qualified name  | 
| PTyvar String | Pads type variable with a name  | 
Instances
Parser terminator condition
Constructors
| LTerm PadsTy | Lexical terminator type: any   | 
| LLen Exp | Lexical length: arbitrary Haskell   | 
Instances
| Eq TermCond Source # | |
| Data TermCond Source # | |
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 # | |
| Generic TermCond Source # | |
| Lift TermCond Source # | |
| Pretty TermCond Source # | |
| type Rep TermCond Source # | |
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)))  | |
Right-hand side of a pads data type declaration
Constructors
| PUnion [BranchInfo] | A pads union data type declaration.
 Syntax: "  | 
| PSwitch Exp [(Pat, BranchInfo)] | A pads switch-case  Syntax: case [pads| case <| tag + 1 |> of
         2 -> Foo
       | 3 -> Bar
|] | 
Instances
| Eq PadsData Source # | |
| Data PadsData Source # | |
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 # | |
| Generic PadsData Source # | |
| Lift PadsData Source # | |
| Pretty PadsData Source # | |
| type Rep PadsData Source # | |
Defined in Language.Pads.Syntax type Rep PadsData = D1 (MetaData "PadsData" "Language.Pads.Syntax" "pads-haskell-0.1.0.0-3ZehAU3aw5R3wNd4fiPXSj" False) (C1 (MetaCons "PUnion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [BranchInfo])) :+: C1 (MetaCons "PSwitch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Pat, BranchInfo)])))  | |
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:  [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:  [pads| Foo (x :: Int) (y :: Char) where <| x == ord y |> Note that this lets you bring variables into scope during parsing (  | 
Instances
data PadsStrict Source #
A hold-over resulting from a deprecation moving from an older version of template-haskell.
Instances
| Eq PadsStrict Source # | |
Defined in Language.Pads.Syntax  | |
| Data PadsStrict Source # | |
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 # | |
Defined in Language.Pads.Syntax Methods showsPrec :: Int -> PadsStrict -> ShowS # show :: PadsStrict -> String # showList :: [PadsStrict] -> ShowS #  | |
| Generic PadsStrict Source # | |
Defined in Language.Pads.Syntax Associated Types type Rep PadsStrict :: Type -> Type #  | |
| Lift PadsStrict Source # | |
Defined in Language.Pads.Syntax Methods lift :: PadsStrict -> Q Exp #  | |
| type Rep PadsStrict Source # | |
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)))  | |