| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
ConLike
Synopsis
- data ConLike
- conLikeArity :: ConLike -> Arity
- conLikeFieldLabels :: ConLike -> [FieldLabel]
- conLikeInstOrigArgTys :: ConLike -> [Type] -> [Type]
- conLikeExTyVars :: ConLike -> [TyVar]
- conLikeName :: ConLike -> Name
- conLikeStupidTheta :: ConLike -> ThetaType
- conLikeWrapId_maybe :: ConLike -> Maybe Id
- conLikeImplBangs :: ConLike -> [HsImplBang]
- conLikeFullSig :: ConLike -> ([TyVar], [TyVar], [EqSpec], ThetaType, ThetaType, [Type], Type)
- conLikeResTy :: ConLike -> [Type] -> Type
- conLikeFieldType :: ConLike -> FieldLabelString -> Type
- conLikesWithFields :: [ConLike] -> [FieldLabelString] -> [ConLike]
- conLikeIsInfix :: ConLike -> Bool
Documentation
A constructor-like thing
Constructors
| RealDataCon DataCon | |
| PatSynCon PatSyn | 
Instances
| Eq ConLike Source # | |
| Data ConLike Source # | |
| Defined in ConLike Methods 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 :: (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 # | |
| OutputableBndr ConLike Source # | |
| Outputable ConLike Source # | |
| Uniquable ConLike Source # | |
| NamedThing ConLike Source # | |
conLikeArity :: ConLike -> Arity Source #
Number of arguments
conLikeFieldLabels :: ConLike -> [FieldLabel] Source #
Names of fields used for selectors
conLikeInstOrigArgTys :: ConLike -> [Type] -> [Type] Source #
Returns just the instantiated value argument types of a ConLike,
 (excluding dictionary args)
conLikeExTyVars :: ConLike -> [TyVar] Source #
Existentially quantified type variables
conLikeName :: ConLike -> Name Source #
conLikeWrapId_maybe :: ConLike -> Maybe Id Source #
Returns the Id of the wrapper. This is also known as the builder in
 some contexts. The value is Nothing only in the case of unidirectional
 pattern synonyms.
conLikeImplBangs :: ConLike -> [HsImplBang] Source #
Returns the strictness information for each constructor
conLikeFullSig :: ConLike -> ([TyVar], [TyVar], [EqSpec], ThetaType, ThetaType, [Type], Type) Source #
The "full signature" of the ConLike returns, in order:
1) The universally quantified type variables
2) The existentially quantified type 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
conLikesWithFields :: [ConLike] -> [FieldLabelString] -> [ConLike] Source #
The ConLikes that have *all* the given fields
conLikeIsInfix :: ConLike -> Bool Source #