module Language.Haskell.Exts.Syntax (
Module(..), WarningText(..), ExportSpec(..),
ImportDecl(..), ImportSpec(..), Assoc(..),
Decl(..), Binds(..), IPBind(..),
ClassDecl(..), InstDecl(..), Deriving,
DataOrNew(..), ConDecl(..), QualConDecl(..), GadtDecl(..), BangType(..),
Match(..), Rhs(..), GuardedRhs(..),
Context, FunDep(..), Asst(..),
Type(..), Boxed(..), Kind(..), TyVarBind(..),
Exp(..), Stmt(..), QualStmt(..), FieldUpdate(..),
Alt(..), GuardedAlts(..), GuardedAlt(..), XAttr(..),
Pat(..), PatField(..), PXAttr(..), RPat(..), RPatOp(..),
Literal(..),
ModuleName(..), QName(..), Name(..), QOp(..), Op(..),
SpecialCon(..), CName(..), IPName(..), XName(..),
Bracket(..), Splice(..),
Safety(..), CallConv(..),
ModulePragma(..), Tool(..),
Rule(..), RuleVar(..), Activation(..),
Annotation(..),
prelude_mod, main_mod,
main_name,
unit_con_name, tuple_con_name, list_cons_name, unboxed_singleton_con_name,
unit_con, tuple_con, unboxed_singleton_con,
as_name, qualified_name, hiding_name, minus_name, bang_name, dot_name, star_name,
export_name, safe_name, unsafe_name, threadsafe_name,
stdcall_name, ccall_name, cplusplus_name, dotnet_name, jvm_name, js_name,
forall_name, family_name,
unit_tycon_name, fun_tycon_name, list_tycon_name, tuple_tycon_name, unboxed_singleton_tycon_name,
unit_tycon, fun_tycon, list_tycon, tuple_tycon, unboxed_singleton_tycon,
SrcLoc(..),
) where
#ifdef __GLASGOW_HASKELL__
#ifdef BASE4
import Data.Data
#else
import Data.Generics (Data(..),Typeable(..))
#endif
#endif
import Language.Haskell.Exts.SrcLoc (SrcLoc(..))
import Language.Haskell.Exts.Annotated.Syntax (Boxed(..), Tool(..))
newtype ModuleName = ModuleName String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data SpecialCon
= UnitCon
| ListCon
| FunCon
| TupleCon Boxed Int
| Cons
| UnboxedSingleCon
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data QName
= Qual ModuleName Name
| UnQual Name
| Special SpecialCon
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Name
= Ident String
| Symbol String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data IPName
= IPDup String
| IPLin String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data QOp
= QVarOp QName
| QConOp QName
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Op
= VarOp Name
| ConOp Name
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data CName
= VarName Name
| ConName Name
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Module = Module SrcLoc ModuleName [ModulePragma] (Maybe WarningText)
(Maybe [ExportSpec]) [ImportDecl] [Decl]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data ExportSpec
= EVar QName
| EAbs QName
| EThingAll QName
| EThingWith QName [CName]
| EModuleContents ModuleName
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data ImportDecl = ImportDecl
{ importLoc :: SrcLoc
, importModule :: ModuleName
, importQualified :: Bool
, importSrc :: Bool
, importPkg :: Maybe String
, importAs :: Maybe ModuleName
, importSpecs :: Maybe (Bool,[ImportSpec])
}
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data ImportSpec
= IVar Name
| IAbs Name
| IThingAll Name
| IThingWith Name [CName]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Assoc
= AssocNone
| AssocLeft
| AssocRight
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
type Deriving = (QName, [Type])
data Decl
= TypeDecl SrcLoc Name [TyVarBind] Type
| TypeFamDecl SrcLoc Name [TyVarBind] (Maybe Kind)
| DataDecl SrcLoc DataOrNew Context Name [TyVarBind] [QualConDecl] [Deriving]
| GDataDecl SrcLoc DataOrNew Context Name [TyVarBind] (Maybe Kind) [GadtDecl] [Deriving]
| DataFamDecl SrcLoc Context Name [TyVarBind] (Maybe Kind)
| TypeInsDecl SrcLoc Type Type
| DataInsDecl SrcLoc DataOrNew Type [QualConDecl] [Deriving]
| GDataInsDecl SrcLoc DataOrNew Type (Maybe Kind) [GadtDecl] [Deriving]
| ClassDecl SrcLoc Context Name [TyVarBind] [FunDep] [ClassDecl]
| InstDecl SrcLoc Context QName [Type] [InstDecl]
| DerivDecl SrcLoc Context QName [Type]
| InfixDecl SrcLoc Assoc Int [Op]
| DefaultDecl SrcLoc [Type]
| SpliceDecl SrcLoc Exp
| TypeSig SrcLoc [Name] Type
| FunBind [Match]
| PatBind SrcLoc Pat (Maybe Type) Rhs Binds
| ForImp SrcLoc CallConv Safety String Name Type
| ForExp SrcLoc CallConv String Name Type
| RulePragmaDecl SrcLoc [Rule]
| DeprPragmaDecl SrcLoc [([Name], String)]
| WarnPragmaDecl SrcLoc [([Name], String)]
| InlineSig SrcLoc Bool Activation QName
| InlineConlikeSig SrcLoc Activation QName
| SpecSig SrcLoc Activation QName [Type]
| SpecInlineSig SrcLoc Bool Activation QName [Type]
| InstSig SrcLoc Context QName [Type]
| AnnPragma SrcLoc Annotation
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Annotation
= Ann Name Exp
| TypeAnn Name Exp
| ModuleAnn Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data DataOrNew = DataType | NewType
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Binds
= BDecls [Decl]
| IPBinds [IPBind]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data IPBind = IPBind SrcLoc IPName Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Match
= Match SrcLoc Name [Pat] (Maybe Type) Rhs Binds
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data QualConDecl
= QualConDecl SrcLoc
[TyVarBind] Context
ConDecl
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data ConDecl
= ConDecl Name [BangType]
| InfixConDecl BangType Name BangType
| RecDecl Name [([Name],BangType)]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data GadtDecl
= GadtDecl SrcLoc Name Type
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data ClassDecl
= ClsDecl Decl
| ClsDataFam SrcLoc Context Name [TyVarBind] (Maybe Kind)
| ClsTyFam SrcLoc Name [TyVarBind] (Maybe Kind)
| ClsTyDef SrcLoc Type Type
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data InstDecl
= InsDecl Decl
| InsType SrcLoc Type Type
| InsData SrcLoc DataOrNew Type [QualConDecl] [Deriving]
| InsGData SrcLoc DataOrNew Type (Maybe Kind) [GadtDecl] [Deriving]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data BangType
= BangedTy Type
| UnBangedTy Type
| UnpackedTy Type
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Rhs
= UnGuardedRhs Exp
| GuardedRhss [GuardedRhs]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data GuardedRhs
= GuardedRhs SrcLoc [Stmt] Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Type
= TyForall
(Maybe [TyVarBind])
Context
Type
| TyFun Type Type
| TyTuple Boxed [Type]
| TyList Type
| TyApp Type Type
| TyVar Name
| TyCon QName
| TyParen Type
| TyInfix Type QName Type
| TyKind Type Kind
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data TyVarBind
= KindedVar Name Kind
| UnkindedVar Name
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Kind
= KindStar
| KindBang
| KindFn Kind Kind
| KindParen Kind
| KindVar Name
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data FunDep
= FunDep [Name] [Name]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
type Context = [Asst]
data Asst = ClassA QName [Type]
| InfixA Type QName Type
| IParam IPName Type
| EqualP Type Type
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Literal
= Char Char
| String String
| Int Integer
| Frac Rational
| PrimInt Integer
| PrimWord Integer
| PrimFloat Rational
| PrimDouble Rational
| PrimChar Char
| PrimString String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Exp
= Var QName
| IPVar IPName
| Con QName
| Lit Literal
| InfixApp Exp QOp Exp
| App Exp Exp
| NegApp Exp
| Lambda SrcLoc [Pat] Exp
| Let Binds Exp
| If Exp Exp Exp
| Case Exp [Alt]
| Do [Stmt]
| MDo [Stmt]
| Tuple Boxed [Exp]
| TupleSection Boxed [Maybe Exp]
| List [Exp]
| Paren Exp
| LeftSection Exp QOp
| RightSection QOp Exp
| RecConstr QName [FieldUpdate]
| RecUpdate Exp [FieldUpdate]
| EnumFrom Exp
| EnumFromTo Exp Exp
| EnumFromThen Exp Exp
| EnumFromThenTo Exp Exp Exp
| ListComp Exp [QualStmt]
| ParComp Exp [[QualStmt]]
| ExpTypeSig SrcLoc Exp Type
| VarQuote QName
| TypQuote QName
| BracketExp Bracket
| SpliceExp Splice
| QuasiQuote String String
| XTag SrcLoc XName [XAttr] (Maybe Exp) [Exp]
| XETag SrcLoc XName [XAttr] (Maybe Exp)
| XPcdata String
| XExpTag Exp
| XChildTag SrcLoc [Exp]
| CorePragma String Exp
| SCCPragma String Exp
| GenPragma String (Int, Int) (Int, Int) Exp
| Proc SrcLoc Pat Exp
| LeftArrApp Exp Exp
| RightArrApp Exp Exp
| LeftArrHighApp Exp Exp
| RightArrHighApp Exp Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data XName
= XName String
| XDomName String String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data XAttr = XAttr XName Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Bracket
= ExpBracket Exp
| PatBracket Pat
| TypeBracket Type
| DeclBracket [Decl]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Splice
= IdSplice String
| ParenSplice Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Safety
= PlayRisky
| PlaySafe Bool
| PlayInterruptible
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data CallConv
= StdCall
| CCall
| CPlusPlus
| DotNet
| Jvm
| Js
| CApi
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data ModulePragma
= LanguagePragma SrcLoc [Name]
| OptionsPragma SrcLoc (Maybe Tool) String
| AnnModulePragma SrcLoc Annotation
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Activation
= AlwaysActive
| ActiveFrom Int
| ActiveUntil Int
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Rule
= Rule String Activation (Maybe [RuleVar]) Exp Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data RuleVar
= RuleVar Name
| TypedRuleVar Name Type
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data WarningText
= DeprText String
| WarnText String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Pat
= PVar Name
| PLit Literal
| PNeg Pat
| PNPlusK Name Integer
| PInfixApp Pat QName Pat
| PApp QName [Pat]
| PTuple Boxed [Pat]
| PList [Pat]
| PParen Pat
| PRec QName [PatField]
| PAsPat Name Pat
| PWildCard
| PIrrPat Pat
| PatTypeSig SrcLoc Pat Type
| PViewPat Exp Pat
| PRPat [RPat]
| PXTag SrcLoc XName [PXAttr] (Maybe Pat) [Pat]
| PXETag SrcLoc XName [PXAttr] (Maybe Pat)
| PXPcdata String
| PXPatTag Pat
| PXRPats [RPat]
| PExplTypeArg QName Type
| PQuasiQuote String String
| PBangPat Pat
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data PXAttr = PXAttr XName Pat
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data RPatOp
= RPStar
| RPStarG
| RPPlus
| RPPlusG
| RPOpt
| RPOptG
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data RPat
= RPOp RPat RPatOp
| RPEither RPat RPat
| RPSeq [RPat]
| RPGuard Pat [Stmt]
| RPCAs Name RPat
| RPAs Name RPat
| RPParen RPat
| RPPat Pat
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data PatField
= PFieldPat QName Pat
| PFieldPun Name
| PFieldWildcard
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Stmt
= Generator SrcLoc Pat Exp
| Qualifier Exp
| LetStmt Binds
| RecStmt [Stmt]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data QualStmt
= QualStmt Stmt
| ThenTrans Exp
| ThenBy Exp Exp
| GroupBy Exp
| GroupUsing Exp
| GroupByUsing Exp Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data FieldUpdate
= FieldUpdate QName Exp
| FieldPun Name
| FieldWildcard
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data Alt
= Alt SrcLoc Pat GuardedAlts Binds
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data GuardedAlts
= UnGuardedAlt Exp
| GuardedAlts [GuardedAlt]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data GuardedAlt
= GuardedAlt SrcLoc [Stmt] Exp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
prelude_mod, main_mod :: ModuleName
prelude_mod = ModuleName "Prelude"
main_mod = ModuleName "Main"
main_name :: Name
main_name = Ident "main"
unit_con_name :: QName
unit_con_name = Special UnitCon
tuple_con_name :: Boxed -> Int -> QName
tuple_con_name b i = Special (TupleCon b (i+1))
list_cons_name :: QName
list_cons_name = Special Cons
unboxed_singleton_con_name :: QName
unboxed_singleton_con_name = Special UnboxedSingleCon
unit_con :: Exp
unit_con = Con unit_con_name
tuple_con :: Boxed -> Int -> Exp
tuple_con b i = Con (tuple_con_name b i)
unboxed_singleton_con :: Exp
unboxed_singleton_con = Con (unboxed_singleton_con_name)
as_name, qualified_name, hiding_name, minus_name, bang_name, dot_name, star_name :: Name
as_name = Ident "as"
qualified_name = Ident "qualified"
hiding_name = Ident "hiding"
minus_name = Symbol "-"
bang_name = Symbol "!"
dot_name = Symbol "."
star_name = Symbol "*"
export_name, safe_name, unsafe_name, threadsafe_name,
stdcall_name, ccall_name, cplusplus_name, dotnet_name,
jvm_name, js_name, forall_name, family_name :: Name
export_name = Ident "export"
safe_name = Ident "safe"
unsafe_name = Ident "unsafe"
threadsafe_name = Ident "threadsafe"
stdcall_name = Ident "stdcall"
ccall_name = Ident "ccall"
cplusplus_name = Ident "cplusplus"
dotnet_name = Ident "dotnet"
jvm_name = Ident "jvm"
js_name = Ident "js"
forall_name = Ident "forall"
family_name = Ident "family"
unit_tycon_name, fun_tycon_name, list_tycon_name, unboxed_singleton_tycon_name :: QName
unit_tycon_name = unit_con_name
fun_tycon_name = Special FunCon
list_tycon_name = Special ListCon
unboxed_singleton_tycon_name = Special UnboxedSingleCon
tuple_tycon_name :: Boxed -> Int -> QName
tuple_tycon_name b i = tuple_con_name b i
unit_tycon, fun_tycon, list_tycon, unboxed_singleton_tycon :: Type
unit_tycon = TyCon unit_tycon_name
fun_tycon = TyCon fun_tycon_name
list_tycon = TyCon list_tycon_name
unboxed_singleton_tycon = TyCon unboxed_singleton_tycon_name
tuple_tycon :: Boxed -> Int -> Type
tuple_tycon b i = TyCon (tuple_tycon_name b i)