6

I am using data-reify and graphviz to transform an eDSL into a nice graphical representation, for introspection purposes.

As simple, contrived example, consider:

{-# LANGUAGE GADTs #-}

data Expr a where
  Constant :: a -> Expr a
  Map :: (other -> a) -> Expr a -> Expr a
  Apply :: Expr (other -> a) -> Expr a -> Expr a

instance Functor Expr where
  fmap fun val = Map fun val

instance Applicative Expr where
  fun_expr <*> data_expr = Apply fun_expr data_expr
  pure val = Constant val

-- And then some functions to optimize an Expr AST, evaluate Exprs, etc.

To make introspection nicer, I would like to print the values which are stored inside certain AST nodes of the DSL datatype. However, in general any a might be stored in Constant, even those that do not implement Show. This is not necessarily a problem since we can constrain the instance of Expr like so:

instance Show a => Show (Expr a) where
  ...

This is not what I want however: I would still like to be able to print Expr even if a is not Show-able, by printing some placeholder value (such as just its type and a message that it is unprintable) instead.

So we want to do one thing if we have an a implementing Show, and another if a particular a does not.

Furthermore, the DSL also has the constructors Map and Apply which are even more problematic. The constructor is existential in other, and thus we cannot assume anything about other, a or (other -> a). Adding constraints to the type of other to the Map resp. Apply constructors would break the implementation of Functor resp. Applicative which forwards to them.

But here also I'd like to print for the functions:

  • a unique reference. This is always possible (even though it is not pretty as it requires unsafePerformIO) using System.Mem.StableName.
  • Its type, if possible (one technique is to use show (typeOf fun), but it requires that fun is Typeable).

Again we reach the issue where we want to do one thing if we have an f implementing Typeable and another if f does not.

How to do this?


Extra disclaimer: The goal here is not to create 'correct' Show instances for types that do not support it. There is no aspiration to be able to Read them later, or that print a != print b implies a != b.

The goal is to print any datastructure in a 'nice for human introspection' way.

The part I am stuck at, is that I want to use one implementation if extra constraints are holding for a resp. (other -> a), but a 'default' one if these do not exist. Maybe type classes with FlexibleInstances, or maybe type families are needed here? I have not been able to figure it out (and maybe I am on the wrong track all together).

duplode
  • 33,731
  • 7
  • 79
  • 150
Qqwy
  • 5,214
  • 5
  • 42
  • 83

3 Answers3

3

Not all problems have solutions. Not all constraint systems have a satisfying assignment.

So... relax the constraints. Store the data you need to make a sensible introspective function in your data structure, and use functions with type signatures like show, fmap, pure, and (<*>), but not exactly equal to them. If you need IO, use IO in your type signature. In short: free yourself from the expectation that your exceptional needs fit into the standard library.

To deal with things where you may either have an instance or not, store data saying whether you have an instance or not:

data InstanceOrNot c where
    Instance :: c => InstanceOrNot c
    Not :: InstanceOrNot c

(Perhaps a Constraint-kinded Either-alike, rather than Maybe-alike, would be more appropriate. I suspect as you start coding this you will discover what's needed.) Demand that clients that call notFmap and friends supply these as appropriate.

In the comments, I propose parameterizing your type by the constraints you demand, and giving a Functor instance for the no-constraints version. Here's a short example showing how that might look:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}

import Data.Kind

type family All cs a :: Constraint where
    All '[] a = ()
    All (c:cs) a = (c a, All cs a)

data Lol cs a where
    Leaf :: a -> Lol cs a
    Fmap :: All cs b => (a -> b) -> Lol cs a -> Lol cs b

instance Functor (Lol '[]) where
    fmap f (Leaf a) = Leaf (f a)
    fmap f (Fmap g garg) = Fmap (f . g) garg
Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • You might be right. However, I do not want to give up yet. it would be very unfortunate if because _some_ users may want to introspect the DSL, _all_ users will have to change how to interact with the library. This would mean that a full alternative `Functor`/`Applicative`/`Monad`/`Alternative`/`Monoid`-etc. suite would need to be made, and that people would be required to use `RebindableSyntax` in their code everywhere. If at all possible, I hope that a backdoor exists because otherwise this will not be usable. Just like e.g. `Debug.Trace` is useful _exactly_ because it uses a backdoor. – Qqwy Apr 09 '21 at 16:49
  • 1
    @Qqwy If you want variants that do and don't support the various things, that's easy: parameterize them (e.g. by the class constraints they will or won't require of their fields). Then you can write the instances for the version that's partially applied to the most relaxed constraints. Although the desire to efficiently convert from one parameterization to the other raises a very interesting question I had never pondered before: can you safely `unsafeCoerce :: Exists (Show Char) -> Exists ()`? I honestly do not know the answer to that. – Daniel Wagner Apr 09 '21 at 16:54
  • Interesting! However, I do not believe a GADT like the one in the example can be parameterized that way, since the variables of the `Map` and `Apply` data constructors are (and need to be?) existential. Or is there a way around this? – Qqwy Apr 09 '21 at 22:02
  • @Qqwy You may need to (also) constrain the existential variables. I guess I'd want to see a few more details before trying to commit to an answer to that question. – Daniel Wagner Apr 09 '21 at 22:33
  • I do not know how to constrain the existential variables while still allowing instances of `Functor`, `Applicative` etc. If there is a way please do tell! And if there are details missing from my example, I'd be happy to add them. Let me know! :-) – Qqwy Apr 10 '21 at 15:18
  • 1
    @Qqwy Constrain them with the parameterized constraint. Give a `Functor` instance for the parameterization that is no constraint at all. – Daniel Wagner Apr 10 '21 at 16:14
  • That sounds very interesting! Could you explain how to do that in detail (Maybe in a new answer?) – Qqwy Apr 10 '21 at 18:54
  • I suspect the unsafe coercion will be safe, though certainly not officially supported. – dfeuer Apr 10 '21 at 18:58
  • 1
    @Qqwy I have added a smallish but hopefully illustrative example. – Daniel Wagner Apr 10 '21 at 22:50
  • @dfeuer I'm not so sure. It may be that multiple constraints manifest as multiple arguments in core -- hence a difference in number of constraints might actually be different enough to not work. – Daniel Wagner Apr 10 '21 at 22:53
  • 1
    `Constraint` and `Type` are very, very similar in `Core`. Constraint tuples are really the same as tuples. They almost always unbox, but in this situation they really can't (modulo inlining). The thing about `()` is that there's nothing you can do with it other than force it. In theory, the RTS *could* check its size (just as the GC does), but why would it bother? – dfeuer Apr 10 '21 at 23:09
  • Thank you for the example! I unfortunately encounter the following two issues to make it work: (1) In your example you currently `fmap` the function directly over the leaf. I'm instead looking to construct an AST first and only apply the functions later, i.e. `instance Functor (Lol '[]) where { fmap f a = Fmap f a;}` regardless of whether `a` is currently a `Leaf` or an `Fmap`. (2) the `cs` parameter is of kind `[Type -> Constraint]`. This does not magically unify with `'[]`. In other words: I have no idea how to be able to use the `Functor` etc. instances when we _do_ have more constraints. – Qqwy Apr 11 '21 at 10:53
  • @Qqwy Did you try it? `fmap f a = Fmap f a` typechecks just fine. For the `cs` parameter, it is not required that `[Type -> Constraint]` and `'[]` unify, but rather that `'[] :: [Type -> Constraint]`, and that latter relation is true. You cannot use the `Functor` instance when you *do* have more constraints, *exactly* as I've been saying all along. This is *only* to prevent you from having to write the data structure twice, once with constraints and once without, so that you can have the `Functor` instance for just one of them. – Daniel Wagner Apr 11 '21 at 15:03
  • Yes, of course I ran and experimented with the code myself. I think I misunderstood, believing that your new approach _would_ allow a `Functor` instance even with more constraints, which was why I was confused and thinking that maybe the difference in `fmap` implementations might be a cause of that. Thank you very much for your help. It's unfortunate that it seems a dead end since I do want to propagate the constraints while allowing a `Functor` etc. instance. I'm not giving up yet. – Qqwy Apr 12 '21 at 10:05
  • But thank you very much for the time and effort spent! The idea to use 'Parameterized constraints' has brought me on the trail of [RMonad](https://hackage.haskell.org/package/rmonad-0.8), specifically its `AsMonad`, which seems like a promising approach that maybe can be adapted to this situation. – Qqwy Apr 12 '21 at 10:07
2

Great timing! Well-typed recently released a library which allows you to recover runtime information. They specifically have an example of showing arbitrary values. It's on github at https://github.com/well-typed/recover-rtti.

Anupam Jain
  • 7,851
  • 2
  • 39
  • 74
  • Nice! This is very useful. I was able to use it successfully to print a good description for the `Constant a` case. I will keep this question open however, as I am still searching for a way to resolve the more difficult situation of tracing existentially quantified functions, i.e. the `Map` and `Apply` cases. – Qqwy Apr 10 '21 at 15:09
0

It turns out that this is a problem which has been recognized by multiple people in the past, known as the 'Constrained Monad Problem'. There is an elegant solution, explained in detail in the paper The Constrained-Monad Problem by Neil Sculthorpe and Jan Bracker and George Giorgidze and Andy Gill.

A brief summary of the technique: Monads (and other typeclasses) have a 'normal form'. We can 'lift' primitives (which are constrained any way we wish) into this 'normal form' construction, itself an existential datatype, and then use any of the operations available for the typeclass we have lifted into. These operations themselves are not constrained, and thus we can use all of Haskell's normal typeclass functions. Finally, to turn this back into the concrete type (which again has all the constraints we are interested in) we 'lower' it, which is an operation that takes for each of the typeclass' operations a function which it will apply at the appropriate time. This way, constraints from the outside (which are part of the functions supplied to the lowering) and constraints from the inside (which are part of the primitives we lifted) are able to be matched, and finally we end up with one big happy constrained datatype for which we have been able to use any of the normal Functor/Monoid/Monad/etc. operations.

Interestingly, while the intermediate operations are not constrained, to my knowledge it is impossible to write something which 'breaks' them as this would break the categorical laws that the typeclass under consideration should adhere to.

This is available in the constrained-normal Hackage package to use in your own code.

The example I struggled with, could be implemented as follows:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}

module Example where

import Data.Dynamic
import Data.Kind
import Data.Typeable

import Control.Monad.ConstrainedNormal


-- | Required to have a simple constraint which we can use as argument to `Expr` / `Expr'`.
-- | This is definitely the part of the example with the roughest edges: I have yet to figure out
-- | how to make Haskell happy with constraints 
class (Show a, Typeable a) => Introspectable a where {}
instance (Show a, Typeable a) => Introspectable a where {}

data Expr' (c :: * -> Constraint) a where
  C :: a -> Expr' c a
  -- M :: (a -> b) -> Expr' a -> Expr' b --^ NOTE: This one is actually never used as ConstrainedNormal will use the 'free' implementation based on A + C.
  A :: c a => Expr' c (a -> b) -> Expr' c a -> Expr' c b


instance Introspectable a => Show (Expr' Introspectable a) where
  show e = case e of
    C x -> "(C " ++ show x ++ ")"
    -- M f x = "(M " ++ show val ++ ")"
    A fx x -> "(A " ++ show (typeOf fx) ++ " " ++ show x ++ ")"

-- | In user-facing code you'd not want to expose the guts of this construction
--   So let's introduce a 'wrapper type' which is what a user would normally interact with.
type Expr c a = NAF c (Expr' c) a

liftExpr :: c a => Expr' c a -> Expr c a
liftExpr expr = liftNAF expr

lowerExpr :: c a => Expr c a -> Expr' c a
lowerExpr lifted_expr = lowerNAF C A lifted_expr

constant :: Introspectable a => a -> Expr c a
constant val = pure val -- liftExpr (C val)

You could now for instance write

ghci> val = constant 10 :: Expr Introspectable Int
(C 10)
ghci> (+2) <$> val
(C 12)
ghci> (+) <$> constant 10 <*> constant 32  :: Expr Introspectable Int

And by using Data.Constraint.Trivial (part of the trivial-constrained library, although it is also possible to write your own 'empty constrained') one could instead write e.g.

ghci> val = constant 10 :: Expr Unconstrained Int

which will work just as before, but now val cannot be printed.


The one thing I have not yet figured out, is how to properly work with subsets of constraints (i.e. if I have a function that only requires Show, make it work with something that is Introspectable). Currently everything has to work with the 'big' set of constraints. Another minor drawback is of course that you'll have to annotate the constraint type (e.g. if you do not want constraints, write Unconstrained manually), as GHC will otherwise complain that c0 is not known.


We've reached the goal of having a type which can be optionally be constrained to be printable, with all machinery that does not need printing to work also on all instances of the family of types including those that are not printable, and the types can be used as Monoids, Functors, Applicatives, etc just as you like.

I think it is a beautiful approach, and want to commend Neil Sculthorpe et al. for their work on the paper and the constrained-normal library that makes this possible. It's very cool!

Qqwy
  • 5,214
  • 5
  • 42
  • 83