% ----------------------------------------------------------------------------- % Id: HsSyn.lhs,v 1.12 2002/04/04 09:57:33 ross Exp % % (c) The GHC Team, 1997-2000 % Some modifications for use with HDoc made by Armin Groesslinger. % % A suite of datatypes describing the abstract syntax of Haskell 98. % % ----------------------------------------------------------------------------- \begin{code} module HsSyn ( SrcLoc(..), Module(..), HsQName(..), HsName(..), HsModule(..), HsExportSpec(..), HsImportDecl(..), HsImportSpec(..), HsAssoc(..), HsDecl(..), HsMatch(..), HsConDecl(..), HsBangType(..), HsRhs(..), HsGuardedRhs(..), HsQualType(..), HsType(..), HsContext, HsAsst, HsLiteral(..), HsExp(..), HsPat(..), HsPatField(..), HsStmt(..), HsFieldUpdate(..), HsAlt(..), HsGuardedAlts(..), HsGuardedAlt(..), HsFunDep, prelude_mod, main_mod, unit_con_name, tuple_con_name, unit_con, tuple_con, as_name, qualified_name, hiding_name, minus_name, pling_name, export_name, dynamic_name, unsafe_name, ccall_name, stdcall_name, unit_tycon_name, fun_tycon_name, list_tycon_name, tuple_tycon_name, unit_tycon, fun_tycon, list_tycon, tuple_tycon ) where data SrcLoc = SrcLoc Int Int -- (Line, Indentation) deriving (Eq,Ord,Show) newtype Module = Module String deriving (Eq,Ord,Show) data HsQName = Qual Module HsName | UnQual HsName deriving (Eq,Ord) instance Show HsQName where showsPrec _ (Qual (Module m) s) = showString m . showString "." . shows s showsPrec _ (UnQual s) = shows s data HsName = HsIdent String | HsSymbol String | HsSpecial String deriving (Eq,Ord) instance Show HsName where showsPrec _ (HsIdent s) = showString s showsPrec _ (HsSymbol s) = showString s showsPrec _ (HsSpecial s) = showString s data HsModule = HsModule SrcLoc Module (Maybe [HsExportSpec]) [HsImportDecl] [HsDecl] deriving Show -- Export/Import Specifications data HsExportSpec = HsEVar HsQName -- variable | HsEAbs HsQName -- T | HsEThingAll HsQName -- T(..) | HsEThingWith HsQName [HsName] -- T(C_1,...,C_n) | HsEModuleContents Module -- module M (not for imports) deriving (Eq,Show) data HsImportDecl = HsImportDecl SrcLoc Module Bool (Maybe Module) (Maybe (Bool,[HsImportSpec])) deriving (Eq,Show) data HsImportSpec = HsIVar HsName -- variable | HsIAbs HsName -- T | HsIThingAll HsName -- T(..) | HsIThingWith HsName [HsName] -- T(C_1,...,C_n) deriving (Eq,Show) data HsAssoc = HsAssocNone | HsAssocLeft | HsAssocRight deriving (Eq,Show) data HsDecl = HsTypeDecl SrcLoc HsName [HsName] HsType | HsDataDecl SrcLoc HsContext HsName [HsName] [HsConDecl] [HsQName] | HsInfixDecl SrcLoc HsAssoc Int [HsName] | HsNewTypeDecl SrcLoc HsContext HsName [HsName] HsConDecl [HsQName] | HsClassDecl SrcLoc HsQualType [HsFunDep] [HsDecl] | HsInstDecl SrcLoc HsQualType [HsDecl] | HsDefaultDecl SrcLoc [HsType] | HsTypeSig SrcLoc [HsName] HsQualType | HsFunBind SrcLoc [HsMatch] | HsPatBind SrcLoc HsPat HsRhs {-where-} [HsDecl] deriving (Eq,Show) type HsFunDep = ([HsName],[HsName]) data HsMatch = HsMatch SrcLoc HsName [HsPat] HsRhs {-where-} [HsDecl] deriving (Eq,Show) data HsConDecl = HsConDecl SrcLoc [HsName] HsContext HsName [HsBangType] | HsRecDecl SrcLoc HsName [([HsName],HsBangType)] deriving (Eq,Show) data HsBangType = HsBangedTy HsType | HsUnBangedTy HsType deriving (Eq,Show) data HsRhs = HsUnGuardedRhs HsExp | HsGuardedRhss [HsGuardedRhs] deriving (Eq,Show) data HsGuardedRhs = HsGuardedRhs SrcLoc [HsStmt] HsExp deriving (Eq,Show) data HsQualType = HsQualType [HsName] HsContext HsType | HsUnQualType HsType deriving (Eq,Show) data HsType = HsTyFun HsType HsType | HsTyTuple [HsType] | HsTyApp HsType HsType | HsTyVar HsName | HsTyCon HsQName | HsTyForall [HsName] HsType deriving (Eq,Show) type HsContext = [HsAsst] type HsAsst = (HsQName,[HsType]) -- for multi-parameter type classes data HsLiteral = HsInt Integer | HsChar Char | HsString String | HsFrac Rational -- GHC unboxed literals: | HsCharPrim Char | HsStringPrim String | HsIntPrim Integer | HsFloatPrim Rational | HsDoublePrim Rational deriving (Eq, Show) data HsExp = HsVar HsQName | HsCon HsQName | HsLit HsLiteral | HsInfixApp HsExp HsExp HsExp | HsApp HsExp HsExp | HsNegApp HsExp | HsLambda [HsPat] HsExp | HsLet [HsDecl] HsExp | HsIf HsExp HsExp HsExp | HsCase HsExp [HsAlt] | HsDo [HsStmt] | HsTuple [HsExp] | HsList [HsExp] | HsParen HsExp | HsLeftSection HsExp HsExp | HsRightSection HsExp HsExp | HsRecConstr HsQName [HsFieldUpdate] | HsRecUpdate HsExp [HsFieldUpdate] | HsEnumFrom HsExp | HsEnumFromTo HsExp HsExp | HsEnumFromThen HsExp HsExp | HsEnumFromThenTo HsExp HsExp HsExp | HsListComp HsExp [HsStmt] | HsExpTypeSig SrcLoc HsExp HsQualType | HsAsPat HsName HsExp -- pattern only | HsWildCard -- ditto | HsIrrPat HsExp -- ditto -- HsCCall (ghc extension) -- HsSCC (ghc extension) deriving (Eq,Show) data HsPat = HsPVar HsName | HsPLit HsLiteral | HsPNeg HsPat | HsPInfixApp HsPat HsQName HsPat | HsPApp HsQName [HsPat] | HsPTuple [HsPat] | HsPList [HsPat] | HsPParen HsPat | HsPRec HsQName [HsPatField] | HsPAsPat HsName HsPat | HsPWildCard | HsPIrrPat HsPat deriving (Eq,Show) data HsPatField = HsPFieldPat HsQName HsPat deriving (Eq,Show) data HsStmt = HsGenerator HsPat HsExp | HsQualifier HsExp | HsLetStmt [HsDecl] deriving (Eq,Show) data HsFieldUpdate = HsFieldUpdate HsQName HsExp deriving (Eq,Show) data HsAlt = HsAlt SrcLoc HsPat HsGuardedAlts [HsDecl] deriving (Eq,Show) data HsGuardedAlts = HsUnGuardedAlt HsExp | HsGuardedAlts [HsGuardedAlt] deriving (Eq,Show) data HsGuardedAlt = HsGuardedAlt SrcLoc [HsStmt] HsExp deriving (Eq,Show) ----------------------------------------------------------------------------- -- Builtin names. prelude_mod = Module "Prelude" main_mod = Module "Main" unit_con_name = Qual prelude_mod (HsSpecial "()") tuple_con_name i = Qual prelude_mod (HsSpecial ("("++replicate i ','++")")) unit_con = HsCon unit_con_name tuple_con i = HsCon (tuple_con_name i) as_name = HsIdent "as" qualified_name = HsIdent "qualified" hiding_name = HsIdent "hiding" minus_name = HsSymbol "-" pling_name = HsSymbol "!" export_name = HsIdent "export" unsafe_name = HsIdent "unsafe" dynamic_name = HsIdent "dynamic" ccall_name = HsIdent "ccall" stdcall_name = HsIdent "stdcall" unit_tycon_name = unit_con_name fun_tycon_name = Qual prelude_mod (HsSymbol "->") list_tycon_name = Qual prelude_mod (HsIdent "[]") tuple_tycon_name i = tuple_con_name i unit_tycon = HsTyCon unit_tycon_name fun_tycon = HsTyCon fun_tycon_name list_tycon = HsTyCon list_tycon_name tuple_tycon i = HsTyCon (tuple_tycon_name i) \end{code}