Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data ConLike
- conLikeConLikeName :: ConLike -> ConLikeName
- isVanillaConLike :: ConLike -> Bool
- conLikeArity :: ConLike -> Arity
- conLikeFieldLabels :: ConLike -> [FieldLabel]
- conLikeConInfo :: ConLike -> ConInfo
- conLikeInstOrigArgTys :: ConLike -> [Type] -> [Scaled Type]
- conLikeUserTyVarBinders :: ConLike -> [InvisTVBinder]
- conLikeExTyCoVars :: ConLike -> [TyCoVar]
- conLikeName :: ConLike -> Name
- conLikeStupidTheta :: ConLike -> ThetaType
- conLikeImplBangs :: ConLike -> [HsImplBang]
- conLikeFullSig :: ConLike -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, ThetaType, [Scaled Type], Type)
- conLikeResTy :: ConLike -> [Type] -> Type
- conLikeFieldType :: ConLike -> FieldLabelString -> Type
- conLikeIsInfix :: ConLike -> Bool
- conLikeHasBuilder :: ConLike -> Bool
Documentation
A constructor-like thing
Instances
NamedThing ConLike Source # | |
Uniquable ConLike Source # | |
Outputable ConLike Source # | |
OutputableBndr ConLike Source # | |
Defined in GHC.Core.ConLike | |
Data ConLike Source # | |
Defined in GHC.Core.ConLike gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConLike -> c ConLike # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConLike # toConstr :: ConLike -> Constr # dataTypeOf :: ConLike -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConLike) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConLike) # gmapT :: (forall b. Data b => b -> b) -> ConLike -> ConLike # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConLike -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConLike -> r # gmapQ :: (forall d. Data d => d -> u) -> ConLike -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConLike -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike # | |
Eq ConLike Source # | |
type Anno ConLike Source # | |
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
conLikeConInfo :: ConLike -> ConInfo Source #
conLikeInstOrigArgTys :: ConLike -> [Type] -> [Scaled Type] Source #
Returns just the instantiated value argument types of a ConLike
,
(excluding dictionary args)
conLikeUserTyVarBinders :: ConLike -> [InvisTVBinder] Source #
TyVarBinder
s 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
conLikeName :: ConLike -> Name Source #
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
conLikeFieldType :: ConLike -> FieldLabelString -> Type Source #
Extract the type for any given labelled field of the ConLike
conLikeIsInfix :: ConLike -> Bool Source #
conLikeHasBuilder :: ConLike -> Bool Source #
conLikeHasBuilder
returns True except for
uni-directional pattern synonyms, which have no builder