-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Hedgehog Generators for clash-lib -- -- Hedgehog Generators for clash-lib @package clash-lib-hedgehog @version 1.9.0 -- | Random type-directed generation of literals. module Clash.Hedgehog.Core.Literal -- | Generate a Literal with the specified core type. If the type -- does not correspond to a known PrimTyCon (as defined in -- Clash.Core.TysPrim) then an error is returned. genLiteralFrom :: forall m. MonadGen m => Type -> m Literal -- | Monad for random generation of clash-core types. module Clash.Hedgehog.Core.Monad -- | The CoreGenT monad keeps track of features like language extensions -- which have an impact on what can be generated. This allows more -- meaningful random generation, as the output of generators can be -- constrained to the same variant of Haskell / Clash used by the caller. data CoreGenT m a -- | Run a generator that generates types from clash-lib. This is -- intended to transform another monad which implements MonadGen. runCoreGenT :: CoreGenT m a -> CoreGenConfig -> m a -- | The configuration of Haskell / Clash which the generated source -- adheres to. These are typically things which change what a user could -- potentially have written in a source file, such as language -- extensions. data CoreGenConfig CoreGenConfig :: Bool -> Bool -> Bool -> Bool -> Bool -> CoreGenConfig [allowDataKinds] :: CoreGenConfig -> Bool [allowPolyKinds] :: CoreGenConfig -> Bool [allowRankNTypes] :: CoreGenConfig -> Bool [allowTypeFamilies] :: CoreGenConfig -> Bool [allowUndecidableInstances] :: CoreGenConfig -> Bool -- | The default configuration matches the set of language extensions which -- are enabled by default when running clash / clashi. -- For most projects, this will likely be the most representative set of -- options. defaultConfig :: CoreGenConfig canGenDataKinds :: forall m. Monad m => CoreGenT m Bool canGenPolyKinds :: forall m. Monad m => CoreGenT m Bool canGenRankNTypes :: forall m. Monad m => CoreGenT m Bool canGenTypeFamilies :: forall m. Monad m => CoreGenT m Bool canGenUndecidableInstances :: forall m. Monad m => CoreGenT m Bool -- | A monoid on applicative functors. -- -- If defined, some and many should be the least solutions -- of the equations: -- --
class Applicative f => Alternative (f :: Type -> Type) -- | The identity of <|> empty :: Alternative f => f a -- | An associative binary operation (<|>) :: Alternative f => f a -> f a -> f a -- | One or more. some :: Alternative f => f a -> f [a] -- | Zero or more. many :: Alternative f => f a -> f [a] infixl 3 <|> -- | Class of monads which can generate input data for tests. class (Monad m, Monad GenBase m) => MonadGen (m :: Type -> Type) where { type family GenBase (m :: Type -> Type) :: Type -> Type; } -- | Extract a GenT from a MonadGen. toGenT :: MonadGen m => m a -> GenT (GenBase m) a -- | Lift a GenT in to a MonadGen. fromGenT :: MonadGen m => GenT (GenBase m) a -> m a -- | See examples in Control.Monad.Reader. Note, the partially -- applied function type (->) r is a simple reader monad. See -- the instance declaration below. class Monad m => MonadReader r (m :: Type -> Type) | m -> r -- | Retrieves the monad environment. ask :: MonadReader r m => m r -- | Executes a computation in a modified environment. local :: MonadReader r m => (r -> r) -> m a -> m a -- | Retrieves a function of the current environment. reader :: MonadReader r m => (r -> a) -> m a instance GHC.Show.Show Clash.Hedgehog.Core.Monad.CoreGenConfig instance Control.Monad.Trans.Class.MonadTrans Clash.Hedgehog.Core.Monad.CoreGenT instance GHC.Base.Monad m => Control.Monad.Reader.Class.MonadReader Clash.Hedgehog.Core.Monad.CoreGenConfig (Clash.Hedgehog.Core.Monad.CoreGenT m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Clash.Hedgehog.Core.Monad.CoreGenT m) instance Hedgehog.Internal.Gen.MonadGen m => Hedgehog.Internal.Gen.MonadGen (Clash.Hedgehog.Core.Monad.CoreGenT m) instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Clash.Hedgehog.Core.Monad.CoreGenT m) instance GHC.Base.Monad m => GHC.Base.Monad (Clash.Hedgehog.Core.Monad.CoreGenT m) instance GHC.Base.Functor m => GHC.Base.Functor (Clash.Hedgehog.Core.Monad.CoreGenT m) instance GHC.Base.Applicative m => GHC.Base.Applicative (Clash.Hedgehog.Core.Monad.CoreGenT m) instance GHC.Base.Alternative m => GHC.Base.Alternative (Clash.Hedgehog.Core.Monad.CoreGenT m) -- | Bias for influencing generator choice. module Clash.Hedgehog.Internal.Bias -- | Determine the bias of an item. This is used to set the weight of that -- item so we can sample using the frequency generator instead of -- element or choice. -- -- Where might you want to introduce such a bias? If there is a -- collection of elements where there is a likeliness that real code -- would use certain values more or less, we want to be able to capture -- this. An obvious example of this is the TyConMap, where -- without it every constructor would have an even weighting, when in -- reality some (like Void# or Addr# are much less -- likely to appear in code written by a Clash user). class Bias a biasOf :: Bias a => a -> Int instance Clash.Hedgehog.Internal.Bias.Bias Clash.Core.TyCon.TyCon -- | Random generation of unique variables and unique containers. module Clash.Hedgehog.Unique genUnique :: forall m. MonadGen m => m Unique genUniqMap :: forall m k v. (MonadGen m, Uniquable k) => Range Int -> m k -> m v -> m (UniqMap v) sampleUniqMap :: forall m v. (Alternative m, MonadGen m, HasType v) => (v -> Bool) -> Type -> UniqMap v -> m (v, [Type]) sampleAnyUniqMap :: forall m v. (Alternative m, MonadGen m, HasType v) => UniqMap v -> m (v, [Type]) -- | Determine the bias of an item. This is used to set the weight of that -- item so we can sample using the frequency generator instead of -- element or choice. -- -- Where might you want to introduce such a bias? If there is a -- collection of elements where there is a likeliness that real code -- would use certain values more or less, we want to be able to capture -- this. An obvious example of this is the TyConMap, where -- without it every constructor would have an even weighting, when in -- reality some (like Void# or Addr# are much less -- likely to appear in code written by a Clash user). class Bias a biasOf :: Bias a => a -> Int sampleUniqMapBiased :: forall m v. (Alternative m, MonadGen m, HasType v, Bias v) => (v -> Bool) -> Type -> UniqMap v -> m (v, [Type]) -- | Random generation of names. module Clash.Hedgehog.Core.Name genKindName :: forall m. MonadGen m => m KiName genTypeName :: forall m. MonadGen m => m TyName genTyConName :: forall m. MonadGen m => m TyConName genTermName :: forall m. MonadGen m => m TmName genDataConName :: forall m. MonadGen m => m DcName genVarName :: forall m a. MonadGen m => m (Name a) -- | Generate a name using the given generator, while ensuring the unique -- of the generated name does not occur in the given UniqMap. genFreshName :: forall m a b. MonadGen m => UniqMap b -> m (Name a) -> m (Name a) -- | Generate a collection of names, from a supplied function to generate -- names and the number of names to generate. -- -- TODO While this gives "unique" names because the uniques are -- different, it can generate multiple names with the same OccName. genNames :: forall m a. MonadGen m => Int -> m (Name a) -> m [Name a] -- | Random generation of core variables. module Clash.Hedgehog.Core.Var -- | Generate a fresh type variable of the specified kind. genTyVar :: forall m. MonadGen m => Kind -> m TyName -> m TyVar -- | Generate a fresh identifier of the specified kind. genId :: forall m. MonadGen m => Type -> m TmName -> m Id -- | Generate a fresh local identifier of the specified kind. genLocalId :: forall m. MonadGen m => Type -> m TmName -> m Id -- | Generate a fresh global identifier of the specified kind. genGlobalId :: forall m. MonadGen m => Type -> m TmName -> m Id -- | Generate a collection of variables, from a supplied function to -- generate variables and the kinds / types of variables to generate. -- -- TODO While this gives "unique" vars because the uniques are different, -- it can generate multiple vars with the same OccName. genVars :: forall m a. MonadGen m => (KindOrType -> m (Name a) -> m (Var a)) -> [KindOrType] -> m (Name a) -> m [Var a] -- | Random kind-directed generation of Kind and Type. module Clash.Hedgehog.Core.Type -- | Generate a kind which is valid for the given TyConMap. The kind -- may contain free variables which are given in a UniqMap, and is -- a valid fit for a hole with the given kind. -- -- N.B. Although the kind generated is a fit for the given hole, -- calling a function like inferCoreKindOf may return a different -- kind. This is because quantifiers are both the introduction rule for -- kind arrows and a kind former of their own right, so for the hole -- -- Type -> Type -- -- a generated fit might be -- -- forall a. a -> a -- -- but this is then inferred to have the kind -- -- Type genKindFrom :: forall m. (Alternative m, MonadGen m) => TyConMap -> UniqMap TyVar -> Kind -> CoreGenT m Kind -- | Generate a closed kind (one without any free variables). If you want -- to be able to use free variables in a kind, see genKindFrom. genClosedKindFrom :: forall m. (Alternative m, MonadGen m) => TyConMap -> Kind -> CoreGenT m Kind -- | Generate a polymorphic type which is valid for the given environment. -- The generated type should have the specified kind, and may contain the -- specified free variables. genPolyTypeFrom :: forall m. (Alternative m, MonadGen m) => TyConMap -> UniqMap TyVar -> Kind -> CoreGenT m Type -- | Generate a polymorphic type which is valid for the given environment. -- The generated type should have the specified kind, and no free -- variables. genClosedPolyType :: forall m. (Alternative m, MonadGen m) => TyConMap -> Kind -> CoreGenT m Type -- | Generate a monomorphic type which is valid for the given environment. -- The generated type should have the specified kind, and may contain the -- specified free variables. genMonoTypeFrom :: forall m. (Alternative m, MonadGen m) => TyConMap -> UniqMap TyVar -> Kind -> CoreGenT m Type -- | Generate a monomorphic type which is valid for the given environment. -- The generated type should have the specified kind, and no free -- variables. genClosedMonoType :: forall m. (Alternative m, MonadGen m) => TyConMap -> Kind -> CoreGenT m Type -- | Generate a function where the codomain is the given type / kind. Any -- other restrictions are enforced by the given generator. This can be -- used with generators for kinds and types. genWithCodomain :: forall m. (Alternative m, MonadGen m) => Kind -> CoreGenT m KindOrType -> CoreGenT m KindOrType instance GHC.Show.Show Clash.Hedgehog.Core.Type.Class instance GHC.Base.Semigroup Clash.Hedgehog.Core.Type.Class instance GHC.Base.Monoid Clash.Hedgehog.Core.Type.Class -- | Random, type-directed generation of Term. module Clash.Hedgehog.Core.Term -- | Generate a term that is valid for the given type constructor map and -- environment of free type and term variables. The term generated must -- have the specified type. genTermFrom :: forall m. (Alternative m, MonadGen m) => TyConMap -> UniqMap (Either TyVar Id) -> Type -> CoreGenT m Term -- | Random type-directed generation of data constructors. module Clash.Hedgehog.Core.DataCon -- | Generate a list of data constructors for a type. This biases towards -- creating constructors which match some common form seen in code, such -- as simple enums with no fields, or records. genDataConsFrom :: forall m. (Alternative m, MonadGen m) => Range Int -> TyConMap -> TyConName -> Kind -> CoreGenT m [DataCon] -- | Random generation of type constructors. module Clash.Hedgehog.Core.TyCon -- | A TyConMap contains all the algebraic data types and type families -- that are used in a program. This is typically the first thing that -- should be generated, as calls to other generators like -- genKind or genTypeFrom will likely want to use the -- type constructors added to the TyConMap. -- -- TODO It would be nice if this also included types from -- clash-prelude like Signal and the sized number types. Maybe -- we want to hook into clash-ghc to load type constructors and -- primitives from Clash.Prelude. genTyConMap :: forall m. (Alternative m, MonadGen m) => Range Int -> CoreGenT m TyConMap