ghc-8.6.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

RdrHsSyn

Synopsis

Documentation

mkTyClD :: LTyClDecl (GhcPass p) -> LHsDecl (GhcPass p) Source #

mkClassDecl builds a RdrClassDecl, filling in the names for tycon and datacon by deriving them from the name of the class. We fill in the names for the tycon and datacon corresponding to the class, by deriving them from the name of the class itself. This saves recording the names in the interface file (which would be equally good).

setRdrNameSpace :: RdrName -> NameSpace -> RdrName Source #

This rather gruesome function is used mainly by the parser. When parsing:

data T a = T | T1 Int

we parse the data constructors as types because of parser ambiguities, so then we need to change the type constr to a data constr

The exact-name case can occur when parsing:

data [] a = [] | a : [a]

For the exact-name case we return an original name.

filterCTuple :: RdrName -> RdrName Source #

Replaces constraint tuple names with corresponding boxed ones.

cvTopDecls :: OrdList (LHsDecl GhcPs) -> [LHsDecl GhcPs] Source #

Function definitions are restructured here. Each is assumed to be recursive initially, and non recursive definitions are discovered by the dependency analyser.

checkBlockArguments :: LHsExpr GhcPs -> P () Source #

Yield a parse error if we have a function applied directly to a do block etc. and BlockArguments is not enabled.

checkContext :: LHsType GhcPs -> P ([AddAnn], LHsContext GhcPs) Source #

Validate the context constraints and break up a context into a list of predicates.

    (Eq a, Ord b)        -->  [Eq a, Ord b]
    Eq a                 -->  [Eq a]
    (Eq a)               -->  [Eq a]
    (((Eq a)))           -->  [Eq a]

checkInfixConstr :: LHsType GhcPs -> P (LHsType GhcPs, Maybe LHsDocString) Source #

Given a type that is a field to an infix data constructor, try to split off a trailing docstring on the type, and check that there are no other docstrings.

checkEmptyGADTs :: Located ([AddAnn], [LConDecl GhcPs]) -> P (Located ([AddAnn], [LConDecl GhcPs])) Source #

Check if the gadt_constrlist is empty. Only raise parse error for `data T where` to avoid affecting existing error message, see #8258.

hintBangPat :: SrcSpan -> HsExpr GhcPs -> P () Source #

Hint about bang patterns, assuming BangPatterns is off.

splitTilde :: [LHsType GhcPs] -> P (LHsType GhcPs) Source #

Transform a list of atype with strict_mark into HsOpTy's of eqTyCon_RDR:

~a, ~b, c, ~d
==> (~a) ~ ((b c) ~ d)

See Note [Parsing ~]

data TyEl Source #

Either an operator or an operand.

mergeOps :: [Located TyEl] -> P (LHsType GhcPs) Source #

Merge a reversed and non-empty soup of operators and operands into a type.

User input: F x y + G a b * X Input to mergeOps: [X, *, b, a, G, +, y, x, F] Output corresponds to what the user wrote assuming all operators are of the same fixity and right-associative.

It's a bit silly that we're doing it at all, as the renamer will have to rearrange this, and it'd be easier to keep things separate.