dragen-0.1.0.0: Automatic derivation of optimized QuickCheck random generators.

Safe HaskellSafe
LanguageHaskell2010

Countable

Description

This file provides a generic implementation for counting how many times a data constructor appears in a value. We use two different type classes in order to achieve this, called Countable (for types of kind *) and Countable1 (for types of kind (* -> *)).

class Countable (a :: *) where
    count :: a -> ConsMap
class Countable1 (f :: * -> *) where
    count1 :: f a -> ConsMap

Let us suppose we have the following type definition:

data Tree = Leaf | Node Tree Tree

if we want to count how many times each type constructor appears within a given value of type Tree, we need to add the following instance derivations:

deriving instance Generic Tree
instance Countable Tree

Then, we can count type constructors over values of type Tree:

count (Node (Node Leaf Leaf) (Node Leaf Leaf))
==> fromList [("Leaf",4),("Node",3)]

Note that, if the Tree data type definition is available, the `deriving instance Generic Tree` could be avoided by including Generic at the type definition deriving clause:

data Tree = Leaf | Node Tree Tree deriving Generic

Countable requires every subtype of a Countable data type to be also Countable in order to work. If we modify our Tree definition as

data GTree a = GLeaf | GNode GTree a GTree

then is necessary to add the following instance derivations:

instance deriving Generic a => Generic (GTree a)
instance (Generic a, Countable a) => Countable (GTree a)

and the Generic and Countable derivations for whatever a we want to use. For example, let a be Bool (Bool already has a Generic instance):

instance Countable Bool

then we can count type constructors on values of type `GTree Bool`

count (GNode (GNode GLeaf False GLeaf) True (GNode GLeaf True GLeaf))
==> fromList [("False",1),("GLeaf",4),("GNode",3),("True",2)]

but what if we are just interested in counting GLeaf and GNode type constructors within values of type `GTree a`? Using Countable type class would require to provide (or derive) proper Generic and Countable instances for whatever type we instantiate a with. Fortunately, we can define a new type class, Countable1, for types of kind (* -> *) that does not count type constructors further than the outter data type. Later, we derive a Countable1 instance for GTree.

instance Countable1 GTree
count1 (GNode (GNode GLeaf 1 GLeaf) 2 (GNode GLeaf 3 GLeaf))
==> fromList [("GLeaf",4),("GNode",3)]
count1 (GNode (GNode GLeaf "a" GLeaf) "b" (GNode GLeaf "c" GLeaf))
==> fromList [("GLeaf",4),("GNode",3)]
Synopsis

Documentation

type ConsMap = Map String Int Source #

A map that associates constructors names and the times each one appears within a value.

class Countable (a :: *) where Source #

Methods

count :: a -> ConsMap Source #

count :: (Generic a, GCountable (Rep a)) => a -> ConsMap Source #

class GCountable f where Source #

Minimal complete definition

gcount

Methods

gcount :: f a -> ConsMap Source #

Instances
GCountable (V1 :: * -> *) Source # 
Instance details

Defined in Countable

Methods

gcount :: V1 a -> ConsMap Source #

GCountable (U1 :: * -> *) Source # 
Instance details

Defined in Countable

Methods

gcount :: U1 a -> ConsMap Source #

GCountable (URec a :: * -> *) Source # 
Instance details

Defined in Countable

Methods

gcount :: URec a a0 -> ConsMap Source #

Countable a => GCountable (K1 i a :: * -> *) Source # 
Instance details

Defined in Countable

Methods

gcount :: K1 i a a0 -> ConsMap Source #

(GCountable f, GCountable g) => GCountable (f :+: g) Source # 
Instance details

Defined in Countable

Methods

gcount :: (f :+: g) a -> ConsMap Source #

(GCountable f, GCountable g) => GCountable (f :*: g) Source # 
Instance details

Defined in Countable

Methods

gcount :: (f :*: g) a -> ConsMap Source #

GCountable f => GCountable (D1 c f) Source # 
Instance details

Defined in Countable

Methods

gcount :: D1 c f a -> ConsMap Source #

(Constructor c, GCountable f) => GCountable (C1 c f) Source # 
Instance details

Defined in Countable

Methods

gcount :: C1 c f a -> ConsMap Source #

GCountable f => GCountable (S1 c f) Source # 
Instance details

Defined in Countable

Methods

gcount :: S1 c f a -> ConsMap Source #

class Countable1 (f :: * -> *) where Source #

Methods

count1 :: f a -> ConsMap Source #

count1 :: (Generic1 f, GCountable1 (Rep1 f)) => f a -> ConsMap Source #

class GCountable1 f where Source #

Minimal complete definition

gcount1

Methods

gcount1 :: f a -> ConsMap Source #

Instances
GCountable1 Par1 Source # 
Instance details

Defined in Countable

Methods

gcount1 :: Par1 a -> ConsMap Source #

GCountable1 (V1 :: * -> *) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: V1 a -> ConsMap Source #

GCountable1 (U1 :: * -> *) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: U1 a -> ConsMap Source #

Countable1 f => GCountable1 (Rec1 f) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: Rec1 f a -> ConsMap Source #

(GCountable1 f, GCountable1 g) => GCountable1 (f :+: g) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: (f :+: g) a -> ConsMap Source #

(GCountable1 f, GCountable1 g) => GCountable1 (f :*: g) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: (f :*: g) a -> ConsMap Source #

GCountable1 f => GCountable1 (D1 c f) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: D1 c f a -> ConsMap Source #

(Constructor c, GCountable1 f) => GCountable1 (C1 c f) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: C1 c f a -> ConsMap Source #

GCountable1 f => GCountable1 (S1 c f) Source # 
Instance details

Defined in Countable

Methods

gcount1 :: S1 c f a -> ConsMap Source #