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

Safe HaskellNone
LanguageHaskell2010

Control.Exhaustive

Contents

Description

exhaustive is a library that guarantees that when building a parser, or some other computation that produces data, all possible constructors in a data type are considered. You can think of this library as providing a symmetry to GHC's built in -fwarn-incomplete-patterns compile time warning, although this library is stricter in that it produces compile time errors if a constructor is omitted.

Usage of this library is intended to be straightforward, though admittedly the types might have you think the opposite! To understand this library, an example may be helpful.

To begin with, consider a simple data type for a "boolean expressions" language:

   import qualified GHC.Generics as GHC

   data Expr
     = ETrue
     | EFalse
     | EIf Expr Expr Expr
     deriving (Eq, GHC.Generic)
   instance Generic Expr

Note that we have to make our data type an instance of both GHC.Generics.Generic and Generics.SOP.Generic, though this only requires boiler-plate code.

Next, we would like to build a parser for this language. Let's assume that we have access to a parsec-like library, where we have one basic combinator:

Ordinarily, we would write our parser as

    parseExpr :: Parser Expr
    parseExpr = msum [ETrue <$ symbol "True"
                     ,EFalse <$ symbol "False"
                     ,EIf <$> symbol "if" *> parseExpr
                          <*> symbol "then" *> parseExpr
                          <*> symbol "else" *> parseExpr
                     ]

However, nothing is making sure that we actually considered all constructors in Expr. We could just as well write

    parseExpr :: Parser Expr
    parseExpr = msum [ETrue <$ symbol "True"
                     ,EFalse <$ symbol "False"]

Although this is significantly less useful!

Using exhaustive, we can get exhaustivity checks that we are at least considering all constructors:

    parseExpr :: Parser Expr
    parseExpr = produceFirst $
      construct (\f -> f <$ symbol "True") :*
      construct (\f -> f <$ symbol "False") :*
      construct (\f -> f <$> symbol "if" *> parseExpr
                         <*> symbol "then" *> parseExpr
                         <*> symbol "else" *> parseExpr) :*
      Nil

As you can hopefully see, exhaustive requires only minimal changes to an existing parser. Specifically, we need to:

  1. Use produceFirst instead of msum
  2. Wrap each constructor application with construct.
  3. Use the provided constructor function, rather than the named constructors in the original data type.

Synopsis

Producing data

The following are the main entry points to the API, all providing functionality to produce data.

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 '[]'.

Constructing Data

In order to produce data, you need a way to construct it - once for each constructor in a data type.

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.

Re-exported

class (SingI [[*]] (Code a), All [*] (SingI [*]) (Code a)) => Generic a

The class of representable datatypes.

The SOP approach to generic programming is based on viewing datatypes as a representation (Rep) built from the sum of products of its components. The components of are datatype are specified using the Code type family.

The isomorphism between the original Haskell datatype and its representation is witnessed by the methods of this class, from and to. So for instances of this class, the following laws should (in general) hold:

to . from === id :: a -> a
from . to === id :: Rep a -> Rep a

You typically don't define instances of this class by hand, but rather derive the class instance automatically.

Option 1: Derive via the built-in GHC-generics. For this, you need to use the DeriveGeneric extension to first derive an instance of the Generic class from module GHC.Generics. With this, you can then give an empty instance for Generic, and the default definitions will just work. The pattern looks as follows:

import qualified GHC.Generics as GHC
import Generics.SOP

...

data T = ... deriving (GHC.Generic, ...)

instance Generic T -- empty
instance HasDatatypeInfo T -- empty, if you want/need metadata

Option 2: Derive via Template Haskell. For this, you need to enable the TemplateHaskell extension. You can then use deriveGeneric from module Generics.SOP.TH to have the instance generated for you. The pattern looks as follows:

import Generics.SOP
import Generics.SOP.TH

...

data T = ...

deriveGeneric ''T -- derives HasDatatypeInfo as well

Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.

Non-standard instances: It is possible to give Generic instances manually that deviate from the standard scheme, as long as at least

to . from === id :: a -> a

still holds.

Instances

Generic Bool 
Generic Ordering 
Generic () 
Generic FormatAdjustment 
Generic FormatSign 
Generic FieldFormat 
Generic FormatParse 
Generic DataRep 
Generic ConstrRep 
Generic Fixity 
Generic Version 
Generic IOMode 
Generic PatternMatchFail 
Generic RecSelError 
Generic RecConError 
Generic RecUpdError 
Generic NoMethodError 
Generic NonTermination 
Generic NestedAtomically 
Generic Errno 
Generic BlockedIndefinitelyOnMVar 
Generic BlockedIndefinitelyOnSTM 
Generic Deadlock 
Generic AssertionFailed 
Generic AsyncException 
Generic ArrayException 
Generic ExitCode 
Generic BufferMode 
Generic Newline 
Generic NewlineMode 
Generic SeekMode 
Generic GeneralCategory 
Generic CChar 
Generic CSChar 
Generic CUChar 
Generic CShort 
Generic CUShort 
Generic CInt 
Generic CUInt 
Generic CLong 
Generic CULong 
Generic CLLong 
Generic CULLong 
Generic CFloat 
Generic CDouble 
Generic CPtrdiff 
Generic CSize 
Generic CWchar 
Generic CSigAtomic 
Generic CClock 
Generic CTime 
Generic CUSeconds 
Generic CSUSeconds 
Generic CIntPtr 
Generic CUIntPtr 
Generic CIntMax 
Generic CUIntMax 
Generic MaskingState 
Generic IOException 
Generic ErrorCall 
Generic ArithException 
Generic All 
Generic Any 
Generic Lexeme 
Generic Number 
Generic [a0] 
Generic (ArgOrder a0) 
Generic (OptDescr a0) 
Generic (ArgDescr a0) 
Generic (Fixed a0) 
Generic (Complex a0) 
Generic (Dual a0) 
Generic (Endo a0) 
Generic (Sum a0) 
Generic (Product a0) 
Generic (First a0) 
Generic (Last a0) 
Generic (Down a0) 
Generic (Maybe a0) 
Generic (I a0) 
Generic (Either a0 b0) 
Generic (a0, b0) 
Generic (Proxy * t0) 
Typeable (* -> Constraint) Generic 
Generic (a0, b0, c0) 
Generic (K * a0 b0) 
Generic (a0, b0, c0, d0) 
Generic (a0, b0, c0, d0, e0) 
Generic ((:.:) * * f0 g0 p0) 
Generic (a0, b0, c0, d0, e0, f0) 
Generic (a0, b0, c0, d0, e0, f0, g0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290, t300) 
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290, t300, t310)