ghc-9.6.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Core.ConLike

Synopsis

Documentation

data ConLike Source #

A constructor-like thing

Instances

Instances details
Data ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConLike -> c ConLike Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConLike Source #

toConstr :: ConLike -> Constr Source #

dataTypeOf :: ConLike -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConLike) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConLike) Source #

gmapT :: (forall b. Data b => b -> b) -> ConLike -> ConLike Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConLike -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConLike -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConLike -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConLike -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike Source #

NamedThing ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Uniquable ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Outputable ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Methods

ppr :: ConLike -> SDoc Source #

OutputableBndr ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Eq ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Methods

(==) :: ConLike -> ConLike -> Bool #

(/=) :: ConLike -> ConLike -> Bool #

type Anno ConLike Source # 
Instance details

Defined in GHC.Hs.Pat

isVanillaConLike :: ConLike -> Bool Source #

Is this a 'vanilla' constructor-like thing (no existentials, no provided constraints)?

conLikeArity :: ConLike -> Arity Source #

Number of arguments

conLikeFieldLabels :: ConLike -> [FieldLabel] Source #

Names of fields used for selectors

conLikeInstOrigArgTys :: ConLike -> [Type] -> [Scaled Type] Source #

Returns just the instantiated value argument types of a ConLike, (excluding dictionary args)

conLikeUserTyVarBinders :: ConLike -> [InvisTVBinder] Source #

TyVarBinders for the type variables of the ConLike. For pattern synonyms, this will always consist of the universally quantified variables followed by the existentially quantified type variables. For data constructors, the situation is slightly more complicated—see Note [DataCon user type variable binders] in GHC.Core.DataCon.

conLikeExTyCoVars :: ConLike -> [TyCoVar] Source #

Existentially quantified type/coercion variables

conLikeStupidTheta :: ConLike -> ThetaType Source #

The "stupid theta" of the ConLike, such as data Eq a in:

data Eq a => T a = ...

It is empty for PatSynCon as they do not allow such contexts. See Note [The stupid context] in GHC.Core.DataCon.

conLikeImplBangs :: ConLike -> [HsImplBang] Source #

Returns the strictness information for each constructor

conLikeFullSig :: ConLike -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, ThetaType, [Scaled Type], Type) Source #

The "full signature" of the ConLike returns, in order:

1) The universally quantified type variables

2) The existentially quantified type/coercion variables

3) The equality specification

4) The provided theta (the constraints provided by a match)

5) The required theta (the constraints required for a match)

6) The original argument types (i.e. before any change of the representation of the type)

7) The original result type

conLikeResTy :: ConLike -> [Type] -> Type Source #

Returns the type of the whole pattern

conLikeFieldType :: ConLike -> FieldLabelString -> Type Source #

Extract the type for any given labelled field of the ConLike

conLikesWithFields :: [ConLike] -> [FieldLabelString] -> [ConLike] Source #

The ConLikes that have *all* the given fields

conLikeHasBuilder :: ConLike -> Bool Source #

conLikeHasBuilder returns True except for uni-directional pattern synonyms, which have no builder