[Haskell-cafe] Dispatch a type-function on the existence (or not) of instances?

Richard Eisenberg eir at cis.upenn.edu
Sat Feb 1 18:21:12 UTC 2014


I am sure that "2) The possibility of "converting" a constraint into a type-level bool." is *not* possible. And, it really shouldn't be possible.

The problem has to do with modules. Suppose we have:

> module A where
> data Foo
> type Magic           -- invented syntax:
>   | Show Foo  = Int
>   | otherwise = Bool

> module B where
> import A
> instance Show Foo
> bar :: Magic
> bar = 3

> module C where
> import A
> quux :: Magic -- no (Show Foo) here!
> quux = False

> module D where
> import B
> import C
> hasSameType :: a -> a -> ()
> hasSameType _ _ = ()
> unit :: ()
> unit = hasSameType bar quux

Does that last line of D type-check? `bar` and `quux` are both declared to have the same type. But, of course, they don't have the same type! Yuck. Thus, `Magic` cannot exist.

In my own work, I've often wanted something like Magic, but I've learned that whenever I start wanting Magic, what I really want is a very different design.

If you really, really want Magic and just can't live without it though, you might consider using Template Haskell. TH code can query the database of available instances and branch on the existence of an instance. See `reifyInstances`. TH can't cause the problem I described above, because the equivalent using TH would give `bar` and `quux` different types at compile time, because the TH code is fully evaluated, unlike something like `Magic` which might not be.

I hope this helps!
Richard

On Jan 31, 2014, at 12:56 PM, Hans Höglund <hans at hanshoglund.se> wrote:

> Dear all,
> 
> I have been curious about the ability to detect the presence of a certain instance (ClassFoo TypeBar) in the type system.
> Specifically, is it possible to "dispatch" a type on the existence (or not) of such an instance. For example given two functions:
> 
> withInstance :: (ClassFoo TypeBar) => TypeIfInstanceExists
> withoutInstance :: TypeIfInstanceDoesNotExists
> 
> I would be able to consolidate them into something like this:
> 
> withOrWithoutInstance :: 
>    (r ~ InstanceExists ClassFoo TypeBar, 
>     a ~ If r TypeIfInstanceExists TypeIfInstanceDoesNotExists) => a
> 
> I guess what I need is:
> 
> 1) A type-level "if".
> 2) The possibility of "converting" a constraint into a type-level bool.
> 
> I am sure (1) is possible but have no idea about (2). Anyone?
> 
> Best regards,
> Hans
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list