Deriving via first-class functions
- You want to derive a class instance for a type
T.
- You want to reuse an existing instance for a similar type
U.
- Define a function or isomorphism between
T and U. Give it a "type-level name" F.
- Derive the instance for
T via Fun F.

Deriving via generic isomorphism
Example type:
data T0 = T0 Int Bool
To reuse existing instances for (Int, Bool),
we can do deriving via the "generic isomorphism" T0 ?-> (Int, Bool).
deriving (Eq, Ord) via Fun (T0 ?-> (Int, Bool))
Complete example with extensions and imports:
{-# LANGUAGE DeriveGeneric, DerivingVia, TypeOperators #-}
import DerivingViaFun
import GHC.Generics (Generic)
import Data.Monoid (Sum(..), Any(..))
data T0 = T0 Int Bool
deriving Generic
deriving (Eq, Ord) via Fun (T0 ?-> (Int, Bool))
deriving (Semigroup, Monoid) via Fun (T0 ?-> (Sum Int, Any))
Function composition
Example: derive the All monoid (aka. (&&)) from Any (aka. (||)) by duality.
newtype All = All Bool
deriving (Semigroup, Monoid)
via Fun (Coerce All Bool >>> Not >>> Coerce Bool Any)
The function Coerce All Bool >>> Not >>> Coerce Bool Any
denotes a function composition of coerce
and the boolean function not,
as well as its inverse.
How it works: classes are functors
The type Fun (f :: a ~> b) is a newtype containing a.
Deriving-via-fun is enabled for a class C
by providing an instance of the form
C b => C (Fun (f :: a ~> b)),
which can be read as a function from C b to C a,
using the mapping f :: a ~> b.
In that way, we can think of many classes C as functors.
Whether the mapping f represents a function from a to b,
or a function from b to a, or a bijection between them,
depends on the specific class C.
For example, Eq has this instance, where Apply f
provides a function a -> b:
instance (Apply f, Eq b) => Eq (Fun (f :: a ~> b)) where
For a different example, Bounded has this instance,
where Apply (Inv f) provides a function b -> a:
instance (Apply (Inv f), Bounded b) => Bounded (Fun (f :: a ~> b)) where
And of course, there are classes that require going both ways,
like Semigroup:
instance (Iso f, Semigroup b) => Semigroup (Fun (f :: a ~> b)) where
For more details, check out the documentation
or read the source code.
Comparison with iso-deriving
This library is quite similar to iso-deriving,
presented in the blog post Deriving isomorphically by Hans Hoeglund.
In iso-deriving, the newtype As is indexed by a source and target type,
and the user must declare a suitable instance of Project and/or Inject
between these types.
In deriving-via-fun (this library), the newtype Fun is indexed by a "function name". Certain function names, notably (?->) and Coerce, can be reused for many pairs of types without further ceremony. Functions can also be composed easily with (.) or (>>>), hence "first-class functions" in the description.
deriving-via-fun can also replicate the usage of iso-deriving
using the Adhoc function name.
Comparison with Generically
There is some overlap in use cases between this library and Generically.
But they still represent rather different approaches.
The provider of a class instance for Generically must commit to a
specific behavior for products and sums once for all.
Using this library, a class instance for Fun only needs to apply
an arbitrary mapping. In other words, the class is seen as some kind of functor in a general sense.
The only part of this library that knows anything about generics
is (?->), which delimits a restricted and localized usage of Generic.
It's still up to the user to select a concrete product or sum type from which to
copy the class instance.