Copyright | (C) MLabs 2025 |
---|---|
License | Apache 2.0 |
Maintainer | koz@mlabs.city, sean@mlabs.city |
Safe Haskell | None |
Language | Haskell2010 |
Covenant.Test
Description
Various utilities designed to help test Covenant.
Note
This is probably not that useful to end users of Covenant, but needs to be exposed so the tests can use this functionality.
Since: 1.0.0
Synopsis
- newtype Concrete = Concrete (ValT AbstractTy)
- data DataDeclFlavor
- newtype DataDeclSet (flavor :: DataDeclFlavor) = DataDeclSet [DataDeclaration AbstractTy]
- chooseInt :: MonadGen m => (Int, Int) -> m Int
- scale :: MonadGen m => (Int -> Int) -> m a -> m a
- prettyDeclSet :: forall (a :: DataDeclFlavor). DataDeclSet a -> String
- checkApp :: Map TyName (DatatypeInfo AbstractTy) -> CompT Renamed -> [Maybe (ValT Renamed)] -> Either TypeAppError (ValT Renamed)
- failLeft :: Show a => Either a b -> IO b
- tyAppTestDatatypes :: Map TyName (DatatypeInfo AbstractTy)
- list :: DataDeclaration AbstractTy
- tree :: DataDeclaration AbstractTy
- weirderList :: DataDeclaration AbstractTy
- unsafeTyCon :: TyName -> [ValT a] -> ValT a
- cycleCheck :: Ord a => Map TyName (DataDeclaration a) -> Maybe KindCheckError
- checkDataDecls :: Map TyName (DataDeclaration AbstractTy) -> Either KindCheckError ()
- checkEncodingArgs :: forall a info. (info -> DataEncoding) -> Map TyName info -> ValT a -> Either (EncodingArgErr a) ()
- data RenameError = InvalidAbstractionReference Int (Index "tyvar")
- data RenameM a
- renameValT :: ValT AbstractTy -> RenameM (ValT Renamed)
- renameCompT :: CompT AbstractTy -> RenameM (CompT Renamed)
- renameDataDecl :: DataDeclaration AbstractTy -> RenameM (DataDeclaration Renamed)
- runRenameM :: RenameM a -> Either RenameError a
QuickCheck data wrappers
Wrapper for ValT
to provide an Arbitrary
instance to generate only
value types without any type variables.
Since: 1.0.0
Constructors
Concrete (ValT AbstractTy) |
data DataDeclFlavor Source #
A 'description type' designed for use with DataDeclSet
to describe what
kind of types it contains.
Since: 1.1.0
Constructors
ConcreteDecl | All constructor arguments are concrete and the declaration is monomorphic. Since: 1.1.0 |
ConcreteNestedDecl | As Since: 1.1.0 |
SimpleRecursive | Recursive, monomorphic type (such as Since: 1.1.0 |
Poly1 | Polymorphic types in one variable, which may or may not be recursive. Since: 1.1.0 |
Poly1PolyThunks | As Since: 1.1.0 |
newtype DataDeclSet (flavor :: DataDeclFlavor) Source #
Helper type to generate datatype definitions. Specifically, this stores already-generated datatype declarations for our (re)use when generating.
Since: 1.1.0
Constructors
DataDeclSet [DataDeclaration AbstractTy] |
Instances
Arbitrary (DataDeclSet 'ConcreteDecl) Source # | |
Defined in Covenant.Test Methods arbitrary :: Gen (DataDeclSet 'ConcreteDecl) # shrink :: DataDeclSet 'ConcreteDecl -> [DataDeclSet 'ConcreteDecl] # | |
Arbitrary (DataDeclSet 'ConcreteNestedDecl) Source # | |
Defined in Covenant.Test Methods arbitrary :: Gen (DataDeclSet 'ConcreteNestedDecl) # shrink :: DataDeclSet 'ConcreteNestedDecl -> [DataDeclSet 'ConcreteNestedDecl] # | |
Arbitrary (DataDeclSet 'Poly1) Source # | |
Defined in Covenant.Test Methods arbitrary :: Gen (DataDeclSet 'Poly1) # shrink :: DataDeclSet 'Poly1 -> [DataDeclSet 'Poly1] # | |
Arbitrary (DataDeclSet 'Poly1PolyThunks) Source # | |
Defined in Covenant.Test Methods arbitrary :: Gen (DataDeclSet 'Poly1PolyThunks) # shrink :: DataDeclSet 'Poly1PolyThunks -> [DataDeclSet 'Poly1PolyThunks] # | |
Arbitrary (DataDeclSet 'SimpleRecursive) Source # | |
Defined in Covenant.Test Methods arbitrary :: Gen (DataDeclSet 'SimpleRecursive) # shrink :: DataDeclSet 'SimpleRecursive -> [DataDeclSet 'SimpleRecursive] # |
Functions
Lifted QuickCheck functions
DataDeclSet
functionality
prettyDeclSet :: forall (a :: DataDeclFlavor). DataDeclSet a -> String Source #
Prettyprinter for DataDeclSet
.
Since: 1.1.0
Test helpers
checkApp :: Map TyName (DatatypeInfo AbstractTy) -> CompT Renamed -> [Maybe (ValT Renamed)] -> Either TypeAppError (ValT Renamed) Source #
Given information about in-scope datatypes, a computation type, and a list of arguments (some of which may be errors), try to construct the type of the result of the application of those arguments to the computation.
Since: 1.0.0
failLeft :: Show a => Either a b -> IO b Source #
If the argument is a Right
, pass the assertion; otherwise, fail the
assertion.
Since: 1.1.0
tyAppTestDatatypes :: Map TyName (DatatypeInfo AbstractTy) Source #
Small collection of datatypes needed to test type application logic.
Since: 1.1.0
list :: DataDeclaration AbstractTy Source #
The onchain list type.
Since: 1.1.0
tree :: DataDeclaration AbstractTy Source #
A datatype equivalent to
data Tree a = Bin (Tree a) (Tree a) | Tip a
Since: 1.1.0
weirderList :: DataDeclaration AbstractTy Source #
A datatype equivalent to
data WeirderList a = Uncons (Maybe (a, WeirderList a))
Since: 1.1.0
unsafeTyCon :: TyName -> [ValT a] -> ValT a Source #
Helper for tests to quickly construct Datatype
s. This is unsafe, as it
allows construction of nonsensical renamings.
Since: 1.1.0
Datatype checks
cycleCheck :: Ord a => Map TyName (DataDeclaration a) -> Maybe KindCheckError Source #
Verifies that no types in the argument are mutually recursive.
Since: 1.1.0
checkDataDecls :: Map TyName (DataDeclaration AbstractTy) -> Either KindCheckError () Source #
Checks that all the data declarations in the argument 'make sense'. Specifically:
- The strategy declared for the datatype is valid for it
- There are no mutually recursive datatype declarations
- Constructor arguments are not thunks
- The number of type variables in any constructor isn't greater than we expect
Since: 1.1.0
checkEncodingArgs :: forall a info. (info -> DataEncoding) -> Map TyName info -> ValT a -> Either (EncodingArgErr a) () Source #
Verifies that a datatype (third argument) is valid according to its stated encoding, as provided by the first two arguments (projection and metadata).
Note
If the datatype being validated refers to other datatypes, we assume that
they exist in the metadata Map
. Thus, we must ensure this holds or the
check will fail.
Since: 1.1.0
Renaming
Types
data RenameError Source #
Ways in which the renamer can fail.
Since: 1.1.0
Constructors
InvalidAbstractionReference Int (Index "tyvar") | An attempt to reference an abstraction in a scope where this abstraction doesn't exist. First field is the true level, second is the index that was requested. Since: 1.0.0 |
Instances
Show RenameError Source # | |
Defined in Covenant.Internal.Rename Methods showsPrec :: Int -> RenameError -> ShowS # show :: RenameError -> String # showList :: [RenameError] -> ShowS # | |
Eq RenameError Source # | |
Defined in Covenant.Internal.Rename |
A 'renaming monad' which allows us to convert type representations from ones that use relative abstraction labelling to absolute abstraction labelling.
Why this is necessary
Consider the following AbstractTy
:
. The meaning of
this is relative to where in a type it is positioned: it could be bound by a
scope higher than our own, or something we can unify with. Because its
meaning (namely, what it refers to) is situational, type checking becomes
more difficult, although it has other advantages.BoundAtScope
1 0
This monad allows us to convert this relative form into an absolute one. More specifically, the renamer does two things:
- Ensures that any given abstraction refers to one, and only one, thing; and
- Indicates which abstractions are unifiable, and which are (effectively) constant or fixed.
Since: 1.0.0
Introduction
renameValT :: ValT AbstractTy -> RenameM (ValT Renamed) Source #
Rename a value type.
Since: 1.0.0
renameCompT :: CompT AbstractTy -> RenameM (CompT Renamed) Source #
Rename a computation type.
Since: 1.0.0
Elimination
runRenameM :: RenameM a -> Either RenameError a Source #
Execute a renaming computation.
Since: 1.0.0