# `simplistic-generics`: generic programming without too many type classes

This library provides a way to do data type-generic programming in GHC,
re-using almost all the machinery from `GHC.Generics`, but without the need
to define a different generic type class for each new operation.

Say that you want to define an operation `op` in a generic fashion.
The [docs of `GHC.Generics`](http://hackage.haskell.org/package/base/docs/GHC-Generics.html)
tell you that you need to create a new type class whose argument is
the set of pattern functors that may generate the data type. Then by
means of a default declaration you bridge the gap between both versions.
Furthermore, in almost every case the instances of this class follow the
same pattern:

```haskell
class GOp (f :: * -> *) where
  gop :: ...
instance GOp U1 where ...
instance (GOp f, GOp g) => GOp (f :+: g) where ...
instance (GOp f, GOp g) => GOp (f :*: g) where ...
instance (GOp f) => GOp (M1 i p f) where ...
instance Op t => GOp (K1 r t) where ...

class Op a where
  op :: ...
  default op :: (Generic a, GOp (Rep a)) => ...
  op = ... gop ...
```

When using `simplistic-generics` you do *not* introduce such a type class;
you just write all the cases of the generic function in one go! The only
thing you need to remember is that you have to pattern match on values of
the type `SRep w f`, where `f` is the pattern functor from `GHC.Generics`.
The definition of the previous operation looks then:

```haskell
gop :: ... SRep w f ...
gop ... S_U1       ... = ...
gop ... (S_L1 x)   ... = ...
gop ... (S_R1 x)   ... = ...
gop ... (x :**: y) ... = ...
gop ... (S_M1 x)   ... = ...
gop ... (S_K1 x)   ... = ...
```

There is only one missing link here. In the definition of `GOp` using
type classes we tied the knot by asking the `K1` instance to satisfy `Op`
recursively. In the case of `SRep` we have a special `OnLeaves` combinator
which requires a constraint from each `K1` node. The signature for `gop`
should read then:

```haskell
gop :: OnLeaves Op f => ... SRep w f ...
```

The final touch is that instead of using `from` and `to` to convert back and
forth generic representations, you use `fromS` and `toS` to get a `SRep w f`.

For real examples, check the [`Derive` folder](https://gitlab.com/trupill/simplistic-generics/tree/master/src/Generics/Simplistic/Derive) in the repo.

### Inspiration

This library is inspired by several previous work:

* [Generic Haskell](http://www.cs.uu.nl/research/projects/generic-haskell/compiler/emerald/GHUsersGuide.pdf),
  described thoroughly in [Andres Löh's thesis](https://www.andres-loeh.de/ExploringGH.pdf),
  which features type-indexed functions in Haskell.
* The [`generics-sop` library](http://hackage.haskell.org/package/generics-sop),
  from which we have copied the `OnLeaves` technique.