How might I be able to write multiple function definitions for multiple types in a polymorphic manner in Haskell? - haskell

Given my type definitions:
data Tile = Revealed | Covered deriving (Eq, Show)
data MinePit = Clean | Unsafe deriving (Eq, Show)
data Flag = Flagged | Unflagged deriving (Eq, Show)
type Square = (Tile, MinePit, Flag)
type Board = [[Square]]
I created two functions:
createBoard generates a 2D list of tuples of values -- or a 'Board'. It initialises a list of dimension n*m all of the same value.
createBoard :: Int -> Int -> Board
createBoard 0 _ = [[]]
createBoard _ 0 = [[]]
createBoard 1 1 = [[(Covered, Clean, Unflagged)]]
createBoard n m = take n (repeat (take m (repeat (Covered, Clean, Unflagged))))
An example:
λ> createBoard 2 3
[[(Covered,Clean,Unflagged),(Covered,Clean,Unflagged),(Covered,Clean,Unflagged)],[(Covered,Clean,Unflagged),(Covered,Clean,Unflagged),(Covered,Clean,Unflagged)]]
A function defineIndices was defined for the purpose of an in order list of indices for Board(s) produced by createBoard.
defineIndices :: Int -> Int -> [[(Int,Int)]]
defineIndices n m = [[(i,j) | j <- [1..m]] | i <- [1..n]]
It behaves like:
λ> defineIndices 2 3
[[(1,1),(1,2),(1,3)],[(2,1),(2,2),(2,3)]]
From here, I have created a function to create a MapBoard, where the values of a particular Square could be looked up given its indicies.
type MapBoard = Map (Int, Int) Square
createMapBoard :: [[(Int,Int)]] -> [[Square]] -> MapBoard
createMapBoard indices squares = M.fromList $ zip (concat indices) (concat squares)
However, it seemed reasonable to me that I should also write a method in which I can create a MapBoard directly from a pair of Int(s), implementing my prior functions. This might look like:
createMapBoard2 :: Int -> Int -> MapBoard
createMapBoard2 n m = createMapBoard indices squares where
indices = defineIndices n m
squares = createBoard n m
However, I looked up as to whether it is possible achieve polymorphism in this situataion with createMapBoard, and have createMapBoard2 be instead createMapBoard. I discovered online that this is called Ad-Hoc Polymorphism, and one can do e.g.
class Square a where
square :: a -> a
instance Square Int where
square x = x * x
instance Square Float where
square x = x * x
Attempting to write something similar myself, the best I could come up with is the following:
class MyClass a b MapBoard where
createMapBoard :: a -> b -> MapBoard
instance createMapBoard [[(Int,Int)]] -> [[Square]] -> MapBoard where
createMapBoard indices squares = M.fromList $ zip (concat indices) (concat squares)
instance createMapBoard Int -> Int -> MapBoard where
createMapBoard n m = createMapBoard indices squares where
indices = defineIndices n m
squares = createBoard n m
Attempting to compile this results in a Compilation error:
src/minesweeper.hs:35:19-26: error: …
Unexpected type ‘MapBoard’
In the class declaration for ‘MyClass’
A class declaration should have form
class MyClass a b c where ...
|
Compilation failed.
λ>
I am confused as to why I am not allowed to use a non-algebraic type such as MapBoard in the class definition.
class MyClass a b MapBoard where
Replacing MapBoard with another algebraic type c brings about another compilation error, which is lost on me.
src/minesweeper.hs:37:10-63: error: …
Illegal class instance: ‘createMapBoard [[(Int, Int)]]
-> [[Square]] -> MapBoard’
Class instances must be of the form
context => C ty_1 ... ty_n
where ‘C’ is a class
|
src/minesweeper.hs:39:10-46: error: …
Illegal class instance: ‘createMapBoard Int -> Int -> MapBoard’
Class instances must be of the form
context => C ty_1 ... ty_n
where ‘C’ is a class
|
Compilation failed.
Is it possible for me to achieve the ad-hoc polymorphism of createMapBoard? Am I able to create a class definition which has a strict constraint that the return type must be MapBoard for all instances?
Edit:
Having corrected the syntactic errors, my code is now:
class MyClass a b where
createMapBoard :: a -> b
instance createMapBoard [[(Int,Int)]] [[Square]] where
createMapBoard indices squares = M.fromList $ zip (concat indices) (concat squares)
instance createMapBoard Int Int where
createMapBoard n m = createMapBoard indices squares where
indices = defineIndices n m
squares = createBoard n m
This leads to yet another compilation error:
src/minesweeper.hs:37:10-23: error: …
Not in scope: type variable ‘createMapBoard’
|
src/minesweeper.hs:39:10-23: error: …
Not in scope: type variable ‘createMapBoard’
|
Compilation failed.
I am inclined to believe that an error in my understanding of classes is still present.

You want to write it this way:
class MyClass a b where createMapBoard :: a -> b -> MapBoard
instance MyClass [[(Int,Int)]] [[Square]] where
createMapBoard indices squares = M.fromList $ zip ...
instance MyClass Int Int where
createMapBoard n m = createMapBoard indices squares where
...
The ... -> ... -> MapBoard is already in the createMapBoard method's signature, this doesn't belong in the class / instance heads.
Incidentally, I'm not convinced that it really makes sense to have a class here at all. There's nothing wrong with having two separately named createMapBoard functions. A class only is the way to go if you can actually write polymorphic functions over it, but in this case I doubt it – you'd rather have either the concrete situation where you need the one version, or the other. There's no need for a class then, just hard-write which version it is you want.
One reason for rather going with separate functions than a class method is that it makes the type checker's work easier. As soon as the arguments of createMapBoard are polymorphic, they could potentially have any type (at least as far as the type checker is concerned). So you can only call it with arguments whose type is fully determined elsewhere. Now, in other programming languages the type of values you might want to pass is generally fixed anyway, but in Haskell it's actually extremely common to have also polymorphic values. The simplest example is number literals – they don't have type Int or so, but Num a => a.
I personally find “reverse polymorphism” normally nicer to work with than “forward polymorphism”: don't make the arguments to functions polymorphic, but rather the results. This way, it's enough to have the outermost type of an expression fixed by the environment, and automatically all the subexpressions are inferred by the type checker. The other way around, you have to have all the individual expressions' types fixed, and the compiler can infer the final result type... which is hardly useful because you probably want to fix that by a signature anyway.

Related

Getting all function arguments in haskel as list

Is there a way in haskell to get all function arguments as a list.
Let's supose we have the following program, where we want to add the two smaller numbers and then subtract the largest. Suppose, we can't change the function definition of foo :: Int -> Int -> Int -> Int. Is there a way to get all function arguments as a list, other than constructing a new list and add all arguments as an element of said list? More importantly, is there a general way of doing this independent of the number of arguments?
Example:
module Foo where
import Data.List
foo :: Int -> Int -> Int -> Int
foo a b c = result!!0 + result!!1 - result!!2 where result = sort ([a, b, c])
is there a general way of doing this independent of the number of arguments?
Not really; at least it's not worth it. First off, this entire idea isn't very useful because lists are homogeneous: all elements must have the same type, so it only works for the rather unusual special case of functions which only take arguments of a single type.
Even then, the problem is that “number of arguments” isn't really a sensible concept in Haskell, because as Willem Van Onsem commented, all functions really only have one argument (further arguments are actually only given to the result of the first application, which has again function type).
That said, at least for a single argument- and final-result type, it is quite easy to pack any number of arguments into a list:
{-# LANGUAGE FlexibleInstances #-}
class UsingList f where
usingList :: ([Int] -> Int) -> f
instance UsingList Int where
usingList f = f []
instance UsingList r => UsingList (Int -> r) where
usingList f a = usingList (f . (a:))
foo :: Int -> Int -> Int -> Int
foo = usingList $ (\[α,β,γ] -> α + β - γ) . sort
It's also possible to make this work for any type of the arguments, using type families or a multi-param type class. What's not so simple though is to write it once and for all with variable type of the final result. The reason being, that would also have to handle a function as the type of final result. But then, that could also be intepreted as “we still need to add one more argument to the list”!
With all respect, I would disagree with #leftaroundabout's answer above. Something being
unusual is not a reason to shun it as unworthy.
It is correct that you would not be able to define a polymorphic variadic list constructor
without type annotations. However, we're not usually dealing with Haskell 98, where type
annotations were never required. With Dependent Haskell just around the corner, some
familiarity with non-trivial type annotations is becoming vital.
So, let's take a shot at this, disregarding worthiness considerations.
One way to define a function that does not seem to admit a single type is to make it a method of a
suitably constructed class. Many a trick involving type classes were devised by cunning
Haskellers, starting at least as early as 15 years ago. Even if we don't understand their
type wizardry in all its depth, we may still try our hand with a similar approach.
Let us first try to obtain a method for summing any number of Integers. That means repeatedly
applying a function like (+), with a uniform type such as a -> a -> a. Here's one way to do
it:
class Eval a where
eval :: Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval i = \y -> eval (i + y)
instance Eval Integer where
eval i = i
And this is the extract from repl:
λ eval 1 2 3 :: Integer
6
Notice that we can't do without explicit type annotation, because the very idea of our approach is
that an expression eval x1 ... xn may either be a function that waits for yet another argument,
or a final value.
One generalization now is to actually make a list of values. The science tells us that
we may derive any monoid from a list. Indeed, insofar as sum is a monoid, we may turn arguments to
a list, then sum it and obtain the same result as above.
Here's how we can go about turning arguments of our method to a list:
class Eval a where
eval2 :: [Integer] -> Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [Integer] where
eval2 is i = i:is
This is how it would work:
λ eval2 [] 1 2 3 4 5 :: [Integer]
[5,4,3,2,1]
Unfortunately, we have to make eval binary, rather than unary, because it now has to compose two
different things: a (possibly empty) list of values and the next value to put in. Notice how it's
similar to the usual foldr:
λ foldr (:) [] [1,2,3,4,5]
[1,2,3,4,5]
The next generalization we'd like to have is allowing arbitrary types inside the list. It's a bit
tricky, as we have to make Eval a 2-parameter type class:
class Eval a i where
eval2 :: [i] -> i -> a
instance (Eval a i) => Eval (i -> a) i where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [i] i where
eval2 is i = i:is
It works as the previous with Integers, but it can also carry any other type, even a function:
(I'm sorry for the messy example. I had to show a function somehow.)
λ ($ 10) <$> (eval2 [] (+1) (subtract 2) (*3) (^4) :: [Integer -> Integer])
[10000,30,8,11]
So far so good: we can convert any number of arguments into a list. However, it will be hard to
compose this function with the one that would do useful work with the resulting list, because
composition only admits unary functions − with some trickery, binary ones, but in no way the
variadic. Seems like we'll have to define our own way to compose functions. That's how I see it:
class Ap a i r where
apply :: ([i] -> r) -> [i] -> i -> a
apply', ($...) :: ([i] -> r) -> i -> a
($...) = apply'
instance Ap a i r => Ap (i -> a) i r where
apply f xs x = \y -> apply f (x:xs) y
apply' f x = \y -> apply f [x] y
instance Ap r i r where
apply f xs x = f $ x:xs
apply' f x = f [x]
Now we can write our desired function as an application of a list-admitting function to any number
of arguments:
foo' :: (Num r, Ord r, Ap a r r) => r -> a
foo' = (g $...)
where f = (\result -> (result !! 0) + (result !! 1) - (result !! 2))
g = f . sort
You'll still have to type annotate it at every call site, like this:
λ foo' 4 5 10 :: Integer
-1
− But so far, that's the best I can do.
The more I study Haskell, the more I am certain that nothing is impossible.

How can I build a recursive tree with concrete data types in Haskell?

I'd like to build a tree in Haskell where each node has a concrete data type. Ultimately I want to build and use my own, more complicated types, but I can't quite figure out how to get the toy example below to work.
I'd like to create a tree of Integers, starting with a large value at the trunk, getting smaller as you traverse down to the leaves.
data Tree x = Empty | Node x (Tree x) (Tree x) deriving (Show, Read, Eq)
copyBox :: Int -> Tree x
copyBox x
| x <= 0 = Node x Empty Empty
| x > 0 = Node x (copyBox (x-1)) (copyBox (x-1))
I would expect to be able to build a small tree like this:
let newtree = copyBox 3
ghci throws an error "Couldn't match expected type 'x' with actual type 'Int'" at line 5.
If I replace the function declaration above with the more general version below, there is no problem:
copyBox :: (Ord x, Num x) => x -> Tree x
Why isn't the type of x just "Int" in both cases?
copyBox :: Int -> Tree x promises to return a Tree of any type at all, at the caller's whim. So I can write copyBox 5 :: Tree String, which is a legal call based on your type signature. But of course this will fail: you're putting x in the Nodes; and you're trying to subtract 1 from it, which only works if it's a numeric type; and you're comparing it to 0, which only works if it's an ordered type...
You probably just intend copyBox :: Int -> Tree Int, since you are clearly only building a Tree with Int values in it.

How to get a value in a tagged union data type in Haskell?

In Haskell, if I create a dataype like this:
data MyT = MyT Int deriving (Show)
myValue = MyT 42
I can get the Int value passing 'myValue' to a function and doing pattern matching:
getInt :: MyT -> Int
getInt (MyT n) = n
It seems to me that something simpler should be possible. Is there another way?
Also, I tried a lambda function:
(\(MyT n) -> n) myValue
It doesn't work and I don't understand why not.
I get the error:
The function `\ (MyT n) -> n' is applied to two arguments,
but its type `MyT -> Int' has only one
EDIT:
Of course, sepp2k below, is right about my lambda function working OK. I was doing:
(\(MyT n) -> n) myT 42
instead of
(\(MyT n) -> n) (myT 42)
If you want to get at the value of MyT inside a larger function without defining a helper function, you could either use case of or pattern matching in local variable definitions. Here are examples of that (assuming that g produces a MyT and f takes an Int):
Using case:
myLargerFunction x = f (case g x of MyT n => n)
Or with local variables:
myLargerFunction x = f myInt
where MyT myInt = g x
Or using let instead of where:
myLargerFunction x =
let MyT myInt = g x in
f myInt
Your lambda function should (and in fact does) also work fine. Your error message suggests that in your real code you're really doing something like (\(MyT n) -> n) myValue somethingElse (presumably by accident).
You can use the record syntax
data MyT = MyT {unMyT :: Int} deriving (Show)
which gives you the projection for free
unMyT :: MyT -> Int
This is nice if your data type has only one constructor (including newtypes). For data types involving more than one constrctor, projection functions tend to be unsafe (e.g., head,tail), and pattern matching is usually preferred instead. GHC checks for non-exhaustive patterns if you enable warnings, and can help to spot errors.
NewTypes create a distinct type and do not have an extra level of indirection like algebraic datatypes. See the Haskell report for more information:
http://www.haskell.org/onlinereport/decls.html#sect4.2.3
Prelude> newtype Age = Age { unAge :: Int } deriving (Show)
Prelude> let personAge = Age 42
Prelude> personAge
Age {unAge = 42}
Prelude> (unAge personAge) + 1
43
Using a lambda function:
Prelude> (\(Age age) -> age * 2) personAge
84

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

Can you pattern match constructors on a type class constrained parameter?

See code example below. It won't compile. I had thought that maybe it's because it has to have a single type for the first parameter in the test function. But that doesn't make sense because if I don't pattern match on it so it will compile, I can call it with both MyObj11 5 and MyObj21 5 which are two different types.
So what is it that restricts so you can't pattern match on constructors with a type class constrained parameter? Or is there some mechanism by which you can?
class SomeClass a where toString :: a -> String
instance SomeClass MyType1 where toString v = "MyType1"
instance SomeClass MyType2 where toString v = "MyType2"
data MyType1 = MyObj11 Int | MyObj12 Int Int
data MyType2 = MyObj21 Int | MyObj22 Int Int
test :: SomeClass a => a -> String
test (MyObj11 x) = "11"
test (MyObj12 x y) = "12" -- Error here if remove 3rd line: rigid type bound error
test (MyObj22 x y) = "22" -- Error here about not match MyType1.
what is it that restricts so you can't pattern match on constructors with a type class constrained parameter?
When you pattern match on an explicit constructor, you commit to a specific data type representation. This data type is not shared among all instances of the class, and so it is simply not possible to write a function that works for all instances in this way.
Instead, you need to associate the different behaviors your want with each instance, like so:
class C a where
toString :: a -> String
draw :: a -> String
instance C MyType1 where
toString v = "MyType1"
draw (MyObj11 x) = "11"
draw (MyObj12 x y) = "12"
instance C MyType2 where
toString v = "MyType2"
draw (MyObj22 x y) = "22"
data MyType1 = MyObj11 Int | MyObj12 Int Int
data MyType2 = MyObj21 Int | MyObj22 Int Int
test :: C a => a -> String
test x = draw x
The branches of your original test function are now distributed amongst the instances.
Some alternative tricks involve using class-associated data types (where you prove to the compiler that a data type is shared amongst all instances), or view patterns (which let you generalize pattern matching).
View patterns
We can use view patterns to clean up the connection between pattern matching and type class instances, a little, allowing us to approximate pattern matching across instances by pattern matching on a shared type.
Here's an example, where we write one function, with two cases, that lets us pattern match against anything in the class.
{-# LANGUAGE ViewPatterns #-}
class C a where
view :: a -> View
data View = One Int
| Two Int Int
data MyType1 = MyObj11 Int | MyObj12 Int Int
instance C MyType1 where
view (MyObj11 n) = One n
view (MyObj12 n m) = Two n m
data MyType2 = MyObj21 Int | MyObj22 Int Int
instance C MyType2 where
view (MyObj21 n) = One n
view (MyObj22 n m) = Two n m
test :: C a => a -> String
test (view -> One n) = "One " ++ show n
test (view -> Two n m) = "Two " ++ show n ++ show m
Note how the -> syntax lets us call back to the right view function in each instance, looking up a custom data type encoding per-type, in order to pattern match on it.
The design challenge is to come up with a view type that captures all the behavior variants you're interested in.
In your original question, you wanted every constructor to have a different behavior, so there's actually no reason to use a view type (dispatching directly to that behavior in each instance already works well enough).

Resources