|
|
|
|
|
| Description |
| Abstract Haskell syntax for expressions.
|
|
| Synopsis |
|
| type LHsExpr id = Located (HsExpr id) | | | type PostTcExpr = HsExpr Id | | | type PostTcTable = [(Name, Id)] | | | noPostTcExpr :: PostTcExpr | | | noPostTcTable :: PostTcTable | | | type SyntaxExpr id = HsExpr id | | | noSyntaxExpr :: SyntaxExpr id | | | type SyntaxTable id = [(Name, SyntaxExpr id)] | | | noSyntaxTable :: SyntaxTable id | | | | | | | tupArgPresent :: HsTupArg id -> Bool | | | type PendingSplice = (Name, LHsExpr Id) | | | pprLExpr :: OutputableBndr id => LHsExpr id -> SDoc | | | pprExpr :: OutputableBndr id => HsExpr id -> SDoc | | | isQuietHsExpr :: HsExpr id -> Bool | | | pprBinds :: (OutputableBndr idL, OutputableBndr idR) => HsLocalBindsLR idL idR -> SDoc | | | ppr_lexpr :: OutputableBndr id => LHsExpr id -> SDoc | | | ppr_expr :: OutputableBndr id => HsExpr id -> SDoc | | | pprCmdArg :: OutputableBndr id => HsCmdTop id -> SDoc | | | pa_brackets :: SDoc -> SDoc | | | pprDebugParendExpr :: OutputableBndr id => LHsExpr id -> SDoc | | | pprParendExpr :: OutputableBndr id => LHsExpr id -> SDoc | | | isAtomicHsExpr :: HsExpr id -> Bool | | | type HsCmd id = HsExpr id | | | type LHsCmd id = LHsExpr id | | | | | type LHsCmdTop id = Located (HsCmdTop id) | | | data HsCmdTop id = HsCmdTop (LHsCmd id) [PostTcType] PostTcType (SyntaxTable id) | | | type HsRecordBinds id = HsRecFields id (LHsExpr id) | | | data MatchGroup id = MatchGroup [LMatch id] PostTcType | | | type LMatch id = Located (Match id) | | | data Match id = Match [LPat id] (Maybe (LHsType id)) (GRHSs id) | | | isEmptyMatchGroup :: MatchGroup id -> Bool | | | matchGroupArity :: MatchGroup id -> Arity | | | hsLMatchPats :: LMatch id -> [LPat id] | | | data GRHSs id = GRHSs {} | | | type LGRHS id = Located (GRHS id) | | | data GRHS id = GRHS [LStmt id] (LHsExpr id) | | | pprMatches :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> MatchGroup idR -> SDoc | | | pprFunBind :: (OutputableBndr idL, OutputableBndr idR) => idL -> Bool -> MatchGroup idR -> SDoc | | | pprPatBind :: (OutputableBndr bndr, OutputableBndr id) => LPat bndr -> GRHSs id -> SDoc | | | pprMatch :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> Match idR -> SDoc | | | pprGRHSs :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> GRHSs idR -> SDoc | | | pprGRHS :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> GRHS idR -> SDoc | | | pp_rhs :: OutputableBndr idR => HsMatchContext idL -> LHsExpr idR -> SDoc | | | type LStmt id = Located (StmtLR id id) | | | type LStmtLR idL idR = Located (StmtLR idL idR) | | | type Stmt id = StmtLR id id | | | | | | | pprStmt :: (OutputableBndr idL, OutputableBndr idR) => StmtLR idL idR -> SDoc | | | pprGroupByClause :: OutputableBndr id => GroupByClause id -> SDoc | | | pprDo :: OutputableBndr id => HsStmtContext any -> [LStmt id] -> LHsExpr id -> SDoc | | | ppr_do_stmts :: OutputableBndr id => [LStmt id] -> LHsExpr id -> SDoc | | | pprComp :: OutputableBndr id => (SDoc -> SDoc) -> [LStmt id] -> LHsExpr id -> SDoc | | | data HsSplice id = HsSplice id (LHsExpr id) | | | pprSplice :: OutputableBndr id => HsSplice id -> SDoc | | | | | pprHsBracket :: OutputableBndr id => HsBracket id -> SDoc | | | thBrackets :: SDoc -> SDoc -> SDoc | | | | | pp_dotdot :: SDoc | | | | | | | isDoExpr :: HsStmtContext id -> Bool | | | isListCompExpr :: HsStmtContext id -> Bool | | | matchSeparator :: HsMatchContext id -> SDoc | | | pprMatchContext :: Outputable id => HsMatchContext id -> SDoc | | | pprStmtContext :: Outputable id => HsStmtContext id -> SDoc | | | matchContextErrString :: Outputable id => HsMatchContext id -> SDoc | | | pprMatchInCtxt :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> Match idR -> SDoc | | | pprStmtInCtxt :: (OutputableBndr idL, OutputableBndr idR) => HsStmtContext idL -> StmtLR idL idR -> SDoc |
|
|
|
| Expressions proper
|
|
|
|
|
| PostTcExpr is an evidence expression attached to the syntax tree by the
type checker (c.f. postTcType).
|
|
|
| We use a PostTcTable where there are a bunch of pieces of evidence, more
than is convenient to keep individually.
|
|
|
|
|
|
|
SyntaxExpr is like PostTcExpr, but it's filled in a little earlier,
by the renamer. It's used for rebindable syntax.
E.g. (>>=) is filled in before the renamer by the appropriate Name for
(>>=), and then instantiated by the type checker with its type args
tec
|
|
|
|
|
Currently used only for CmdTop (sigh)
- Before the renamer, this list is noSyntaxTable
- After the renamer, it takes the form [(std_name, HsVar actual_name)]
For example, for the return op of a monad
- normal case: (GHC.Base.return, HsVar GHC.Base.return)
- with rebindable syntax: (GHC.Base.return, return_22)
where return_22 is whatever return is in scope
- After the type checker, it takes the form [(std_name, expression)]
where expression is the evidence for the method
|
|
|
|
|
| A Haskell expression.
| | Constructors | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | HsHigherOrderApp | | | HsFirstOrderApp | |
|
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| GRHSs are used both for pattern bindings and for Matches
| | Constructors | | GRHSs | | | grhssGRHSs :: [LGRHS id] | Guarded RHSs
| | grhssLocalBinds :: HsLocalBinds id | The where clause
|
|
|
|
|
|
|
|
| Guarded Right Hand Side.
| | Constructors | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Produced by Haddock version 2.6.1 |