exhaustive-1.0.0: Compile time checks that a computation considers producing data through all possible constructors

Safe HaskellNone
LanguageHaskell2010

Control.Exhaustive.Internal

Synopsis

Documentation

type Constructor fields = forall r. Apply (FunctorStack fields) (NP I fields) r => r Source

A Constructor is an n-ary function from all fields of a specific constructor in a data type, to a generic representation.

type Producer f code = Injection (NP I) code -.-> K (f (NS (NP I) code)) Source

A Producer is a lifted function (in the terms of generics-sop) that instantiates a particular constructor of a data type, possibly using the side-effects provided by f.

Most users will want to create Producers using the smart constructor construct.

type family FunctorStack args :: * -> * Source

This type family is internal, but provides the building block for building n-ary functions. Most users will probably not need to work with this directly.

Equations

FunctorStack [] = I 
FunctorStack (a : as) = Compose ((->) a) (FunctorStack as) 

produceM :: (code ~ Code a, SingI code, Generic a, Applicative f) => NP (Producer f code) code -> [f a] Source

Build a list of computations, one for each constructor in a data type.

produceFirst :: (code ~ Code a, SingI code, Generic a, Alternative f) => NP (Producer f code) code -> f a Source

Keep attempting to construct a data type until a constructor succeeds. The first constructor to successfully be constructed (in the order defined in the original data type) will be returned, or empty if all constructions fail.

produceAll :: (code ~ Code a, SingI code, Generic a, Alternative f) => NP (Producer f code) code -> f [a] Source

Produce all successful constructions of a data-type. If any constructors fail, they will not be included in the resulting list. If all constructors fail, this will return pure '[]'.

construct :: forall fields code f. (Applicative f, SingI fields) => (Constructor fields -> f (NP I fields)) -> Producer f code fields Source

construct builds a Producer for a single constructor of a data type. As you can see, the type is a little scary - but there are a few main parts that will interest you, while the rest are unfortunate implementation details.

  • f is the type of functor who's side effects you can use. For example, you can choose f to be IO, (MyEnv ->), or even more complex monad transformer stacks.
  • fields is a list of types that are used in the constructor.

    As an example, given the data type

    data User = User { name :: String, age :: Int}

    then fields will correspond to [String, Int].

The Constructor argument is what you use to actually create your data type. A Constructor is an n-ary function from all field types. Continuing the example with User above, we would have

Constructor fields == Text -> Int -> out

Thus a complete call to construct would be

construct (\f -> f <$> parseName <*> parseAge)

For a complete example of how this all fits together, user's are pointed to the example at the top of this page.

class Functor f => Apply f a b | f a -> b where Source

Internal machinery to build n-ary functions. As a user of exhaustive, you generally shouldn't need to worry about this type class, other than knowing that the type variable b will correspond to a function of all types mentioned in a.

Methods

apply :: f a -> b Source

Instances

Apply I b b 
Apply ((->) a) b (a -> b) 
(Apply g a b, Apply f b c) => Apply (Compose f g) a c