constraints-deriving: Manipulating constraints and deriving class instances programmatically.

[ bsd3, constraints, library ] [ Propose Tags ]

The library provides a plugin to derive class instances programmatically. Please see the README on GitHub at https://github.com/achirkin/constraints-deriving#readme


[Skip to Readme]

Flags

Manual Flags

NameDescriptionDefault
constraints

Use vanilla constraints package as a dependency instead of the manual minimalistic definitions copied from there.

Disabled
debug

Show debug trace info (used only for library development). Note, if you want to see the debug output of the plugin in another project, you may need to manually define a CPP option -DPLUGIN_DEBUG in that project.

Disabled
examples

Whether to build examples

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 1.0.0.0, 1.0.1.0, 1.0.1.1, 1.0.1.2, 1.0.2.0, 1.0.3.0, 1.0.4.0, 1.1.0.0, 1.1.1.0, 1.1.1.1, 1.1.1.2
Dependencies base (>=4.9 && <5), constraints-deriving, ghc (>=8.0.1 && <9.1) [details]
License BSD-3-Clause
Copyright Copyright: (c) 2019 Artem Chirkin
Author Artem Chirkin
Maintainer achirkin@users.noreply.github.com
Category Constraints
Home page https://github.com/achirkin/constraints-deriving#readme
Bug tracker https://github.com/achirkin/constraints-deriving/issues
Source repo head: git clone https://github.com/achirkin/constraints-deriving
Uploaded by achirkin at 2021-03-24T16:24:52Z
Distributions
Reverse Dependencies 2 direct, 16 indirect [details]
Executables deriving-example
Downloads 4905 total (39 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for constraints-deriving-1.1.1.2

[back to package description]

Hackage Build Status

constraints-deriving

This project is based on the constraints library. Module Data.Constraint.Deriving is a GHC Core compiler plugin that provides new flexible programmable ways to generate class instances.

The main goal of this project is to make possible a sort of ad-hoc polymorphism that I wanted to implement in easytensor for performance reasons: an umbrella type unifies multiple specialized type family backend instances; if the type instance is known, GHC picks a specialized (overlapping) class instance for a required function; otherwise, GHC resorts to a unified (overlappable) instance that is defined for the whole type family.

To use the plugin, add

{-# OPTIONS_GHC -fplugin Data.Constraint.Deriving #-}

to the header of your module. For debugging, add a plugin option dump-instances:

{-# OPTIONS_GHC -fplugin-opt Data.Constraint.Deriving:dump-instances #-}

to the header of your file; it will print all instances declared in the module (hand-written and auto-generated). To enable much more verbose debug output, use library flag dev (for debugging the plugin itself).

Check out example folder for a motivating use case (enabled with flag examples).

The plugin is controlled via GHC annotations; there are three types of annotations corresponding to plugin passes. All passes are core-to-core, which means the plugin runs after the typechecker, which in turn means the generated class instances are available only outside of the module. A sort of inconvenience you may have experienced with template haskell 😉.

DeriveAll

DeriveAll plugin pass inspects a newtype declaration. To enable DeriveAll for a newtype Foo, add an annotation as follows:

data Bar a = ...
{-# ANN type Foo DeriveAll #-}
newtype Foo a = Foo (Bar a)

-- the result is that Foo has the same set of instances as Bar

check out test/Spec/ for more examples.

DeriveAll plugin pass looks through all possible type instances (in the presence of type families) of the base type, and copies all class instances for the newtype wrapper.

Sometimes, you may need to refine the relation between the base type and the newtype; you can do this via a special type family DeriveContext newtype :: Constraint. By adding equality constraints, you can specify custom dependencies between type variables present in the newtype declaration (e.g. test/Spec/DeriveAll01.hs). By adding class constraints, you force these class constraints for all generated class instances (e.g. in test/Spec/DeriveAll02.hs all class instances of BazTy a b c d e f have an additional constraint Show e).

Note, the internal machinery is different from GeneralizedNewtypeDeriving approach: rather than coercing every function in the instance definition from the base type to the newtype, it coerces the whole instance dictionary.

Blacklisting instances from being DeriveAll-ed

Sometimes you may want to avoid deriving a number of instances for your newtype. Use DeriveAllBut [String] constructor in the annotation and specify names of type classes you don't want to derive.

{-# ANN type CHF (DeriveAllBut ["Show"]) #-}
newtype CHF = CHF Double deriving Show

-- the result is a normal `Show CHF` instance and the rest of `Double`'s instances are DeriveAll-ed

For your safety, the plugin is hardcoded to not generate instances for any classes and types in GHC.Generics, Data.Data, Data.Typeable, Language.Haskell.TH.

Overlapping instances

By default DeriveAll marks all instances as NoOverlap if there are no overlapping closed type families involved. Otherwise, it marks overlapped type instances as Incoherent. If this logic does not suit you, you can enforce OverlapMode using DeriveAll' data constructor.

ToInstance

ToInstance plugin pass converts a top-level Ctx => Dict (Class t1..tn) value declaration into an instance of the form instance Ctx => Class t1..tn. Thus, one can write arbitrary Haskell code (returning a class dictionary) to be executed every time an instance is looked up by the GHC machinery. To derive an instance this way, use ToInstance (x :: OverlapMode) for a declaration, e.g. as follows:

newtype Foo t = Foo t

{-# ANN deriveEq (ToInstance NoOverlap) #-}
deriveEq :: Eq t => Dict (Eq (Foo t))
deriveEq = mapDict (unsafeDerive Foo) Dict

-- the result of the above is equal to
-- deriving instance Eq t => Eq (Foo t)

You can find a more meaningful example in test/Spec/ToInstance01.hs or example/Lib/VecBackend.hs.

Danger: ToInstance removes duplicate instances; if you have defined an instance with the same head using vanilla Haskell and the plugin, the latter will try to replace the former in place. Behavior of the instance in the same module is undefined in this case (the other modules should be fine seeing the plugin version). I used this trick to convince .hs-boot to see the instances generated by the plugin.

ClassDict

ClassDict plugin pass lets you construct a new class dictionary without actually creating a class instance:

{-# ANN defineEq ClassDict #-}
defineEq :: (a -> a -> Bool) -> (a -> a -> Bool) -> Dict (Eq a)
defineEq = defineEq
-- the plugin replaces the above line with an actual class data constructor application

Check out test/Spec/ClassDict01.hs for a more elaborate example.

Further work

DeriveAll derivation mechanics currently ignores and may break functional dependencies.