Generic solution to (Eq, Show) overlapping instances issue when defining class (* -> *) - haskell

Stack has many threads on overlapping instances, and while these are helpful in explaining the source of the problem, I am still not clear as to how to redesign my code for the problem to go away. While I will certain invest more time and effort in going through the details of existing answers, I will post here the general pattern which I have identified as creating the problem, in the hope that a simple and generic answer exists: I typically find myself defining a class such as:
{-# LANGUAGE FlexibleInstances #-}
class M m where
foo :: m v -> Int
bar :: m v -> String
together with the instance declarations:
instance (M m) => Eq (m v) where
(==) x y = (foo x) == (foo y) -- details unimportant
instance (M m) => Show (m v) where
show = bar -- details unimportant
and in the course of my work I will inevitably create some data type:
data A v = A v
and declare A as an instance of class M:
instance M A where
foo x = 1 -- details unimportant
bar x = "bar"
Then defining some elements of A Integer:
x = A 2
y = A 3
I have no issue printing x and y or evaluating the Boolean x == y, but if I attempt to print the list [x] or evaluate the Boolean [x] == [y], then the overlapping instance error occurs:
main = do
print x -- fine
print y -- fine
print (x == y) -- fine
print [x] -- overlapping instance error
if [x] == [y] then return () else return () -- overlapping instance error
The cause of these errors is now very clear I think: they stem from the existing instance declarations instance Show a => Show [a] and instance Eq a => Eq [a] and while it is true that [] :: * -> * has not yet been declared as an instance of my class M, there is nothing preventing someone doing so at some point: so the compiler ignores the context of instance declarations.
When faced with the pattern I have described, how can it be re-engineered to avoid the problem?

There's no backtracking in instance search. Instances are matched purely based on the syntactic structure of the instance head. That means instance contexts are not accounted for during instance resolution.
So, when you write
instance (M m) => Show (m v) where
show = bar
you're saying "Here is an instance for Show, for any type of the form m v". Since [x] :: [] (A Int) is indeed a type of the form m v (set m ~ [] and v ~ A Int), instance search for Show [A Int] turns up two candidates:
instance Show a => Show [a]
instance M m => Show (m v)
Like I said, the type checker doesn't look at the instances' contexts when selecting an instance, so these two instances are overlapping.
The fix is to not declare instances like Show (m v). As a general rule, it's a bad idea to declare instances whose head is composed purely of type variables. Every instance you write should start with an honest-to-goodness type constructor, and you should approach instances which don't fit that pattern with suspicion.
Supplying a newtype for your default instances is a fairly standard design (see, for example, WrappedBifunctor's Functor instance),
newtype WrappedM m a = WrappedM { unwrapM :: m a }
instance M m => Show (WrappedM m a) where
show = bar . unwrapM
as is giving a default implementation of the function at the top level (see eg foldMapDefault):
showDefault = bar

Related

Optimize Superclass Method Depending on Subclass

Can I provide a refined implementation (aka. override in OOP) of a method in a class instance, when the type is in another class, too? Or at least, if that other class is a subclass.
I have a class C with method m, a subclass S of C with method s and a type T a so there are instantiations
class C a where m :: [a] -> Bool
class C a => S a where s :: a -> a -> Bool
instance C a => C (T a) where m = ...
instance S a => S (T a) where s = ...
as usual.
Now it happens to be that when T a is in the subclass (which I cannot know as it depends on a), method m could be implemented much more efficient (quadratic vs. exponential time) using s.
I tried 'overriding' m in the implementation
instance S a => S (T a) where
s = ...
m = (all . uncurry) (=^=) . pairs -- override C.m
but the compiler errors basically because, m is not a public method of S. Well, it is not, but it's inherited in the OO sense.
For the specific purpose, the specialized version of m can be used for all instances; it's not a default to be overridden anywhere.
Edit: Because requested, the concrete code with a bit of explanation.
I have a class Model which has (among others) a method con that checks a list for consistency.
class Model a where
con :: [a] -> Bool
Two models can form an arrow model.
data Arrow a b = [a] :->: b
lhs w = [ a | (u :->: _) <- w, a <- u ]
rhs w = [ b | (_ :->: b) <- w ]
For the specific instance Model (Arrow a b), the general con implementation is very expensive (note powerset in the definition).
instance (Model a, Model b) => Model (Arrow a b) where
con w = all (\w' -> con (lhs w') `implies` con (rhs w')) (powerset w)
There is a subclass CoherentModel of Model which has a method (=^=) that checks consistency for two objects. The condition for coherent models is that a list is consistent iff all pairs are.
class Model a => CoherentModel a where
(=^=) :: a -> a -> Bool
a =^= b = con [a, b]
The class CoherentModel is at this point more documentation than a feature.
So, given that a model is coherent, consistency is much more efficient to check.
instance (Model a, CoherentModel b) => CoherentModel (Arrow a b) where
(u :->: a) =^= (v :->: b) = con (u ++ v) `implies` a =^= b
And in this case, con can be implemented using
con = (all . uncurry) (=^=) . pairs
where
pairs :: [a] -> [(a,a)]
pairs [] = []
pairs [_] = []
pairs [x,y] = [(x,y)]
pairs (x:xs) = map ((,) x) xs ++ pairs xs
but I find no way to specify this. It's not only for Arrow, it's relevant for all models with parameter. I chose Arrow because the improvement is significant.
It's a good question. One thing to remember is that whether a data type is an instance of a typeclass is compile-time only information -- i.e. we are always able to choose which instance to use using statically available information at the use site, and polymorphism comes from being able to choose an instance from the context. In general, if you ask "is a a member of typeclass B?", the only answers you can get are "yes" and "compile error". (This second observation is changed a bit by OverlappingInstances, but it doesn't seem to help in your case)
So the answer to your immediate question is no. You can't make a decision about a type's membership in a type class unless you are a method of that type class. What we can do is add this decision as a method (using the constraints package)
import Data.Constraint
class Model a where
con :: [a] -> Bool
isCoherent :: Maybe (Dict (CoherentModel a))
isCoherent = Nothing
Which you can define trivially for any type you have instantiated CoherentModel at:
instance Model Foo where
con = ...
isCoherent = Just Dict
Now you can implement your decision like this (w/ extensions ScopedTypeVariables and TypeApplications):
instance (Model a, Model b) => Model (Arrow a b) where
con | Just Dict <- isCoherent #b = -- efficient implementation
| otherwise = -- inefficient implementation
In the body of the first case we will have a local CoherentModel b in the context. It's kind of cool.
Too bad we have a sort of expression problem here where all the different implementations of con need to be collected up into one place. Also too bad isCoherent needs to be implemented manually on each coherent Model instance, separate from where its CoherentModel instance is.
There is a lot to explore here but I have to go. Good luck!

Using makeLenses, class constraints and type synonyms together

I'm quite new to Haskell and want to use makeLenses from Control.Lens and class constraints together with type synonyms to make my functions types more compact (readable?).
I've tried to come up with a minimal dummy example to demonstrate what I want to achieve and the example serves no other purpose than this.
At the end of this post I've added an example closer to my original problem if you are interested in the context.
Minimal example
As an example, say I define the following data type:
data State a = State { _a :: a
} deriving Show
, for which I also make lenses:
makeLenses ''State
In order to enforce a class constraint on the type parameter a used by the type constructor State I use a smart constructor:
mkState :: (Num a) => a -> State a
mkState n = State {_a = n}
Next, say I have a number of functions with type signatures similar to this:
doStuff :: Num a => State a -> State a
doStuff s = s & a %~ (*2)
This all works as intended, for example:
test = doStuff . mkState $ 5.5 -- results in State {_a = 11.0}
Problem
I've tried to use the following type synonym:
type S = (Num n) => State n -- Requires the RankNTypes extensions
, together with:
{-# LANGUAGE RankNTypes #-}
, in an attempt to simplify the type signature of doStuff:
doStuff :: S -> S
, but this gives the following error:
Couldn't match type `State a0' with `forall n. Num n => State n'
Expected type: a0 -> S
Actual type: a0 -> State a0
In the second argument of `(.)', namely `mkState'
In the expression: doStuff . mkState
In the expression: doStuff . mkState $ 5.5
Failed, modules loaded: none.
Question
My current knowledge of Haskell is not sufficient to understand what causes the above error. I hope someone can explain what causes the error and/or suggest other ways to construct the type synonym or why such a type synonym is not possible.
Background
My original problem looks closer to this:
data State r = State { _time :: Int
, _ready :: r
} deriving Show
makeLenses ''State
data Task = Task { ... }
Here I want to enforce the type of _ready being an instance of the Queue class using the following smart constructor:
mkState :: (Queue q) => Int -> q Task -> State (q Task)
mkState t q = State { _time = t
, _ready = q
}
I also have a number of functions with type signatures similar to this:
updateState :: Queue q => State (q Task) -> Task -> State (q Task)
updateState s x = s & ready %~ (enqueue x) & time %~ (+1)
I would like to use a type synonym S to be able to rewrite the type of such functions as:
updateState :: S -> Task -> S
, but as with the first minimal example I don't know how to define the type synonym S or whether it is possible at all.
Maybe there is no real benefit in trying to simplify the type signatures?
Related reading
I've read the following related questions on SO:
Class constraints for data records
Are type synonyms with typeclass constraints possible?
This might also be related but given my current understanding of Haskell I cannot really understand all of it:
Unifying associated type synonyms with class constraints
Follow-up
It's been a while since I've had the opportunity to do some Haskell. Thanks to #bheklilr I've now managed to introduce a type synonym only to hit the next type error I'm still not able to understand. I've posted the following follow-up question Type synonym causes type error regarding the new type error.
You see that error in particular because of the combination of the . operator and your use of RankNTypes. If you change it from
test = doStuff . mkState $ 5.5
to
test = doStuff $ mkState 5.5
or even
test = doStuff (mkState 5.5)
it will compile. Why is this? Look at the types:
doStuff :: forall n. Num n => State n -> State n
mkState :: Num n => n -> State n
(doStuff) . (mkState) <===> (forall n. Num n => State n -> State n) . (Num n => n -> State n)
Hopefully the parentheses help make it clear here, the n from forall n. Num n ... for doStuff is a different type variable from the Num n => ... for mkState because the scope of the forall only extends to the end of the parentheses. So these functions can't actually compose because the compiler sees them as separate types! There are actually special rules for the $ operator specifically for using the ST monad precisely for this reason, just so you can do runST $ do ....
You may be able to accomplish what you want easier using GADTs, but I don't believe lens' TemplateHaskell will work with GADT types. However, you can write your own pretty easily in this case, so it isn't that big of a deal.
A further explanation:
doStuff . mkState $ 5.5
is very different than
doStuff $ mkState 5.5
In the first one, doStuff says that for all Num types n, its type is State n -> State n, whereas mkState says for some Num type m, its type is m -> State m. These two types are not the same because of the "for all" and "for some" quantifications (hence ExistentialQuantification), since composing them would mean that for some Num m you can produce all Num n.
In the doStuff $ mkState 5.5, you have the equivalent of
(forall n. Num n => State n -> State n) $ (Num m => State m)
Notice that the type after the $ is not a function because mkState 5.5 is fully applied. So this works because for all Num n you can do State n -> State n, and you're providing it some Num m => State m. This works intuitively. Again, the difference here is the composition versus application. You can't compose a function that works on some types with a function that works on all types, but you can pass a value to a function that works on all types ("all types" here meaning forall n. Num n => n).

Haskell - create instance of class (how to do it right?)

I read the chapter about that topic in "learn you a haskell" and tried to find some hints on different websites - but are still unable to solve the following task.
Im a haskell newbie (6 weeks of "experience") and its the first time I have to work with instances.
So here is the task, my code has to pass the HUnit tests and the end. I tried to implement the instances but it seems like I´ve missed something there. Hope you can help me! THX
module SemiGroup where
{-
A type class 'SemiGroup' is given. It has exactly one method: a binary operation
called '(<>)'. Also a data type 'Tree' a newtype 'Sum' and a newtype 'Max' are
given. Make them instances of the 'SemiGroup' class.
The 'Tree' instance should build a 'Branch' of the given left and right side.
The 'Sum' instance should take the sum of its given left and right side. You need
a 'Num' constraint for that.
The 'Max' instance should take the maximum of its given left and right side. You
also need a constraint for that but you have to figure out yourself which one.
This module is not going to compile until you add the missing instances.
-}
import Test.HUnit (runTestTT,Test(TestLabel,TestList),(~?=))
-- | A semigroup has a binary operation.
class SemiGroup a where
(<>) :: a -> a -> a
-- Leaf = Blatt, Branch = Ast
-- | A binary tree data type.
data Tree a = Leaf a
| Branch (Tree a) (Tree a)
deriving (Eq,Show)
-- | A newtype for taking the sum.
newtype Sum a = Sum {unSum :: a}
-- | A newtype for taking the maximum.
newtype Max a = Max {unMax :: a}
instance SemiGroup Tree where
(<>) x y = ((x) (y))
instance SemiGroup (Num Sum) where
(<>) x y = x+y
instance SemiGroup (Eq Max) where
(<>) x y = if x>y then x else y
-- | Tests the implementation of the 'SemiGroup' instances.
main :: IO ()
main = do
testresults <- runTestTT tests
print testresults
-- | List of tests for the 'SemiGroup' instances.
tests :: Test
tests = TestLabel "SemiGroupTests" (TestList [
Leaf "Hello" <> Leaf "Friend" ~?= Branch (Leaf "Hello") (Leaf "Friend"),
unSum (Sum 4 <> Sum 8) ~?= 12,
unMax (Max 8 <> Max 4) ~?= 8])
I tried something like:
class SemiGroup a where
(<>) :: a -> a -> a
-- Leaf = Blatt, Branch = Ast
-- | A binary tree data type.
data Tree a = Leaf a
| Branch (Tree a) (Tree a)
deriving (Eq,Show)
-- | A newtype for taking the sum.
newtype Sum a = Sum {unSum :: a}
-- | A newtype for taking the maximum.
newtype Max a = Max {unMax :: a}
instance SemiGroup Tree where
x <> y = Branch x y
instance Num a => SemiGroup (Sum a) where
x <> y = x+y
instance Eq a => SemiGroup (Max a) where
x <> y = if x>y then x else y
But there a still some failures left! At least the wrap/unwrap thing that "chi" mentioned. But I have no idea. maybe another hint ? :/
I fail to see how to turn Tree a into a semigroup (unless it has to be considered up-to something).
For the Sum a newtype, you need to require that a is of class Num. Then, you need to wrap/unwrap the Sum constructor around values so that: 1) you take two Sum a, 2) you convert them into two a, which is a proper type over which + is defined, 3) you sum them, 4) you turn the result back into a Sum a.
You can try to code the above yourself starting from
instance Num a => Semigroup (Sum a) where
x <> y = ... -- Here both x and y have type (Sum a)
The Max a instance will require a similar wrap/unwrap code.
A further hint: to unwrap a Sum a into an a you can use the function
unSum :: Sum a -> a
to wrap an a into a Sum a you can use instead
Sum :: a -> Sum a
Note that both functions Sum, unSum are already implicitly defined by your newtype declaration, so you do not have to define them (you already did).
Alternatively, you can use pattern matching to unwrap your values. Instead of defining
x <> y = ... -- x,y have type Sum a (they are wrapped)
you can write
Sum x <> Sum y = ... -- x,y have type a (they are unwrapped)
Pay attention to the types. Either manually, or with some help from GHCi, figure out the type of the functions you are writing -- you'll find they don't match the types that the typeclass instance needs. You'll use wrapping and unwrapping to adjust the types until they work.

Trying to make my typeclass/instance. GHC says "Could not deduce..."

I am trying to make a simple graph structure and I wrote the following. But GHG raises error and I stacked there. This is the first time I make my own typeclass so maybe I am doing something terribly wrong. Can somebody explain what is wrong?
I found a similar question but I don't think it applies to my case.:
Error binding type variables in instance of typeclass
class Link l where
node :: (Node n) => l -> n
class Node n where
links :: (Link l) => n -> [l]
data (Node n) => SimpleLink n =
SimpleLink
{ simpleLinkNode :: n
} deriving (Show, Read, Eq)
instance (Node n) => Link (SimpleLink n) where
node = simpleLinkNode
data (Link l) => SimpleNode l =
SimpleNode
{ simpleNodeLinks :: [l]
} deriving (Show, Read, Eq)
instance (Link l) => Node (SimpleNode l) where
links = simpleNodeLinks
This is the error message I've got:
***.hs:13:10:Could not deduce (n ~ n1)
from the context (Node n)
bound by the instance declaration
at ***.hs:12:10-40
or from (Node n1)
bound by the type signature for
node :: Node n1 => SimpleLink n -> n1
at ***.hs:13:3-23
`n' is a rigid type variable bound by
the instance declaration
at ***.hs:12:16
`n1' is a rigid type variable bound by
the type signature for node :: Node n1 => SimpleLink n -> n1
at ***.hs:13:3
Expected type: SimpleLink n -> n1
Actual type: SimpleLink n -> n
In the expression: simpleLinkNode
In an equation for `node': node = simpleLinkNode
***.hs:21:11:Could not deduce (l ~ l1)
from the context (Link l)
bound by the instance declaration
at ***.hs:20:10-40
or from (Link l1)
bound by the type signature for
links :: Link l1 => SimpleNode l -> [l1]
at ***.hs:21:3-25
`l' is a rigid type variable bound by
the instance declaration
at ***.hs:20:16
`l1' is a rigid type variable bound by
the type signature for links :: Link l1 => SimpleNode l -> [l1]
at ***.hs:21:3
Expected type: SimpleNode l -> [l1]
Actual type: SimpleNode l -> [l]
In the expression: simpleNodeLinks
In an equation for `links': links = simpleNodeLinks
Edit 1
I tried some of Daniel's suggestions.
But I couldn't make them work.
constructor class
Got: "`n' is not applied to enough type arguments"
class Link l n where
node :: Node n l => l n -> n l
class Node n l where
links :: Link l n => n l -> [l n]
multi-parameter type class (MPTC)
Got: "Cycle in class declarations (via superclasses)"
class (Node n) => Link l n where
node :: l -> n
class (Link l) => Node n l where
links :: n -> [l]
MPTC with functional dependencies
Got: "Cycle in class declarations (via superclasses)"
class (Node n) => Link l n | l -> n where
node :: l -> n
class (Link l) => Node n l | n -> l where
links :: n -> [l]
Goal (Edit 2)
What I want to implement is a directed acyclic graph structure like the following (more specifically, a Factor graph).
(source: microsoft.com)
There are two kinds of node (white circle and red square) and they connect only to the different type of node, meaning that there are two kinds of links.
I want different version of nodes and links which have data (arrays) attached to them. I also want "vanilla" DAG which has only one type of node and link. But for traversing them, I want only one interface to do that.
The signature of the class methods
class Link l where
node :: (Node n) => l -> n
class Node n where
links :: (Link l) => n -> [l]
say that "whatever type the caller desires, node resp. links can produce it, as long as it's a member of Link resp. Node", but the implementation says that only one specific type of value can be produced.
It's fundamentally different from interfaces in OOP, where the implementation decides the type and the caller has to take it, here the caller decides.
You are running into kind problems with your constructor class attempt. Your classes take two parameters, l of kind kl and n of kind kn. The kinds of the arguments to (->) must both be *, the kind of types. So for l n to be a well-kinded argument of (->), l must be a type constructor taking an argument of kind kn and creating a result of kind *, i.e.
l :: kn -> *
Now you try to make the result type of node be n l, so that would mean
n :: kl -> *
But above we saw that kl = kn -> *, which yields
n :: (kn -> *) -> *
resp. kn = (kn -> *) -> *, which is an infinite kind. Infinite kinds, like infinite types, are not allowed. But kind-inference is implemented only very rudimentary, so the compiler assumes that the argument to l has kind *, but sees from n l that n has kind kl -> *, hence as an argument to l, n has the wrong kind, it is not applied to enough type arguments.
The normal use of constructor classes is a single-parameter class
class Link l where
node :: l nod -> nod
class Node n where
links :: n lin -> [lin]
-- note that we don't have constraints here, because the kinds don't fit
instance Link SimpleLink where
node = simpleLinkNode
instance Node SimpleNode where
links = simpleNodeLinks
You have to remove the DatatypeContexts from the data declarations,
They have been removed from the language (they are available via an extension)
They were never useful anyway
then the above compiles. I don't think it would help you, though. As Chris Kuklewicz observed, your types chase their own tail, you'd use them as
SimpleLink (SimpleNode (SimpleLink (SimpleNode ... {- ad infinitum -})))
For the multiparameter classes, you can't have each a requirement of the other, as the compiler says, that causes a dependency cycle (also, in your constraints you use them with only one parameter,
class Node n => Link l n where ...
which is malformed, the compiler would refuse that if the cycle is broken).
You could resolve the cycle by merging the classes,
class NodeLinks l n | l -> n, n -> l where
node :: l -> n
links :: n -> l
but you'd still have the problems that your types aren't useful for that.
I don't understand your goal well enough to suggest a viable solution, sorry.
Can somebody explain what is wrong?
An initial issue before I explain the error messages: Polymorphic data types are good, but in the end there has to be concrete type being used.
With SimpleNode of kind * -> * and SimpleLinks of kind * -> * there is no concrete type:
SimpleNode (SimpleLink (SimpleNode (SimpleLink (SimpleNode (...
You cannot have and infinite type in Haskell, though newtype and data get you closer:
type G0 = SimpleNode (SimpleLink G0) -- illegal
newtype G1 = G1 (SimpleNode (SimpleLink G1)) -- legal
data G2 = G2 (SimpleNode (SimpleLink G2)) -- legal
Perhaps you need to rethink your data types before creating the type class.
Now on to the error message explanation: Your type class Link defines a function node
class Link l where
node :: (Node n) => l -> n
The node is a magical OOP factory that, given the type and value of l, can then make any type n (bounded by Node n) the caller of node wishes. This n has nothing to do with the n in your instance:
instance (Node n) => Link (SimpleLink n) where
node = simpleLinkNode
To repeat myself: the n in the instance above is not the same n as in the node :: (Node n) => l -> n definition. The compiler makes a related but fresh name n1 and gives you the error:
`n' is a rigid type variable bound by
the instance declaration
at ***.hs:12:16
`n1' is a rigid type variable bound by
the type signature for node :: Node n1 => SimpleLink n -> n1
at ***.hs:13:3
The n in the instance is taken from the type (SimpleLink n) of the input to the node function. The n1 is the type that the caller of node is demanding that this magical factory produce. If n and n1 were the same then the compiler would be happy...but your definition of the type class and instance do not constrain this and thus the code snippet is rejected.
The analogous story is repeated for the error in SimpleLink. There is no silver-bullet fix for this. I expect that you need to rethink and redesign this, probably after reading other people's code in order to learn ways to accomplish your goal.
What is your goal? Graph data structures can be quite varied and the details matter.
I am breaking stack overflow etiquette and adding a second answer to keep this separate. This is a simple code example for a bipartite undirected graph with unlabeled edges, which might be useful to model a Factor Graph:
-- Bipartite graph representation, unlabeled edges
-- Data types to hold information about nodes, e.g. ID number
data VariableVertex = VV { vvID :: Int } deriving (Show)
data FactorVertex = FV { fvID :: Int } deriving (Show)
-- Node holds itself and a list of neighbors of the oppostite type
data Node selfType adjacentType =
N { self :: selfType
, adj :: [Node adjacentType selfType] }
-- A custom Show for Node to prevent infinite output
instance (Show a, Show b) => Show (Node a b) where
show (N x ys) = "Node "++ show x ++ " near " ++ show (map self ys)
-- Type aliases for the two node types that will be used
type VariableNode = Node VariableVertex FactorVertex
type FactorNode = Node FactorVertex VariableVertex
data FactorGraph = FG [VariableNode] [FactorNode] deriving (Show)
v1 = N (VV 1) [f1,f2]
v2 = N (VV 2) [f2]
v3 = N (VV 3) [f1,f3]
f1 = N (FV 1) [v1,v3]
f2 = N (FV 2) [v1,v2]
f3 = N (FV 3) [v3]
g = FG [v1,v2,v3] [f1,f2,f3]
With the hint from Chris Kuklewicz (http://stackoverflow.com/a/11450715/727827), I got the code I wanted in the first place.
However, I think Crhis's answer (using *Vertex to hold data) is simple and better. I am leaving this here to clarify what I wanted.
class NodeClass n where
adjacent :: n a b -> [n b a]
data Node selfType adjacentType =
N
{ selfNode :: selfType
, adjNode :: [Node adjacentType selfType] }
data NodeWithData selfType adjacentType =
NWD
{ selfNodeWithData :: selfType
, adjNodeWithData :: [NodeWithData adjacentType selfType]
, getDataWithData :: [Double]
}
instance NodeClass Node where
adjacent = adjNode
instance NodeClass NodeWithData where
adjacent = adjNodeWithData
data VariableVertex = VV { vvID :: Int } deriving (Show)
data FactorVertex = FV { fvID :: Int } deriving (Show)
type VariableNode = Node VariableVertex FactorVertex
type FactorNode = Node FactorVertex VariableVertex
type VariableNodeWithData = NodeWithData VariableVertex FactorVertex
type FactorNodeWithData = NodeWithData FactorVertex VariableVertex

Get a list of the instances in a type class in Haskell

Is there a way to programmatically get a list of instances of a type class?
It strikes me that the compiler must know this information in order to type check and compile the code, so is there some way to tell the compiler: hey, you know those instances of that class, please put a list of them right here (as strings or whatever some representation of them).
You can generate the instances in scope for a given type class using Template Haskell.
import Language.Haskell.TH
-- get a list of instances
getInstances :: Name -> Q [ClassInstance]
getInstances typ = do
ClassI _ instances <- reify typ
return instances
-- convert the list of instances into an Exp so they can be displayed in GHCi
showInstances :: Name -> Q Exp
showInstances typ = do
ins <- getInstances typ
return . LitE . stringL $ show ins
Running this in GHCi:
*Main> $(showInstances ''Num)
"[ClassInstance {ci_dfun = GHC.Num.$fNumInteger, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Integer.Type.Integer]},ClassInstance {ci_dfun = GHC.Num.$fNumInt, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Int]},ClassInstance {ci_dfun = GHC.Float.$fNumFloat, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Float]},ClassInstance {ci_dfun = GHC.Float.$fNumDouble, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Double]}]"
Another useful technique is showing all instances in scope for a given type class using GHCi.
Prelude> :info Num
class (Eq a, Show a) => Num a where
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Integer -> a
-- Defined in GHC.Num
instance Num Integer -- Defined in GHC.Num
instance Num Int -- Defined in GHC.Num
instance Num Float -- Defined in GHC.Float
instance Num Double -- Defined in GHC.Float
Edit: The important thing to know is that the compiler is only aware of type classes in scope in any given module (or at the ghci prompt, etc.). So if you call the showInstances TH function with no imports, you'll only get instances from the Prelude. If you have other modules in scope, e.g. Data.Word, then you'll see all those instances too.
See the template haskell documentation: http://hackage.haskell.org/packages/archive/template-haskell/2.5.0.0/doc/html/Language-Haskell-TH.html
Using reify, you can get an Info record, which for a class includes its list of instances. You can also use isClassInstance and classInstances directly.
This is going to run into a lot of problems as soon as you get instance declarations like
instance Eq a => Eq [a] where
[] == [] = True
(x:xs) == (y:ys) = x == y && xs == ys
_ == _ = False
and
instance (Eq a,Eq b) => Eq (a,b) where
(a1,b1) == (a2,b2) = a1 == a2 && b1 == b2
along with a single concrete instance (e.g. instance Eq Bool).
You'll get an infinite list of instances for Eq - Bool,[Bool],[[Bool]],[[[Bool]]] and so on, (Bool,Bool), ((Bool,Bool),Bool), (((Bool,Bool),Bool),Bool) etcetera, along with various combinations of these such as ([((Bool,[Bool]),Bool)],Bool) and so forth. It's not clear how to represent these in a String; even a list of TypeRep would require some pretty smart enumeration.
The compiler can (try to) deduce whether a type is an instance of Eq for any given type, but it doesn't read in all the instance declarations in scope and then just starts deducing all possible instances, since that will never finish!
The important question is of course, what do you need this for?
I guess, it's not possible. I explain you the implementation of typeclasses (for GHC), from it, you can see, that the compiler has no need to know which types are instance of a typeclass. It only has to know, whether a specific type is instance or not.
A typeclass will be translated into a datatype. As an example, let's take Eq:
class Eq a where
(==),(/=) :: a -> a -> Bool
The typeclass will be translated into a kind of dictionary, containing all its functions:
data Eq a = Eq {
(==) :: a -> a -> Bool,
(/=) :: a -> a -> Bool
}
Each typeclass constraint is then translated into an extra argument containing the dictionary:
elem :: Eq a => a -> [a] -> Bool
elem _ [] = False
elem a (x:xs) | x == a = True
| otherwise = elem a xs
becomes:
elem :: Eq a -> a -> [a] -> Bool
elem _ _ [] = False
elem eq a (x:xs) | (==) eq x a = True
| otherwise = elem eq a xs
The important thing is, that the dictionary will be passed at runtime. Imagine, your project contains many modules. GHC doesn't have to check all the modules for instances, it just has to look up, whether an instance is defined anywhere.
But if you have the source available, I guess an old-style grep for the instances would be sufficient.
It is not possible to automatically do this for existing classes. For your own class and instances thereof you could do it. You would need to declare everything via Template Haskell (or perhaps the quasi-quoting) and it would automatically generate some strange data structure that encodes the declared instances. Defining the strange data structure and making Template Haskell do this are details left to whomever has a use case for them.
Perhaps you could add some Template Haskell or other magic to your build to include all the source files as text available at run-time (c.f. program quine). Then your program would 'grep itself'...

Resources