Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Tc.Gen.Expr
Description
Typecheck an expression
Synopsis
- tcCheckExpr :: LHsExpr GhcRn -> TcSigmaType -> TcM (LHsExpr GhcTc)
- tcLExpr :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc)
- tcLExprNC :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc)
- tcExpr :: HsExpr GhcRn -> ExpRhoType -> TcM (HsExpr GhcTc)
- tcInferSigma :: LHsExpr GhcRn -> TcM (LHsExpr GhcTc, TcSigmaType)
- tcInferRho :: LHsExpr GhcRn -> TcM (LHsExpr GhcTc, TcRhoType)
- tcInferRhoNC :: LHsExpr GhcRn -> TcM (LHsExpr GhcTc, TcRhoType)
- tcSyntaxOp :: CtOrigin -> SyntaxExprRn -> [SyntaxOpType] -> ExpRhoType -> ([TcSigmaType] -> TcM a) -> TcM (a, SyntaxExprTc)
- tcSyntaxOpGen :: CtOrigin -> SyntaxExprRn -> [SyntaxOpType] -> SyntaxOpType -> ([TcSigmaType] -> TcM a) -> TcM (a, SyntaxExprTc)
- data SyntaxOpType
- synKnownType :: TcType -> SyntaxOpType
- tcCheckId :: Name -> ExpRhoType -> TcM (HsExpr GhcTc)
- addAmbiguousNameErr :: RdrName -> TcM ()
- getFixedTyVars :: [FieldLabelString] -> [TyVar] -> [ConLike] -> TyVarSet
Documentation
tcCheckExpr :: LHsExpr GhcRn -> TcSigmaType -> TcM (LHsExpr GhcTc) Source #
tcInferSigma :: LHsExpr GhcRn -> TcM (LHsExpr GhcTc, TcSigmaType) Source #
Arguments
:: CtOrigin | |
-> SyntaxExprRn | |
-> [SyntaxOpType] | shape of syntax operator arguments |
-> ExpRhoType | overall result type |
-> ([TcSigmaType] -> TcM a) | Type check any arguments |
-> TcM (a, SyntaxExprTc) |
Typecheck a syntax operator The operator is a variable or a lambda at this stage (i.e. renamer output)
tcSyntaxOpGen :: CtOrigin -> SyntaxExprRn -> [SyntaxOpType] -> SyntaxOpType -> ([TcSigmaType] -> TcM a) -> TcM (a, SyntaxExprTc) Source #
Slightly more general version of tcSyntaxOp
that allows the caller
to specify the shape of the result of the syntax operator
data SyntaxOpType Source #
What to expect for an argument to a rebindable-syntax operator.
Quite like Type
, but allows for holes to be filled in by tcSyntaxOp.
The callback called from tcSyntaxOp gets a list of types; the meaning
of these types is determined by a left-to-right depth-first traversal
of the SyntaxOpType
tree. So if you pass in
SynAny `SynFun` (SynList `SynFun` SynType Int) `SynFun` SynAny
you'll get three types back: one for the first SynAny
, the element
type of the list, and one for the last SynAny
. You don't get anything
for the SynType
, because you've said positively that it should be an
Int, and so it shall be.
This is defined here to avoid defining it in GHC.Tc.Gen.Expr boot file.
Constructors
SynAny | Any type |
SynRho | A rho type, deeply skolemised or instantiated as appropriate |
SynList | A list type. You get back the element type of the list |
SynFun SyntaxOpType SyntaxOpType infixr 0 | A function. |
SynType ExpType | A known type. |
synKnownType :: TcType -> SyntaxOpType Source #
Like SynType
but accepts a regular TcType
addAmbiguousNameErr :: RdrName -> TcM () Source #
This name really is ambiguous, so add a suitable "ambiguous occurrence" error, then continue
getFixedTyVars :: [FieldLabelString] -> [TyVar] -> [ConLike] -> TyVarSet Source #