Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.PureScript.Types
Description
Data types for types
Synopsis
- type SourceType = Type SourceAnn
- type SourceConstraint = Constraint SourceAnn
- newtype SkolemScope = SkolemScope {}
- data WildcardData
- data TypeVarVisibility
- typeVarVisibilityPrefix :: TypeVarVisibility -> Text
- data Type a
- = TUnknown a Int
- | TypeVar a Text
- | TypeLevelString a PSString
- | TypeLevelInt a Integer
- | TypeWildcard a WildcardData
- | TypeConstructor a (Qualified (ProperName 'TypeName))
- | TypeOp a (Qualified (OpName 'TypeOpName))
- | TypeApp a (Type a) (Type a)
- | KindApp a (Type a) (Type a)
- | ForAll a TypeVarVisibility Text (Maybe (Type a)) (Type a) (Maybe SkolemScope)
- | ConstrainedType a (Constraint a) (Type a)
- | Skolem a Text (Maybe (Type a)) Int SkolemScope
- | REmpty a
- | RCons a Label (Type a) (Type a)
- | KindedType a (Type a) (Type a)
- | BinaryNoParensType a (Type a) (Type a) (Type a)
- | ParensInType a (Type a)
- srcTUnknown :: Int -> SourceType
- srcTypeVar :: Text -> SourceType
- srcTypeLevelString :: PSString -> SourceType
- srcTypeLevelInt :: Integer -> SourceType
- srcTypeWildcard :: SourceType
- srcTypeConstructor :: Qualified (ProperName 'TypeName) -> SourceType
- srcTypeApp :: SourceType -> SourceType -> SourceType
- srcKindApp :: SourceType -> SourceType -> SourceType
- srcForAll :: TypeVarVisibility -> Text -> Maybe SourceType -> SourceType -> Maybe SkolemScope -> SourceType
- srcConstrainedType :: SourceConstraint -> SourceType -> SourceType
- srcREmpty :: SourceType
- srcRCons :: Label -> SourceType -> SourceType -> SourceType
- srcKindedType :: SourceType -> SourceType -> SourceType
- pattern REmptyKinded :: a -> Maybe (Type a) -> Type a
- toREmptyKinded :: Type a -> Maybe (a, Maybe (Type a))
- isREmpty :: Type a -> Bool
- data ConstraintData = PartialConstraintData [[Text]] Bool
- data Constraint a = Constraint {
- constraintAnn :: a
- constraintClass :: Qualified (ProperName 'ClassName)
- constraintKindArgs :: [Type a]
- constraintArgs :: [Type a]
- constraintData :: Maybe ConstraintData
- srcConstraint :: Qualified (ProperName 'ClassName) -> [SourceType] -> [SourceType] -> Maybe ConstraintData -> SourceConstraint
- mapConstraintArgs :: ([Type a] -> [Type a]) -> Constraint a -> Constraint a
- overConstraintArgs :: Functor f => ([Type a] -> f [Type a]) -> Constraint a -> f (Constraint a)
- mapConstraintArgsAll :: ([Type a] -> [Type a]) -> Constraint a -> Constraint a
- overConstraintArgsAll :: Applicative f => ([Type a] -> f [Type a]) -> Constraint a -> f (Constraint a)
- constraintDataToJSON :: ConstraintData -> Value
- constraintToJSON :: (a -> Value) -> Constraint a -> Value
- typeVarVisToJSON :: TypeVarVisibility -> Value
- typeToJSON :: (a -> Value) -> Type a -> Value
- constraintDataFromJSON :: Value -> Parser ConstraintData
- constraintFromJSON :: Parser a -> (Value -> Parser a) -> Value -> Parser (Constraint a)
- typeVarVisFromJSON :: Value -> Parser TypeVarVisibility
- typeFromJSON :: Parser a -> (Value -> Parser a) -> Value -> Parser (Type a)
- data RowListItem a = RowListItem {
- rowListAnn :: a
- rowListLabel :: Label
- rowListType :: Type a
- srcRowListItem :: Label -> SourceType -> RowListItem SourceAnn
- rowToList :: Type a -> ([RowListItem a], Type a)
- rowToSortedList :: Type a -> ([RowListItem a], Type a)
- rowFromList :: ([RowListItem a], Type a) -> Type a
- alignRowsWith :: (Label -> Type a -> Type a -> r) -> Type a -> Type a -> ([r], (([RowListItem a], Type a), ([RowListItem a], Type a)))
- isMonoType :: Type a -> Bool
- mkForAll :: [(a, (Text, Maybe (Type a)))] -> Type a -> Type a
- replaceTypeVars :: Text -> Type a -> Type a -> Type a
- replaceAllTypeVars :: [(Text, Type a)] -> Type a -> Type a
- genPureName :: Text -> [Text] -> Text
- addVisibility :: [(Text, TypeVarVisibility)] -> Type a -> Type a
- usedTypeVariables :: Type a -> [Text]
- freeTypeVariables :: Type a -> [Text]
- completeBinderList :: Type a -> Maybe ([(a, (Text, Type a))], Type a)
- quantify :: Type a -> Type a
- moveQuantifiersToFront :: a -> Type a -> Type a
- containsForAll :: Type a -> Bool
- unknowns :: Type a -> IntSet
- containsUnknowns :: Type a -> Bool
- eraseKindApps :: Type a -> Type a
- eraseForAllKindAnnotations :: Type a -> Type a
- unapplyTypes :: Type a -> (Type a, [Type a], [Type a])
- unapplyConstraints :: Type a -> ([Constraint a], Type a)
- srcInstanceType :: SourceSpan -> [(Text, SourceType)] -> Qualified (ProperName 'ClassName) -> [SourceType] -> SourceType
- everywhereOnTypes :: (Type a -> Type a) -> Type a -> Type a
- everywhereOnTypesM :: Monad m => (Type a -> m (Type a)) -> Type a -> m (Type a)
- everywhereOnTypesTopDownM :: Monad m => (Type a -> m (Type a)) -> Type a -> m (Type a)
- everythingOnTypes :: (r -> r -> r) -> (Type a -> r) -> Type a -> r
- everythingWithContextOnTypes :: s -> r -> (r -> r -> r) -> (s -> Type a -> (s, r)) -> Type a -> r
- annForType :: forall a f. Functor f => (a -> f a) -> Type a -> f (Type a)
- getAnnForType :: Type a -> a
- setAnnForType :: a -> Type a -> Type a
- eqType :: Type a -> Type b -> Bool
- eqMaybeType :: Maybe (Type a) -> Maybe (Type b) -> Bool
- compareType :: Type a -> Type b -> Ordering
- compareMaybeType :: Maybe (Type a) -> Maybe (Type b) -> Ordering
- eqConstraint :: Constraint a -> Constraint b -> Bool
- compareConstraint :: Constraint a -> Constraint b -> Ordering
Documentation
type SourceType = Type SourceAnn #
type SourceConstraint = Constraint SourceAnn #
newtype SkolemScope #
An identifier for the scope of a skolem variable
Constructors
SkolemScope | |
Fields |
Instances
data WildcardData #
Describes how a TypeWildcard should be presented to the user during type checking: holes (?foo) are always emitted as errors, whereas unnamed wildcards (_) default to warnings, but are ignored entirely if they are contained by a binding with a complete (wildcard-free) type signature.
Constructors
HoleWildcard Text | |
UnnamedWildcard | |
IgnoredWildcard |
Instances
FromJSON WildcardData # | |||||
Defined in Language.PureScript.Types | |||||
ToJSON WildcardData # | |||||
Defined in Language.PureScript.Types Methods toJSON :: WildcardData -> Value # toEncoding :: WildcardData -> Encoding # toJSONList :: [WildcardData] -> Value # toEncodingList :: [WildcardData] -> Encoding # omitField :: WildcardData -> Bool # | |||||
NFData WildcardData # | |||||
Defined in Language.PureScript.Types Methods rnf :: WildcardData -> () # | |||||
Generic WildcardData # | |||||
Defined in Language.PureScript.Types Associated Types
| |||||
Show WildcardData # | |||||
Defined in Language.PureScript.Types Methods showsPrec :: Int -> WildcardData -> ShowS # show :: WildcardData -> String # showList :: [WildcardData] -> ShowS # | |||||
Eq WildcardData # | |||||
Defined in Language.PureScript.Types | |||||
Ord WildcardData # | |||||
Defined in Language.PureScript.Types Methods compare :: WildcardData -> WildcardData -> Ordering # (<) :: WildcardData -> WildcardData -> Bool # (<=) :: WildcardData -> WildcardData -> Bool # (>) :: WildcardData -> WildcardData -> Bool # (>=) :: WildcardData -> WildcardData -> Bool # max :: WildcardData -> WildcardData -> WildcardData # min :: WildcardData -> WildcardData -> WildcardData # | |||||
Serialise WildcardData # | |||||
Defined in Language.PureScript.Types Methods encode :: WildcardData -> Encoding # decode :: Decoder s WildcardData # encodeList :: [WildcardData] -> Encoding # decodeList :: Decoder s [WildcardData] # | |||||
type Rep WildcardData # | |||||
Defined in Language.PureScript.Types type Rep WildcardData = D1 ('MetaData "WildcardData" "Language.PureScript.Types" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) (C1 ('MetaCons "HoleWildcard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "UnnamedWildcard" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IgnoredWildcard" 'PrefixI 'False) (U1 :: Type -> Type))) |
data TypeVarVisibility #
Constructors
TypeVarVisible | |
TypeVarInvisible |
Instances
FromJSON TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods parseJSON :: Value -> Parser TypeVarVisibility # parseJSONList :: Value -> Parser [TypeVarVisibility] # | |||||
ToJSON TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods toJSON :: TypeVarVisibility -> Value # toEncoding :: TypeVarVisibility -> Encoding # toJSONList :: [TypeVarVisibility] -> Value # toEncodingList :: [TypeVarVisibility] -> Encoding # omitField :: TypeVarVisibility -> Bool # | |||||
NFData TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods rnf :: TypeVarVisibility -> () # | |||||
Generic TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Associated Types
Methods from :: TypeVarVisibility -> Rep TypeVarVisibility x # to :: Rep TypeVarVisibility x -> TypeVarVisibility # | |||||
Show TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods showsPrec :: Int -> TypeVarVisibility -> ShowS # show :: TypeVarVisibility -> String # showList :: [TypeVarVisibility] -> ShowS # | |||||
Eq TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods (==) :: TypeVarVisibility -> TypeVarVisibility -> Bool # (/=) :: TypeVarVisibility -> TypeVarVisibility -> Bool # | |||||
Ord TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods compare :: TypeVarVisibility -> TypeVarVisibility -> Ordering # (<) :: TypeVarVisibility -> TypeVarVisibility -> Bool # (<=) :: TypeVarVisibility -> TypeVarVisibility -> Bool # (>) :: TypeVarVisibility -> TypeVarVisibility -> Bool # (>=) :: TypeVarVisibility -> TypeVarVisibility -> Bool # max :: TypeVarVisibility -> TypeVarVisibility -> TypeVarVisibility # min :: TypeVarVisibility -> TypeVarVisibility -> TypeVarVisibility # | |||||
Serialise TypeVarVisibility # | |||||
Defined in Language.PureScript.Types Methods encode :: TypeVarVisibility -> Encoding # decode :: Decoder s TypeVarVisibility # encodeList :: [TypeVarVisibility] -> Encoding # decodeList :: Decoder s [TypeVarVisibility] # | |||||
type Rep TypeVarVisibility # | |||||
Defined in Language.PureScript.Types |
The type of types
Constructors
TUnknown a Int | A unification variable of type Type |
TypeVar a Text | A named type variable |
TypeLevelString a PSString | A type-level string |
TypeLevelInt a Integer | A type-level natural |
TypeWildcard a WildcardData | A type wildcard, as would appear in a partial type synonym |
TypeConstructor a (Qualified (ProperName 'TypeName)) | A type constructor |
TypeOp a (Qualified (OpName 'TypeOpName)) | A type operator. This will be desugared into a type constructor during the "operators" phase of desugaring. |
TypeApp a (Type a) (Type a) | A type application |
KindApp a (Type a) (Type a) | Explicit kind application |
ForAll a TypeVarVisibility Text (Maybe (Type a)) (Type a) (Maybe SkolemScope) | Forall quantifier |
ConstrainedType a (Constraint a) (Type a) | A type with a set of type class constraints |
Skolem a Text (Maybe (Type a)) Int SkolemScope | A skolem constant |
REmpty a | An empty row |
RCons a Label (Type a) (Type a) | A non-empty row |
KindedType a (Type a) (Type a) | A type with a kind annotation |
BinaryNoParensType a (Type a) (Type a) (Type a) | Binary operator application. During the rebracketing phase of desugaring, this data constructor will be removed. |
ParensInType a (Type a) | Explicit parentheses. During the rebracketing phase of desugaring, this data constructor will be removed. Note: although it seems this constructor is not used, it _is_ useful, since it prevents certain traversals from matching. |
Instances
Functor Type # | |||||
Foldable Type # | |||||
Defined in Language.PureScript.Types Methods fold :: Monoid m => Type m -> m # foldMap :: Monoid m => (a -> m) -> Type a -> m # foldMap' :: Monoid m => (a -> m) -> Type a -> m # foldr :: (a -> b -> b) -> b -> Type a -> b # foldr' :: (a -> b -> b) -> b -> Type a -> b # foldl :: (b -> a -> b) -> b -> Type a -> b # foldl' :: (b -> a -> b) -> b -> Type a -> b # foldr1 :: (a -> a -> a) -> Type a -> a # foldl1 :: (a -> a -> a) -> Type a -> a # elem :: Eq a => a -> Type a -> Bool # maximum :: Ord a => Type a -> a # | |||||
Traversable Type # | |||||
FromJSON (Type SourceAnn) # | |||||
FromJSON (Type ()) # | |||||
Defined in Language.PureScript.Types | |||||
FromJSON a => FromJSON (Type a) # | |||||
Defined in Language.PureScript.Types | |||||
ToJSON a => ToJSON (Type a) # | |||||
NFData a => NFData (Type a) # | |||||
Defined in Language.PureScript.Types | |||||
Generic (Type a) # | |||||
Defined in Language.PureScript.Types Associated Types
| |||||
Show a => Show (Type a) # | |||||
Eq (Type a) # | |||||
Ord (Type a) # | |||||
Serialise a => Serialise (Type a) # | |||||
type Rep (Type a) # | |||||
Defined in Language.PureScript.Types type Rep (Type a) = D1 ('MetaData "Type" "Language.PureScript.Types" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) ((((C1 ('MetaCons "TUnknown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "TypeVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "TypeLevelString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PSString)) :+: C1 ('MetaCons "TypeLevelInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))) :+: ((C1 ('MetaCons "TypeWildcard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WildcardData)) :+: C1 ('MetaCons "TypeConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Qualified (ProperName 'TypeName))))) :+: (C1 ('MetaCons "TypeOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Qualified (OpName 'TypeOpName)))) :+: C1 ('MetaCons "TypeApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a))))))) :+: (((C1 ('MetaCons "KindApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)))) :+: C1 ('MetaCons "ForAll" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeVarVisibility) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Type a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SkolemScope)))))) :+: (C1 ('MetaCons "ConstrainedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Constraint a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)))) :+: C1 ('MetaCons "Skolem" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Type a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SkolemScope)))))) :+: ((C1 ('MetaCons "REmpty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "RCons" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Label)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a))))) :+: (C1 ('MetaCons "KindedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)))) :+: (C1 ('MetaCons "BinaryNoParensType" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)))) :+: C1 ('MetaCons "ParensInType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a)))))))) |
srcTUnknown :: Int -> SourceType #
srcTypeVar :: Text -> SourceType #
srcTypeLevelInt :: Integer -> SourceType #
srcTypeConstructor :: Qualified (ProperName 'TypeName) -> SourceType #
srcTypeApp :: SourceType -> SourceType -> SourceType #
srcKindApp :: SourceType -> SourceType -> SourceType #
srcForAll :: TypeVarVisibility -> Text -> Maybe SourceType -> SourceType -> Maybe SkolemScope -> SourceType #
srcREmpty :: SourceType #
srcRCons :: Label -> SourceType -> SourceType -> SourceType #
srcKindedType :: SourceType -> SourceType -> SourceType #
pattern REmptyKinded :: a -> Maybe (Type a) -> Type a #
data ConstraintData #
Additional data relevant to type class constraints
Constructors
PartialConstraintData [[Text]] Bool | Data to accompany a Partial constraint generated by the exhaustivity checker.
It contains (rendered) binder information for those binders which were
not matched, and a flag indicating whether the list was truncated or not.
Note: we use |
Instances
FromJSON ConstraintData # | |||||
Defined in Language.PureScript.Types Methods parseJSON :: Value -> Parser ConstraintData # parseJSONList :: Value -> Parser [ConstraintData] # | |||||
ToJSON ConstraintData # | |||||
Defined in Language.PureScript.Types Methods toJSON :: ConstraintData -> Value # toEncoding :: ConstraintData -> Encoding # toJSONList :: [ConstraintData] -> Value # toEncodingList :: [ConstraintData] -> Encoding # omitField :: ConstraintData -> Bool # | |||||
NFData ConstraintData # | |||||
Defined in Language.PureScript.Types Methods rnf :: ConstraintData -> () # | |||||
Generic ConstraintData # | |||||
Defined in Language.PureScript.Types Associated Types
Methods from :: ConstraintData -> Rep ConstraintData x # to :: Rep ConstraintData x -> ConstraintData # | |||||
Show ConstraintData # | |||||
Defined in Language.PureScript.Types Methods showsPrec :: Int -> ConstraintData -> ShowS # show :: ConstraintData -> String # showList :: [ConstraintData] -> ShowS # | |||||
Eq ConstraintData # | |||||
Defined in Language.PureScript.Types Methods (==) :: ConstraintData -> ConstraintData -> Bool # (/=) :: ConstraintData -> ConstraintData -> Bool # | |||||
Ord ConstraintData # | |||||
Defined in Language.PureScript.Types Methods compare :: ConstraintData -> ConstraintData -> Ordering # (<) :: ConstraintData -> ConstraintData -> Bool # (<=) :: ConstraintData -> ConstraintData -> Bool # (>) :: ConstraintData -> ConstraintData -> Bool # (>=) :: ConstraintData -> ConstraintData -> Bool # max :: ConstraintData -> ConstraintData -> ConstraintData # min :: ConstraintData -> ConstraintData -> ConstraintData # | |||||
Serialise ConstraintData # | |||||
Defined in Language.PureScript.Types Methods encode :: ConstraintData -> Encoding # decode :: Decoder s ConstraintData # encodeList :: [ConstraintData] -> Encoding # decodeList :: Decoder s [ConstraintData] # | |||||
type Rep ConstraintData # | |||||
Defined in Language.PureScript.Types type Rep ConstraintData = D1 ('MetaData "ConstraintData" "Language.PureScript.Types" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) (C1 ('MetaCons "PartialConstraintData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[Text]]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) |
data Constraint a #
A typeclass constraint
Constructors
Constraint | |
Fields
|
Instances
Functor Constraint # | |||||
Defined in Language.PureScript.Types Methods fmap :: (a -> b) -> Constraint a -> Constraint b # (<$) :: a -> Constraint b -> Constraint a # | |||||
Foldable Constraint # | |||||
Defined in Language.PureScript.Types Methods fold :: Monoid m => Constraint m -> m # foldMap :: Monoid m => (a -> m) -> Constraint a -> m # foldMap' :: Monoid m => (a -> m) -> Constraint a -> m # foldr :: (a -> b -> b) -> b -> Constraint a -> b # foldr' :: (a -> b -> b) -> b -> Constraint a -> b # foldl :: (b -> a -> b) -> b -> Constraint a -> b # foldl' :: (b -> a -> b) -> b -> Constraint a -> b # foldr1 :: (a -> a -> a) -> Constraint a -> a # foldl1 :: (a -> a -> a) -> Constraint a -> a # toList :: Constraint a -> [a] # null :: Constraint a -> Bool # length :: Constraint a -> Int # elem :: Eq a => a -> Constraint a -> Bool # maximum :: Ord a => Constraint a -> a # minimum :: Ord a => Constraint a -> a # sum :: Num a => Constraint a -> a # product :: Num a => Constraint a -> a # | |||||
Traversable Constraint # | |||||
Defined in Language.PureScript.Types Methods traverse :: Applicative f => (a -> f b) -> Constraint a -> f (Constraint b) # sequenceA :: Applicative f => Constraint (f a) -> f (Constraint a) # mapM :: Monad m => (a -> m b) -> Constraint a -> m (Constraint b) # sequence :: Monad m => Constraint (m a) -> m (Constraint a) # | |||||
FromJSON (Constraint SourceAnn) # | |||||
Defined in Language.PureScript.Types Methods parseJSON :: Value -> Parser (Constraint SourceAnn) # parseJSONList :: Value -> Parser [Constraint SourceAnn] # | |||||
FromJSON (Constraint ()) # | |||||
Defined in Language.PureScript.Types Methods parseJSON :: Value -> Parser (Constraint ()) # parseJSONList :: Value -> Parser [Constraint ()] # omittedField :: Maybe (Constraint ()) # | |||||
FromJSON a => FromJSON (Constraint a) # | |||||
Defined in Language.PureScript.Types Methods parseJSON :: Value -> Parser (Constraint a) # parseJSONList :: Value -> Parser [Constraint a] # omittedField :: Maybe (Constraint a) # | |||||
ToJSON a => ToJSON (Constraint a) # | |||||
Defined in Language.PureScript.Types Methods toJSON :: Constraint a -> Value # toEncoding :: Constraint a -> Encoding # toJSONList :: [Constraint a] -> Value # toEncodingList :: [Constraint a] -> Encoding # omitField :: Constraint a -> Bool # | |||||
NFData a => NFData (Constraint a) # | |||||
Defined in Language.PureScript.Types Methods rnf :: Constraint a -> () # | |||||
Generic (Constraint a) # | |||||
Defined in Language.PureScript.Types Associated Types
| |||||
Show a => Show (Constraint a) # | |||||
Defined in Language.PureScript.Types Methods showsPrec :: Int -> Constraint a -> ShowS # show :: Constraint a -> String # showList :: [Constraint a] -> ShowS # | |||||
Eq (Constraint a) # | |||||
Defined in Language.PureScript.Types | |||||
Ord (Constraint a) # | |||||
Defined in Language.PureScript.Types Methods compare :: Constraint a -> Constraint a -> Ordering # (<) :: Constraint a -> Constraint a -> Bool # (<=) :: Constraint a -> Constraint a -> Bool # (>) :: Constraint a -> Constraint a -> Bool # (>=) :: Constraint a -> Constraint a -> Bool # max :: Constraint a -> Constraint a -> Constraint a # min :: Constraint a -> Constraint a -> Constraint a # | |||||
Serialise a => Serialise (Constraint a) # | |||||
Defined in Language.PureScript.Types Methods encode :: Constraint a -> Encoding # decode :: Decoder s (Constraint a) # encodeList :: [Constraint a] -> Encoding # decodeList :: Decoder s [Constraint a] # | |||||
type Rep (Constraint a) # | |||||
Defined in Language.PureScript.Types type Rep (Constraint a) = D1 ('MetaData "Constraint" "Language.PureScript.Types" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) (C1 ('MetaCons "Constraint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "constraintAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "constraintClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Qualified (ProperName 'ClassName)))) :*: (S1 ('MetaSel ('Just "constraintKindArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type a]) :*: (S1 ('MetaSel ('Just "constraintArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type a]) :*: S1 ('MetaSel ('Just "constraintData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ConstraintData)))))) |
srcConstraint :: Qualified (ProperName 'ClassName) -> [SourceType] -> [SourceType] -> Maybe ConstraintData -> SourceConstraint #
mapConstraintArgs :: ([Type a] -> [Type a]) -> Constraint a -> Constraint a #
overConstraintArgs :: Functor f => ([Type a] -> f [Type a]) -> Constraint a -> f (Constraint a) #
mapConstraintArgsAll :: ([Type a] -> [Type a]) -> Constraint a -> Constraint a #
overConstraintArgsAll :: Applicative f => ([Type a] -> f [Type a]) -> Constraint a -> f (Constraint a) #
constraintToJSON :: (a -> Value) -> Constraint a -> Value #
typeToJSON :: (a -> Value) -> Type a -> Value #
constraintFromJSON :: Parser a -> (Value -> Parser a) -> Value -> Parser (Constraint a) #
data RowListItem a #
Constructors
RowListItem | |
Fields
|
Instances
Functor RowListItem # | |||||
Defined in Language.PureScript.Types Methods fmap :: (a -> b) -> RowListItem a -> RowListItem b # (<$) :: a -> RowListItem b -> RowListItem a # | |||||
Foldable RowListItem # | |||||
Defined in Language.PureScript.Types Methods fold :: Monoid m => RowListItem m -> m # foldMap :: Monoid m => (a -> m) -> RowListItem a -> m # foldMap' :: Monoid m => (a -> m) -> RowListItem a -> m # foldr :: (a -> b -> b) -> b -> RowListItem a -> b # foldr' :: (a -> b -> b) -> b -> RowListItem a -> b # foldl :: (b -> a -> b) -> b -> RowListItem a -> b # foldl' :: (b -> a -> b) -> b -> RowListItem a -> b # foldr1 :: (a -> a -> a) -> RowListItem a -> a # foldl1 :: (a -> a -> a) -> RowListItem a -> a # toList :: RowListItem a -> [a] # null :: RowListItem a -> Bool # length :: RowListItem a -> Int # elem :: Eq a => a -> RowListItem a -> Bool # maximum :: Ord a => RowListItem a -> a # minimum :: Ord a => RowListItem a -> a # sum :: Num a => RowListItem a -> a # product :: Num a => RowListItem a -> a # | |||||
Traversable RowListItem # | |||||
Defined in Language.PureScript.Types Methods traverse :: Applicative f => (a -> f b) -> RowListItem a -> f (RowListItem b) # sequenceA :: Applicative f => RowListItem (f a) -> f (RowListItem a) # mapM :: Monad m => (a -> m b) -> RowListItem a -> m (RowListItem b) # sequence :: Monad m => RowListItem (m a) -> m (RowListItem a) # | |||||
Generic (RowListItem a) # | |||||
Defined in Language.PureScript.Types Associated Types
Methods from :: RowListItem a -> Rep (RowListItem a) x # to :: Rep (RowListItem a) x -> RowListItem a # | |||||
Show a => Show (RowListItem a) # | |||||
Defined in Language.PureScript.Types Methods showsPrec :: Int -> RowListItem a -> ShowS # show :: RowListItem a -> String # showList :: [RowListItem a] -> ShowS # | |||||
type Rep (RowListItem a) # | |||||
Defined in Language.PureScript.Types type Rep (RowListItem a) = D1 ('MetaData "RowListItem" "Language.PureScript.Types" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) (C1 ('MetaCons "RowListItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "rowListAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "rowListLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Label) :*: S1 ('MetaSel ('Just "rowListType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type a))))) |
srcRowListItem :: Label -> SourceType -> RowListItem SourceAnn #
rowToList :: Type a -> ([RowListItem a], Type a) #
Convert a row to a list of pairs of labels and types
rowToSortedList :: Type a -> ([RowListItem a], Type a) #
Convert a row to a list of pairs of labels and types, sorted by the labels.
rowFromList :: ([RowListItem a], Type a) -> Type a #
Convert a list of labels and types to a row
alignRowsWith :: (Label -> Type a -> Type a -> r) -> Type a -> Type a -> ([r], (([RowListItem a], Type a), ([RowListItem a], Type a))) #
Align two rows of types, splitting them into three parts:
- Those types which appear in both rows
- Those which appear only on the left
- Those which appear only on the right
Note: importantly, we preserve the order of the types with a given label.
isMonoType :: Type a -> Bool #
Check whether a type is a monotype
replaceTypeVars :: Text -> Type a -> Type a -> Type a #
Replace a type variable, taking into account variable shadowing
genPureName :: Text -> [Text] -> Text #
addVisibility :: [(Text, TypeVarVisibility)] -> Type a -> Type a #
Add visible type abstractions to top-level foralls.
usedTypeVariables :: Type a -> [Text] #
Collect all type variables appearing in a type
freeTypeVariables :: Type a -> [Text] #
Collect all free type variables appearing in a type
completeBinderList :: Type a -> Maybe ([(a, (Text, Type a))], Type a) #
Collect a complete set of kind-annotated quantifiers at the front of a type.
moveQuantifiersToFront :: a -> Type a -> Type a #
Move all universal quantifiers to the front of a type
containsForAll :: Type a -> Bool #
Check if a type contains `forall`
containsUnknowns :: Type a -> Bool #
Check if a type contains unknowns in a position that is relevant to constraint solving. (Kinds are not.)
eraseKindApps :: Type a -> Type a #
eraseForAllKindAnnotations :: Type a -> Type a #
unapplyConstraints :: Type a -> ([Constraint a], Type a) #
srcInstanceType :: SourceSpan -> [(Text, SourceType)] -> Qualified (ProperName 'ClassName) -> [SourceType] -> SourceType #
Construct the type of an instance declaration from its parts. Used in error messages describing unnamed instances.
everythingOnTypes :: (r -> r -> r) -> (Type a -> r) -> Type a -> r #
everythingWithContextOnTypes :: s -> r -> (r -> r -> r) -> (s -> Type a -> (s, r)) -> Type a -> r #
annForType :: forall a f. Functor f => (a -> f a) -> Type a -> f (Type a) #
getAnnForType :: Type a -> a #
setAnnForType :: a -> Type a -> Type a #
compareType :: Type a -> Type b -> Ordering #
eqConstraint :: Constraint a -> Constraint b -> Bool #
compareConstraint :: Constraint a -> Constraint b -> Ordering #