bidirectional-instances-0.1.0.0: Make instance constraints bidirectional
CopyrightLev Dvorkin (c) 2022
LicenseMIT
Maintainerlev_135@mail.ru
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Bidirectional

Description

This module provides class wrapper for instances that should be bidirectional, i. e. lets GHC know that from instance

instance (A a, B b) => C (Foo a b)

not only forall a b. (A a, B b) => C (Foo a b), but also forall a b. C (Foo a b) => A a and forall a b. C (Foo a b) => B b can be deduced. This is correct, provided that there are no overlapping instances for C (Foo a b).

Example 1: showing GADT

Expand

Suppose we want to write Show instance for the following GADT type:

data Term :: Type -> Type where
  Con :: a -> Term a
  Tup :: Term b -> Term c -> Term (b, c)

It's a bit tricky, because an obvious declaration

instance Show a => Show (Term a) where
  show (Con x) = show x
  show (Tup x y) = unwords ["(", show x, ",", show y, ")"]

fails to typecheck, because in the second equation we apply show function to x, so we need Show instance for b (from GADT constructor). But we only have Show a where a ~ (b, c). So we need to deduce Show (b, c) => Show b and GHC fails to do this. This package provides a solution for this problem:

First of all, we need to make instance Show (b, c) bidirectional. Maybe sometime in the future it will be declared in Prelude, but now we need to make it manually. TH functions from this module can help to reduce boilerplate:

makeBidirectionalInstances [d|
    instance (Show b, Show c)  => Show (b, c)
  |]

After bidirectional instance has been declared, we can use our previous Show (Term a) declaration with a small change: changing constraint from Show a to BidirectionalRec Show a.

instance BidirectionalRec Show a => Show (Term a) where
  show (Con x) = show x
  show (Tup x y) = unwords ["(", show x, ",", show y, ")"]

Why we need BidirectionalRec constraint, but not simple Bidirectional? It's so because we may have nested tuples: (Tup (Tup x y) z) and for showing (Tup x y) we also need bidirectional Show instance. So GHC must infer BidirectionalRec Show (b, c) => BidirectionalRec Show b and Bidirectional Show (b, c) => Show b is not enough.

Example 2: mapping error type for ErrorT preserving MonadState constraint

Expand

Suppose we want to change e type for ExceptT transformer preserving knowledge of MonadState s instance for composed monad. So we want to infer MonadState s (ExceptT e m) => MonadState s (ExceptT e' m). Using bidirectional instances it can be done this way:

Bidirectional (MonadState s) (ExceptT e m) 
  => MonadState s ExceptT e m 
  => Bidirectional (MonadSTate s) EXceptT e m

Thus, the following is well-typed:

makeBidirectionalInstances [d|
  instance Monad m => MonadState s (StateT s m)
  instance MonadState s m => MonadState s (ExceptT e m)
|]

class (forall s e m e'. Bidirectional (MonadState s) (ExceptT e m) => 
  Bidirectional (MonadState s) (ExceptT e' m)) => W'
instance W'

Interaction with overlapping instances

As was mentioned above backward implication is sound only when we have no overlapping instances for. However, solution from this package can work with overlapping instances, provided that only one of them is selected to use in backward direction. Selected instance should be passed to makeBidirectionalInstances/decBidirectionalInstances.

For example this code is correct:

data A a = A a

decBidirectionalInstances [d| 
    instance Show a => Show (A a) where
      show (A a) = "A " ++ show a
  |]

instance  Show (A Int) where
  show (A a) = "Integral A: " ++ show (toInteger a)
Synopsis

Documentation

class (c a, Constr c a) => Bidirectional (c :: k -> Constraint) (a :: k) Source #

Class for non-recursive bidirectional instances, i. e. for instances, such that their components constraints (Constr) is ordinary instance.

Arguments:

  • c class for which we declare bidirectional instance
  • a data type for which instance is provided

For example:

instance Show a => Bidirectional Show [a] where
  type ConstrRec Show [a] = Show a

is correct Bidirectional instance. If you want to have bidirectional Show instance in backward constraint, use BidirectionalRec

Instances for this class are supposed to be generated by makeBidirectionalInstances or by decBidirectionalInstances.

Associated Types

type Constr c a :: Constraint Source #

Constraint for backwards inference. Should not be recursively bidirectional (it means that all constraints should not be wrapped in Bidirectional, e. g. Show a but not Bidirectional Show a)

class (c a, ConstrRec c a, Bidirectional c a) => BidirectionalRec (c :: k -> Constraint) (a :: k) Source #

Class for recursive bidirectional instances, i. e. for instances, such that components also have bidirectional instance. Use Bidirectional non-recursive variant, if you need only one step in backward direction.

Arguments:

  • c class for which we declare bidirectional instance
  • a data type for which instance is provided

For example, this is a nice recursive instance:

instance BidirectionalRec Show a => BidirectionalRec Show [a] where
  type ConstrRec Show [a] = BidirectionalRec Show a

but this one isn't (actually it should be a Bidirectional instance):

instance Show a => BidirectionalRec Show [a] where
  type ConstrRec Show [a] = Show a

Instances for this class are supposed to be generated by makeBidirectionalInstances or by decBidirectionalInstances.

Associated Types

type ConstrRec c a :: Constraint Source #

Constraint for backwards inference. Should be recursively bidirectional (it means that all constraints should be wrapped in BidirectionalRec, e. g. BidirectionalRec Show a but not simply Show a)

decBidirectionalInstances :: Q [Dec] -> Q [Dec] Source #

Declare instance and make it bidirectional at the same time. Provides instances for Bidirectional and BidirectionalRec.

It's suitable for declaring your own instances. To make existing instances (for example, from libs) bidirectional, use makeBidirectionalInstances.

You can use it for declaring multiple instances:

data A a = A a
data B a b = B a b
data C a b = CA a | CB b

decBidirectionalInstances [d| 
    instance Show a => Show (A a) where
      show (A a) = "A " ++ show a
    instance (Show a, Show b) => Show (B a b) where
      show (B a b) = "B " ++ show a ++ " " show b
    instance (Show a, Show b) => Show (C a b) where
      show (CA a) = "CA " ++ show a
      show (CB b) = "CB " ++ show b
  |] 

makeBidirectionalInstances :: Q [Dec] -> Q [Dec] Source #

Make existing instance bidirectional. Provides instances for Bidirectional and BidirectionalRec.

It's suitable for making bidirectional existing instances, that you can't change (for example, from libs). If you want to declare your one instance and make it bidirectional, use decBidirectionalInstances.

You can use it for declaring multiple instances:

makeBidirectionalInstances [d| 
    instance Show a => Show [a]
    instance (Show a, Show b) => Show (a, b)
    instance (Show a, Show b) => Show (Either a b)
  |] 

Note that you need not provide the body of instance, only its head.