fourmolu-0.19.0.0: A formatter for Haskell source code
Safe HaskellNone
LanguageGHC2021

Ormolu.Printer.Meat.Type

Description

Rendering of types.

Synopsis

Documentation

hasDocStrings :: HsType GhcPs -> Bool Source #

Return True if at least one argument in HsType has a doc string attached to it.

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 #

p_forallBndrs :: HasLoc l => ForAllVisibility -> (a -> R ()) -> [GenLocated l a] -> R () Source #

Render several forall-ed variables.

class (Anno a ~ SrcSpanAnnA, Outputable a) => FunRepr a where Source #

Instances

Instances details
FunRepr (HsExpr GhcPs) Source #

Function types in expressions, e.g. with -XRequiredTypeArguments

Instance details

Defined in Ormolu.Printer.Meat.Declaration.Value

FunRepr (HsType GhcPs) Source # 
Instance details

Defined in Ormolu.Printer.Meat.Type

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.