Safe Haskell | None |
---|---|
Language | GHC2021 |
Ormolu.Printer.Meat.Type
Description
Rendering of types.
Synopsis
- p_hsType :: HsType GhcPs -> R ()
- p_hsTypeAnnotation :: LHsType GhcPs -> R ()
- hasDocStrings :: HsType GhcPs -> Bool
- p_hsContext :: HsContext GhcPs -> R ()
- p_hsContext' :: (Outputable (GenLocated (Anno a) a), HasLoc (Anno a)) => (a -> R ()) -> [XRec GhcPs a] -> R ()
- p_hsTyVarBndr :: IsTyVarBndrFlag flag => HsTyVarBndr flag GhcPs -> R ()
- data ForAllVisibility
- p_forallBndrs :: HasLoc l => ForAllVisibility -> (a -> R ()) -> [GenLocated l a] -> R ()
- p_conDeclFields :: [LConDeclField GhcPs] -> R ()
- p_lhsTypeArg :: LHsTypeArg GhcPs -> R ()
- p_hsSigType :: HsSigType GhcPs -> R ()
- class (Anno a ~ SrcSpanAnnA, Outputable a) => FunRepr a where
- renderFunItem :: a -> R ()
- parseFunRepr :: LocatedA a -> ParsedFunRepr a
- data ParsedFunRepr a
- = ParsedFunSig (ParsedFunRepr a)
- | ParsedFunForall (LocatedA (HsForAllTelescope GhcPs)) (ParsedFunRepr a)
- | ParsedFunQuals [LocatedA (LocatedC [LocatedA a])] (ParsedFunRepr a)
- | ParsedFunArgs [LocatedA (LocatedA a, Maybe (LHsDoc GhcPs), HsArrowOf (LocatedA a) GhcPs)] (ParsedFunRepr a)
- | ParsedFunReturn (LocatedA a, Maybe (LHsDoc GhcPs))
- p_hsFun :: FunRepr a => a -> R ()
- hsOuterTyVarBndrsToHsType :: HsOuterTyVarBndrs Specificity GhcPs -> LHsType GhcPs -> HsType GhcPs
- hsSigTypeToType :: HsSigType GhcPs -> HsType GhcPs
- lhsTypeToSigType :: LHsType GhcPs -> LHsSigType GhcPs
Documentation
p_hsContext' :: (Outputable (GenLocated (Anno a) a), HasLoc (Anno a)) => (a -> R ()) -> [XRec GhcPs a] -> R () Source #
p_hsTyVarBndr :: IsTyVarBndrFlag flag => HsTyVarBndr flag GhcPs -> R () Source #
data ForAllVisibility Source #
Constructors
ForAllInvis | |
ForAllVis |
p_forallBndrs :: HasLoc l => ForAllVisibility -> (a -> R ()) -> [GenLocated l a] -> R () Source #
Render several forall
-ed variables.
p_conDeclFields :: [LConDeclField GhcPs] -> R () Source #
p_lhsTypeArg :: LHsTypeArg GhcPs -> R () Source #
class (Anno a ~ SrcSpanAnnA, Outputable a) => FunRepr a where Source #
Instances
FunRepr (HsExpr GhcPs) Source # | Function types in expressions, e.g. with -XRequiredTypeArguments |
Defined in Ormolu.Printer.Meat.Declaration.Value Methods renderFunItem :: HsExpr GhcPs -> R () Source # parseFunRepr :: LocatedA (HsExpr GhcPs) -> ParsedFunRepr (HsExpr GhcPs) Source # | |
FunRepr (HsType GhcPs) Source # | |
Defined in Ormolu.Printer.Meat.Type Methods renderFunItem :: HsType GhcPs -> R () Source # parseFunRepr :: LocatedA (HsType GhcPs) -> ParsedFunRepr (HsType GhcPs) Source # |
data ParsedFunRepr a Source #
The parsed representation of a function
Constructors
ParsedFunSig (ParsedFunRepr a) | |
ParsedFunForall (LocatedA (HsForAllTelescope GhcPs)) (ParsedFunRepr a) | |
ParsedFunQuals [LocatedA (LocatedC [LocatedA a])] (ParsedFunRepr a) | |
ParsedFunArgs [LocatedA (LocatedA a, Maybe (LHsDoc GhcPs), HsArrowOf (LocatedA a) GhcPs)] (ParsedFunRepr a) | The argument, its optional docstring, and the arrow going to the next arg/return |
ParsedFunReturn (LocatedA a, Maybe (LHsDoc GhcPs)) |
p_hsFun :: FunRepr a => a -> R () Source #
For implementing function-arrows and related configuration, we'll collect all the components of the function type first, then render as a block instead of rendering each part independently, which will let us track local state within a function type.
This function should be passed the first function-related construct we find; see FunRepr for more details.