module Language.Haskell.Syntax (
HsModule(..), HsExportSpec(..),
HsImportDecl(..), HsImportSpec(..), HsAssoc(..),
HsDecl(..), HsConDecl(..), HsBangType(..),
HsMatch(..), HsRhs(..), HsGuardedRhs(..),
HsSafety(..),
HsQualType(..), HsContext, HsAsst,
HsType(..),
HsExp(..), HsStmt(..), HsFieldUpdate(..),
HsAlt(..), HsGuardedAlts(..), HsGuardedAlt(..),
HsPat(..), HsPatField(..),
HsLiteral(..),
Module(..), HsQName(..), HsName(..), HsQOp(..), HsOp(..),
HsSpecialCon(..), HsCName(..),
prelude_mod, main_mod,
main_name,
unit_con_name, tuple_con_name, list_cons_name,
unit_con, tuple_con,
unit_tycon_name, fun_tycon_name, list_tycon_name, tuple_tycon_name,
unit_tycon, fun_tycon, list_tycon, tuple_tycon,
SrcLoc(..),
) where
#ifdef __GLASGOW_HASKELL__
import Data.Generics.Basics
import Data.Generics.Instances()
#endif
data SrcLoc = SrcLoc {
srcFilename :: String,
srcLine :: Int,
srcColumn :: Int
}
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
newtype Module = Module String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsSpecialCon
= HsUnitCon
| HsListCon
| HsFunCon
| HsTupleCon Int
| HsCons
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsQName
= Qual Module HsName
| UnQual HsName
| Special HsSpecialCon
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsName
= HsIdent String
| HsSymbol String
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsQOp
= HsQVarOp HsQName
| HsQConOp HsQName
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsOp
= HsVarOp HsName
| HsConOp HsName
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsCName
= HsVarName HsName
| HsConName HsName
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsModule = HsModule SrcLoc Module (Maybe [HsExportSpec])
[HsImportDecl] [HsDecl]
#ifdef __GLASGOW_HASKELL__
deriving (Show,Typeable,Data)
#else
deriving (Show)
#endif
data HsExportSpec
= HsEVar HsQName
| HsEAbs HsQName
| HsEThingAll HsQName
| HsEThingWith HsQName [HsCName]
| HsEModuleContents Module
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsImportDecl = HsImportDecl
{ importLoc :: SrcLoc
, importModule :: Module
, importQualified :: Bool
, importAs :: Maybe Module
, importSpecs :: Maybe (Bool,[HsImportSpec])
}
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsImportSpec
= HsIVar HsName
| HsIAbs HsName
| HsIThingAll HsName
| HsIThingWith HsName [HsCName]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsAssoc
= HsAssocNone
| HsAssocLeft
| HsAssocRight
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsDecl
= HsTypeDecl SrcLoc HsName [HsName] HsType
| HsDataDecl SrcLoc HsContext HsName [HsName] [HsConDecl] [HsQName]
| HsInfixDecl SrcLoc HsAssoc Int [HsOp]
| HsNewTypeDecl SrcLoc HsContext HsName [HsName] HsConDecl [HsQName]
| HsClassDecl SrcLoc HsContext HsName [HsName] [HsDecl]
| HsInstDecl SrcLoc HsContext HsQName [HsType] [HsDecl]
| HsDefaultDecl SrcLoc [HsType]
| HsTypeSig SrcLoc [HsName] HsQualType
| HsFunBind [HsMatch]
| HsPatBind SrcLoc HsPat HsRhs [HsDecl]
| HsForeignImport SrcLoc String HsSafety String HsName HsType
| HsForeignExport SrcLoc String String HsName HsType
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsMatch
= HsMatch SrcLoc HsName [HsPat] HsRhs [HsDecl]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsConDecl
= HsConDecl SrcLoc HsName [HsBangType]
| HsRecDecl SrcLoc HsName [([HsName],HsBangType)]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsBangType
= HsBangedTy HsType
| HsUnBangedTy HsType
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsRhs
= HsUnGuardedRhs HsExp
| HsGuardedRhss [HsGuardedRhs]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsGuardedRhs
= HsGuardedRhs SrcLoc HsExp HsExp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsSafety
= HsSafe
| HsUnsafe
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Ord,Show,Typeable,Data)
#else
deriving (Eq,Ord,Show)
#endif
data HsQualType
= HsQualType HsContext HsType
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsType
= HsTyFun HsType HsType
| HsTyTuple [HsType]
| HsTyApp HsType HsType
| HsTyVar HsName
| HsTyCon HsQName
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
type HsContext = [HsAsst]
type HsAsst = (HsQName,[HsType])
data HsLiteral
= HsChar Char
| HsString String
| HsInt Integer
| HsFrac Rational
| HsCharPrim Char
| HsStringPrim String
| HsIntPrim Integer
| HsFloatPrim Rational
| HsDoublePrim Rational
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsExp
= HsVar HsQName
| HsCon HsQName
| HsLit HsLiteral
| HsInfixApp HsExp HsQOp HsExp
| HsApp HsExp HsExp
| HsNegApp HsExp
| HsLambda SrcLoc [HsPat] HsExp
| HsLet [HsDecl] HsExp
| HsIf HsExp HsExp HsExp
| HsCase HsExp [HsAlt]
| HsDo [HsStmt]
| HsTuple [HsExp]
| HsList [HsExp]
| HsParen HsExp
| HsLeftSection HsExp HsQOp
| HsRightSection HsQOp 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
| HsWildCard
| HsIrrPat HsExp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
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
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsPatField
= HsPFieldPat HsQName HsPat
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsStmt
= HsGenerator SrcLoc HsPat HsExp
| HsQualifier HsExp
| HsLetStmt [HsDecl]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsFieldUpdate
= HsFieldUpdate HsQName HsExp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsAlt
= HsAlt SrcLoc HsPat HsGuardedAlts [HsDecl]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsGuardedAlts
= HsUnGuardedAlt HsExp
| HsGuardedAlts [HsGuardedAlt]
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
data HsGuardedAlt
= HsGuardedAlt SrcLoc HsExp HsExp
#ifdef __GLASGOW_HASKELL__
deriving (Eq,Show,Typeable,Data)
#else
deriving (Eq,Show)
#endif
prelude_mod, main_mod :: Module
prelude_mod = Module "Prelude"
main_mod = Module "Main"
main_name :: HsName
main_name = HsIdent "main"
unit_con_name :: HsQName
unit_con_name = Special HsUnitCon
tuple_con_name :: Int -> HsQName
tuple_con_name i = Special (HsTupleCon (i+1))
list_cons_name :: HsQName
list_cons_name = Special HsCons
unit_con :: HsExp
unit_con = HsCon unit_con_name
tuple_con :: Int -> HsExp
tuple_con i = HsCon (tuple_con_name i)
unit_tycon_name, fun_tycon_name, list_tycon_name :: HsQName
unit_tycon_name = unit_con_name
fun_tycon_name = Special HsFunCon
list_tycon_name = Special HsListCon
tuple_tycon_name :: Int -> HsQName
tuple_tycon_name i = tuple_con_name i
unit_tycon, fun_tycon, list_tycon :: HsType
unit_tycon = HsTyCon unit_tycon_name
fun_tycon = HsTyCon fun_tycon_name
list_tycon = HsTyCon list_tycon_name
tuple_tycon :: Int -> HsType
tuple_tycon i = HsTyCon (tuple_tycon_name i)