Copyright | (C) MLabs 2025 |
---|---|
License | Apache 2.0 |
Maintainer | koz@mlabs.city, sean@mlabs.city |
Safe Haskell | None |
Language | Haskell2010 |
Covenant.Data
Description
Information about datatype definitions, and various ways to interact with
them. Most of the useful functionality is in DatatypeInfo
and its optics.
Note
Some of the low-level functions in the module make use of ScopeBoundary
.
This is mostly an artifact of needing this for tests; if you ever need their
functionality, assume that the only sensible value is 0
, which will work
via its overloaded number syntax.
Since: 1.1.0
Synopsis
- data BBFError = InvalidRecursion TyName (ValT AbstractTy)
- data DatatypeInfo var = DatatypeInfo {
- _originalDecl :: DataDeclaration var
- _baseFunctorStuff :: Maybe (DataDeclaration var, ValT var)
- _bbForm :: Maybe (ValT var)
- mkDatatypeInfo :: DataDeclaration AbstractTy -> Either BBFError (DatatypeInfo AbstractTy)
- allComponentTypes :: DataDeclaration AbstractTy -> [ValT AbstractTy]
- mkBBF :: DataDeclaration AbstractTy -> Either BBFError (Maybe (ValT AbstractTy))
- noPhantomTyVars :: DataDeclaration AbstractTy -> Bool
- mkBaseFunctor :: DataDeclaration AbstractTy -> Reader ScopeBoundary (Maybe (DataDeclaration AbstractTy))
- isRecursiveChildOf :: TyName -> ValT AbstractTy -> Reader ScopeBoundary Bool
- hasRecursive :: TyName -> ValT AbstractTy -> Reader ScopeBoundary Bool
- everythingOf :: Ord a => ValT a -> Set (ValT a)
Types
All possible errors that could arise when constructing a Boehm-Berrarducci form.
Since: 1.1.0
Constructors
InvalidRecursion TyName (ValT AbstractTy) | The type is recursive in a prohibited way. Typically, this means contravariant recursion. This gives the type name and the invalid recursive constructor argument. Since: 1.1.0 |
data DatatypeInfo var Source #
Contains essential information about datatype definitions. Most of the time, you want to use this type via its optics, rather than directly.
In pretty much any case imaginable, the var
type variable will be one of
AbstractTy
or Renamed
.
Since: 1.1.0
Constructors
DatatypeInfo | |
Fields
|
Instances
(k ~ A_Lens, a ~ Maybe (DataDeclaration var, ValT var), b ~ Maybe (DataDeclaration var, ValT var)) => LabelOptic "baseFunctor" k (DatatypeInfo var) (DatatypeInfo var) a b Source # | The base functor for this data type, if it exists. Types which are not self-recursive lack base functors. Since: 1.1.0 |
Defined in Covenant.Data Methods labelOptic :: Optic k NoIx (DatatypeInfo var) (DatatypeInfo var) a b # | |
(k ~ A_Fold, a ~ ValT var, b ~ ValT var) => LabelOptic "bbBaseF" k (DatatypeInfo var) (DatatypeInfo var) a b Source # | The base functor Boehm-Berrarducci form of this type, if it exists. A type must have both a base functor and a Boehm-Berrarducci form to have a base functor Boehm-Berrarducci form. In other words, they must have at least one constructor and be self-recursive. Since: 1.1.0 |
Defined in Covenant.Data Methods labelOptic :: Optic k NoIx (DatatypeInfo var) (DatatypeInfo var) a b # | |
(k ~ A_Lens, a ~ Maybe (ValT var), b ~ Maybe (ValT var)) => LabelOptic "bbForm" k (DatatypeInfo var) (DatatypeInfo var) a b Source # | The Boehm-Berrarducci form of this type, if it exists. Types with no constructors (that is, types without inhabitants) lack Boehm-Berrarducci forms. Since: 1.1.0 |
Defined in Covenant.Data Methods labelOptic :: Optic k NoIx (DatatypeInfo var) (DatatypeInfo var) a b # | |
(k ~ A_Lens, a ~ DataDeclaration var, b ~ DataDeclaration var) => LabelOptic "originalDecl" k (DatatypeInfo var) (DatatypeInfo var) a b Source # | The original declaration of the data type. Since: 1.1.0 |
Defined in Covenant.Data Methods labelOptic :: Optic k NoIx (DatatypeInfo var) (DatatypeInfo var) a b # | |
Show var => Show (DatatypeInfo var) Source # | Since: 1.1.0 |
Defined in Covenant.Data Methods showsPrec :: Int -> DatatypeInfo var -> ShowS # show :: DatatypeInfo var -> String # showList :: [DatatypeInfo var] -> ShowS # | |
Eq var => Eq (DatatypeInfo var) Source # | Since: 1.1.0 |
Defined in Covenant.Data Methods (==) :: DatatypeInfo var -> DatatypeInfo var -> Bool # (/=) :: DatatypeInfo var -> DatatypeInfo var -> Bool # |
Functions
Datatype-related
mkDatatypeInfo :: DataDeclaration AbstractTy -> Either BBFError (DatatypeInfo AbstractTy) Source #
Given a declaration of a datatype, either produce its datatype info, or fail.
Since: 1.1.0
allComponentTypes :: DataDeclaration AbstractTy -> [ValT AbstractTy] Source #
Returns all datatype constructors used as any argument to the datatype defined by the first argument.
Since: 1.1.0
mkBBF :: DataDeclaration AbstractTy -> Either BBFError (Maybe (ValT AbstractTy)) Source #
Constructs a base functor Boehm-Berrarducci form for the given datatype.
Returns Nothing
if the type is not self-recursive.
Since: 1.1.0
noPhantomTyVars :: DataDeclaration AbstractTy -> Bool Source #
Verifies that all type variables declared by the given datatype have a corresponding value in some 'arm'.
Since: 1.1.0
Lower-level
mkBaseFunctor :: DataDeclaration AbstractTy -> Reader ScopeBoundary (Maybe (DataDeclaration AbstractTy)) Source #
Constructs a base functor from a suitable data declaration, returning
Nothing
if the input is not a recursive type.
Since: 1.1.0
isRecursiveChildOf :: TyName -> ValT AbstractTy -> Reader ScopeBoundary Bool Source #
Returns True
if the second argument is a recursive child of the datatype
named by the first argument.
Since: 1.1.0
hasRecursive :: TyName -> ValT AbstractTy -> Reader ScopeBoundary Bool Source #
Determines whether the type represented by the second argument and named by the first requires a base functor.
Since: 1.1.0