Writing A Function Polymorphic In A Type Family - haskell

I was experimenting with type families yesterday and ran into an obstacle with the following code:
{-# LANGUAGE TypeFamilies #-}
class C a where
type A a
myLength :: A a -> Int
instance C String where
type A String = [String]
myLength = length
instance C Int where
type A Int = [Int]
myLength = length
main = let a1 = [1,2,3]
a2 = ["hello","world"]
in print (myLength a1)
>> print (myLength a2)
Here I have a type associated with class C and a function that calculates the length of the associated type. However the above code gives me this error:
/tmp/type-families.hs:18:30:
Couldn't match type `A a1' with `[a]'
In the first argument of `myLength', namely `a1'
In the first argument of `print', namely `(myLength a1)'
In the first argument of `(>>)', namely `print (myLength a1)'
/tmp/type-families.hs:19:30:
Couldn't match type `A a2' with `[[Char]]'
In the first argument of `myLength', namely `a2'
In the first argument of `print', namely `(myLength a2)'
In the second argument of `(>>)', namely `print (myLength a2)'
Failed, modules loaded: none.
If, however I change "type" to "data" the code compiles and works:
{-# LANGUAGE TypeFamilies #-}
class C a where
data A a
myLength :: A a -> Int
instance C String where
data A String = S [String]
myLength (S a) = length a
instance C Int where
data A Int = I [Int]
myLength (I a) = length a
main = let a1 = I [1,2,3]
a2 = S ["hello","world"]
in
print (myLength a1) >>
print (myLength a2)
Why does "length" not work as expected in the first case? The lines "type A String ..." and "type A Int ..." specify that the type "A a" is a list so myLength should have the following types respectively : "myLength :: [String] -> Int" or "myLength :: [Int] -> Int".

Hm. Let's forget about types for a moment.
Let's say you have two functions:
import qualified Data.IntMap as IM
a :: Int -> Float
a x = fromInteger (x * x) / 2
l :: Int -> String
l x = fromMaybe "" $ IM.lookup x im
where im = IM.fromList -- etc...
Say there exists some value n :: Int that you care about. Given only the value of a n, how do you find the value of l n? You don't, of course.
How is this relevant? Well, the type of myLength is A a -> Int, where A a is the result of applying the "type function" A to some type a. However, myLength being part of a type class, the class parameter a is used to select which implementation of myLength to use. So, given a value of some specific type B, applying myLength to it gives a type of B -> Int, where B ~ A a and you need to know the a in order to look up the implementation of myLength. Given only the value of A a, how do you find the value of a? You don't, of course.
You could reasonably object that in your code here, the function A is invertible, unlike the a function in my earlier example. This is true, but the compiler can't do anything with that because of the open world assumption where type classes are involved; your module could, in theory, be imported by another module that defines its own instance, e.g.:
instance C Bool where
type A Bool = [String]
Silly? Yes. Valid code? Also yes.
In many cases, the use of constructors in Haskell serves to create trivially injective functions: The constructor introduces a new entity that is defined only and uniquely by the arguments it's given, making it simple to recover the original values. This is precisely the difference between the two versions of your code; the data family makes the type function invertible by defining a new, distinct type for each argument.

Related

Basic Haskell function types?

Super basic question - but I can't seem to get a clear answer. The below function won't compile:
randomfunc :: a -> a -> b
randomfunc e1 e2
| e1 > 2 && e2 > 2 = "Both greater"
| otherwise = "Not both greater"
main = do
let x = randomfunc 2 1
putStrLn $ show x
I'm confused as to why this won't work. Both parameters are type 'a' (Ints) and the return parameter is type 'b' (String)?
Error:
"Couldn't match expected type ‘b’ with actual type ‘[Char]’"
Not quite. Your function signature indicates: for all types a and b, randomfunc will return something of type b if given two things of type a.
However, randomFunc returns a String ([Char]). And since you compare e1 with 2 each other, you cannot use all a's, only those that can be used with >:
(>) :: Ord a => a -> a -> Bool
Note that e1 > 2 also needs a way to create such an an a from 2:
(> 2) :: (Num a, Ord a) => a -> Bool
So either use a specific type, or make sure that you handle all those constraints correctly:
randomfunc :: Int -> Int -> String
randomFunc :: (Ord a, Num a) => a -> a -> String
Both parameters are type 'a' (Ints) and the return parameter is type 'b' (String)?
In a Haskell type signature, when you write names that begin with a lowercase letter such as a, the compiler implicitly adds forall a. to the beginning of the type. So, this is what the compiler actually sees:
randomfunc :: forall a b. a -> a -> b
The type signature claims that your function will work for whatever ("for all") types a and b the caller throws at you. But this is not true for your function, since it only works on Int and String respectively.
You need to make your type more specific:
randomfunc :: Int -> Int -> String
On the other hand, perhaps you intended to ask the compiler to fill out a and b for you automatically, rather than to claim that it will work for all a and b. In that case, what you are really looking for is the PartialTypeSignatures feature:
{-# LANGUAGE PartialTypeSignatures #-}
randomfunc :: _a -> _a -> _b

What can type families do that multi param type classes and functional dependencies cannot

I have played around with TypeFamilies, FunctionalDependencies, and MultiParamTypeClasses. And it seems to me as though TypeFamilies doesn't add any concrete functionality over the other two. (But not vice versa). But I know type families are pretty well liked so I feel like I am missing something:
"open" relation between types, such as a conversion function, which does not seem possible with TypeFamilies. Done with MultiParamTypeClasses:
class Convert a b where
convert :: a -> b
instance Convert Foo Bar where
convert = foo2Bar
instance Convert Foo Baz where
convert = foo2Baz
instance Convert Bar Baz where
convert = bar2Baz
Surjective relation between types, such as a sort of type safe pseudo-duck typing mechanism, that would normally be done with a standard type family. Done with MultiParamTypeClasses and FunctionalDependencies:
class HasLength a b | a -> b where
getLength :: a -> b
instance HasLength [a] Int where
getLength = length
instance HasLength (Set a) Int where
getLength = S.size
instance HasLength Event DateDiff where
getLength = dateDiff (start event) (end event)
Bijective relation between types, such as for an unboxed container, which could be done through TypeFamilies with a data family, although then you have to declare a new data type for every contained type, such as with a newtype. Either that or with an injective type family, which I think is not available prior to GHC 8. Done with MultiParamTypeClasses and FunctionalDependencies:
class Unboxed a b | a -> b, b -> a where
toList :: a -> [b]
fromList :: [b] -> a
instance Unboxed FooVector Foo where
toList = fooVector2List
fromList = list2FooVector
instance Unboxed BarVector Bar where
toList = barVector2List
fromList = list2BarVector
And lastly a surjective relations between two types and a third type, such as python2 or java style division function, which can be done with TypeFamilies by also using MultiParamTypeClasses. Done with MultiParamTypeClasses and FunctionalDependencies:
class Divide a b c | a b -> c where
divide :: a -> b -> c
instance Divide Int Int Int where
divide = div
instance Divide Int Double Double where
divide = (/) . fromIntegral
instance Divide Double Int Double where
divide = (. fromIntegral) . (/)
instance Divide Double Double Double where
divide = (/)
One other thing I should also add is that it seems like FunctionalDependencies and MultiParamTypeClasses are also quite a bit more concise (for the examples above anyway) as you only have to write the type once, and you don't have to come up with a dummy type name which you then have to type for every instance like you do with TypeFamilies:
instance FooBar LongTypeName LongerTypeName where
FooBarResult LongTypeName LongerTypeName = LongestTypeName
fooBar = someFunction
vs:
instance FooBar LongTypeName LongerTypeName LongestTypeName where
fooBar = someFunction
So unless I am convinced otherwise it really seems like I should just not bother with TypeFamilies and use solely FunctionalDependencies and MultiParamTypeClasses. Because as far as I can tell it will make my code more concise, more consistent (one less extension to care about), and will also give me more flexibility such as with open type relationships or bijective relations (potentially the latter is solver by GHC 8).
Here's an example of where TypeFamilies really shines compared to MultiParamClasses with FunctionalDependencies. In fact, I challenge you to come up with an equivalent MultiParamClasses solution, even one that uses FlexibleInstances, OverlappingInstance, etc.
Consider the problem of type level substitution (I ran across a specific variant of this in Quipper in QData.hs). Essentially what you want to do is recursively substitute one type for another. For example, I want to be able to
substitute Int for Bool in Either [Int] String and get Either [Bool] String,
substitute [Int] for Bool in Either [Int] String and get Either Bool String,
substitute [Int] for [Bool] in Either [Int] String and get Either [Bool] String.
All in all, I want the usual notion of type level substitution. With a closed type family, I can do this for any types (albeit I need an extra line for each higher-kinded type constructor - I stopped at * -> * -> * -> * -> *).
{-# LANGUAGE TypeFamilies #-}
-- Subsitute type `x` for type `y` in type `a`
type family Substitute x y a where
Substitute x y x = y
Substitute x y (k a b c d) = k (Substitute x y a) (Substitute x y b) (Substitute x y c) (Substitute x y d)
Substitute x y (k a b c) = k (Substitute x y a) (Substitute x y b) (Substitute x y c)
Substitute x y (k a b) = k (Substitute x y a) (Substitute x y b)
Substitute x y (k a) = k (Substitute x y a)
Substitute x y a = a
And trying at ghci I get the desired output:
> :t undefined :: Substitute Int Bool (Either [Int] String)
undefined :: Either [Bool] [Char]
> :t undefined :: Substitute [Int] Bool (Either [Int] String)
undefined :: Either Bool [Char]
> :t undefined :: Substitute [Int] [Bool] (Either [Int] String)
undefined :: Either [Bool] [Char]
With that said, maybe you should be asking yourself why am I using MultiParamClasses and not TypeFamilies. Of the examples you gave above, all except Convert translate to type families (albeit you will need an extra line per instance for the type declaration).
Then again, for Convert, I am not convinced it is a good idea to define such a thing. The natural extension to Convert would be instances such as
instance (Convert a b, Convert b c) => Convert a c where
convert = convert . convert
instance Convert a a where
convert = id
which are as unresolvable for GHC as they are elegant to write...
To be clear, I am not saying there are no uses of MultiParamClasses, just that when possible you should be using TypeFamilies - they let you think about type-level functions instead of just relations.
This old HaskellWiki page does an OK job of comparing the two.
EDIT
Some more contrasting and history I stumbled upon from augustss blog
Type families grew out of the need to have type classes with
associated types. The latter is not strictly necessary since it can be
emulated with multi-parameter type classes, but it gives a much nicer
notation in many cases. The same is true for type families; they can
also be emulated by multi-parameter type classes. But MPTC gives a
very logic programming style of doing type computation; whereas type
families (which are just type functions that can pattern match on the
arguments) is like functional programming.
Using closed type families
adds some extra strength that cannot be achieved by type classes. To
get the same power from type classes we would need to add closed type
classes. Which would be quite useful; this is what instance chains
gives you.
Functional dependencies only affect the process of constraint solving, while type families introduced the notion of non-syntactic type equality, represented in GHC's intermediate form by coercions. This means type families interact better with GADTs. See this question for the canonical example of how functional dependencies fail here.

Couldn't match expected type in Haskell code that print nested list?

Here is my function
data Item a = One a | Many [Item a]
let flat (One x) = show x
let flat (Many xs) = show xs
Here is the output
Prelude> flat [[3]]
<interactive>:21:6:
Couldn't match expected type ‘Item t0’ with actual type ‘[[t1]]’
In the first argument of ‘flat’, namely ‘[[3]]’
In the expression: flat [[3]]
In an equation for ‘it’: it = flat [[3]]
It seems like flat doesn't recognize Item as its function signature so I tried redefine the function signature
flat :: Item a -> [a]
<interactive>:22:1:
Couldn't match type ‘a1’ with ‘Char’
‘a1’ is a rigid type variable bound by
an expression type signature: Item a1 -> [a1] at <interactive>:22:1
Expected type: Item a1 -> [a1]
Actual type: Item a1 -> String
In the expression: flat :: Item a -> [a]
In an equation for ‘it’: it = flat :: Item a -> [a]
But Haskell does not let you redefine function signature in ghci, is there a way around this?
flat [[3]] yields a type error. [[3]] has type Num a => [[a]], not Show a => Item a that you can pass into flat.
flat (Many [3]) will return "[3]".
Answering a follow-up question you asked in the comments of #jtobin's answer: yes there is a way to automatically dectect that [3] needs to be wrapped into a Maybe constructor. However you'll probably need to add type annotations (cf. example to help Haskell figure out what to do=.
We start with a bunch of language extensions.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
Then comes your definition of Item.
module Item where
data Item a = One a | Many [Item a]
We introduce a class of things which may be reified to an Item a and declare two instances: the Many one and the base case. You can see that we now have overlapping instances (e.g. for Itemable [Int] [Int]) so you're playing with fire here.
class Itemable b a where
item :: b -> Item a
instance Itemable b a => Itemable [b] a where
item = Many . fmap item
instance Itemable a a where
item = One
You can finally define flat as a function that turns a b into an Item a first and then flattens it:
flat :: Itemable b a => b -> [a]
flat = go . item where
go (One a) = [a]
go (Many as) = concatMap go as
Which works as the following example typechecking and evaluating to [2,43,7,8,1] shows:
example :: [Int]
example = flat [[[[[[2::Int],[43]],[[7],[8]],[[1]]]]]]
However, as soon as you try to use the overlapping instances it'll blow in your face. E.g.:
example' :: [[Int]]
example' = flat [[[[[[2::Int],[43]],[[7],[8]],[[1]]]]]]

How to tell whether variable is a certain data in Haskell?

Edit: This class instance of QWhere fails when it's passed input like this: >qWhere fly john even though fly is type Argument -> Argument -> Predicate and john is type Argument.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
data Argument = Argument { ttype :: Type, value :: String } deriving (Show, Eq)
data Predicate = Predicate { lemma :: String, arguments :: [Argument] } deriving (Show, Eq)
class Fly a b where
fly :: a -> b -> Predicate
instance Fly Argument Argument where
fly x y = Predicate { lemma = "fly", arguments = [x, y] }
instance Fly Argument Predicate where
fly x y = Predicate { lemma = "fly", arguments = [x, arguments y !! 0] }
class QWhere a b where
qWhere :: a -> b -> String
instance QWhere (Argument -> Argument -> Predicate) Argument where
qWhere x y = "hi"
This is the output from the ghci:
No instance for (QWhere (a0 -> b0 -> Predicate) Argument)
arising from a use of ‘qWhere’
The type variables ‘a0’, ‘b0’ are ambiguous
Note: there is a potential instance available:
instance QWhere (Argument -> Argument -> Predicate) Argument
-- Defined at new_context.hs:116:10
In the expression: qWhere fly john
In an equation for ‘it’: it = qWhere fly john
No instance for (Fly a0 b0) arising from a use of ‘fly’
The type variables ‘a0’, ‘b0’ are ambiguous
Note: there are several potential instances:
instance Fly Argument Predicate
-- Defined at new_context.hs:110:10
instance Fly Argument Argument
-- Defined at new_context.hs:107:10
In the first argument of ‘qWhere’, namely ‘fly’
In the expression: qWhere fly john
In an equation for ‘it’: it = qWhere fly john
These questions are relevant, but none of the answers have solved my problem.
(1) Checking for a particular data constructor
(2) Test if Haskell variable matches user-defined data type option
And some internet sources which should address this question but I could not find the solution from:
(3) https://www.haskell.org/haskellwiki/Determining_the_type_of_an_expression
(4) http://okmij.org/ftp/Haskell/typeEQ.html
My problem: I have two Haskell data types defined. I am given an input and I need to determine if it belongs to data type A or data type B.
Here is the data types definition:
data Argument = Argument { ttype :: Type, value :: String } deriving (Show, Eq)
data Predicate = Predicate { lemma :: String, arguments :: [Argument] } deriving (Show, Eq)
I need a function which returns true/false if a variable is a data type Argument or Predicate.
I attempted to follow the answers of both SO questions, but only got complaints from the ghci compiler:
--checks if a variable is of data type Argument
--this does not compile (from question (2))
isArgument :: a -> Bool
isArgument (Argument _) = True
isArgument _ = False
--from question (1), also fails
isArgument :: a -> String
isArgument value =
case token of
Argument arg -> "is argument"
Predicate p -> "is predicate"
The sort of dynamic typing you are trying to do is very rarely used in Haskell. If you want to write functions that can take values of both Predicate and Argument there are at least two idiomatic ways depending on your exact use-case.
The first is to overload the function using type-classes. E.g.
class IsArgument a where
isArgument :: a -> Bool
instance IsArgument Argument where
isArgument _ = True
instance IsArgument Predicate where
isArgument _ = False
The second is to use some sum-type such as Either Predicate Argument or a custom sum-type such as:
data Expr = ArgumentExpr Argument | PredicateExpr Predicate
isArgument :: Expr -> Bool
isArgument (ArgumentExpr _) = True
isArgument _ = False
You can also make Argument and Predicate constructors of the same type, but then of course you lose the type safety of treating them as separate types. You can circumvent this by using a GADT and tagging the constructors with a phantom type but this gets into the slightly more advanced type extensions that GHC offers:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
data ExprType = Argument | Predicate
data Expr t where
ArgumentExpr :: { ttype :: Type, value :: String } -> Expr Argument
PredicateExpr :: { lemma :: String, arguments :: [Expr Argument] } -> Expr Predicate
deriving instance Show (Expr t)
deriving instance Eq (Expr t)
isArgument :: Expr t -> Bool
isArgument (ArgumentExpr {}) = True
isArgument _ = False
Now arguments and predicates are constructors of the same type but you can limit the values to a specific constructor by using the type parameter as is done in arguments :: [Expr Argument] but you can also just accept any expression using the type Expr t as in isArgument.
If you really really need run-time polymorphism, it can be achieved using the Typeable type-class which enables you to get runtime type information and do type-casts on opaque, generic types.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data Argument = Argument { ttype :: Type, value :: String } deriving (Show, Eq, Typeable)
data Predicate = Predicate { lemma :: String, arguments :: [Argument] } deriving (Show, Eq, Typeable)
isArgument :: Typeable a => a -> Bool
isArgument a = case cast a of
Just (Argument {}) -> True
_ -> False
The function cast tries to convert any Typeable a => a value into some known type and returns a Just value if the type-cast succeeds and Nothing if it fails.
You can do what you want by making Argument and Predicate part of the same type....
data LogicElement = Argument { ttype :: Type, value :: String } |
Predicate { lemma :: String, arguments :: [LogicElement] } deriving (Show, Eq)
While it is possible to define a function of type (a->Bool), it is unusual, and generally implies that the value being input will be ignored (ie- how can you do anything to something if you don't even know what it is? You pretty much can only apply other (a->b) functions on it).
In the particular example, you compiler will complain at the following
isArgument (Argument _) = True
because the pattern implicitly implies that the input argument must be type Argument, whereas the signature you gave was undefined type a.
When you say that isArgument has type a -> Bool, you're saying that it can take any, or rather every possible a, not just certain ones. There are a few solutions to this, though. My preference would be that for simple alternatives, just use Either:
import Data.Either
isArgument :: Either Argument Predicate -> Bool
isArgument = isLeft
Or
-- Note the use of {} instead of _, the {} expands to all fields in a record
-- the _ only would have taken the place of the ttype field, although you could have
-- (Argument _ _) to capture both fields of the Argument constructor
isArgument :: Either Argument Predicate -> Bool
isArgument (Left (Argument {})) = True
isArgument _ = False
Although, the only use of this sort of function would be when you aren't sure which data type you have, and a value in Haskell can't be ambiguously typed. It would be equivalent to if you had in Java/C/C++/C# something like
if (some_condition) {
x = "a string";
} else {
x = 5;
}
These are statically typed languages, a variable can't take on values of two different types. The same holds in Haskell. If you wanted to give a type to a variable that could take on two different values, you'd have to write a container for it. The Either container in Haskell is pre-defined for this purpose.

Haskell get type of algebraic parameter

I have a type
class IntegerAsType a where
value :: a -> Integer
data T5
instance IntegerAsType T5 where value _ = 5
newtype (IntegerAsType q) => Zq q = Zq Integer deriving (Eq)
newtype (Num a, IntegerAsType n) => PolyRing a n = PolyRing [a]
I'm trying to make a nice "show" for the PolyRing type. In particular, I want the "show" to print out the type 'a'. Is there a function that returns the type of an algebraic parameter (a 'show' for types)?
The other way I'm trying to do it is using pattern matching, but I'm running into problems with built-in types and the algebraic type.
I want a different result for each of Integer, Int and Zq q.
(toy example:)
test :: (Num a, IntegerAsType q) => a -> a
(Int x) = x+1
(Integer x) = x+2
(Zq x) = x+3
There are at least two different problems here.
1) Int and Integer are not data constructors for the 'Int' and 'Integer' types. Are there data constructors for these types/how do I pattern match with them?
2) Although not shown in my code, Zq IS an instance of Num. The problem I'm getting is:
Ambiguous constraint `IntegerAsType q'
At least one of the forall'd type variables mentioned by the constraint
must be reachable from the type after the '=>'
In the type signature for `test':
test :: (Num a, IntegerAsType q) => a -> a
I kind of see why it is complaining, but I don't know how to get around that.
Thanks
EDIT:
A better example of what I'm trying to do with the test function:
test :: (Num a) => a -> a
test (Integer x) = x+2
test (Int x) = x+1
test (Zq x) = x
Even if we ignore the fact that I can't construct Integers and Ints this way (still want to know how!) this 'test' doesn't compile because:
Could not deduce (a ~ Zq t0) from the context (Num a)
My next try at this function was with the type signature:
test :: (Num a, IntegerAsType q) => a -> a
which leads to the new error
Ambiguous constraint `IntegerAsType q'
At least one of the forall'd type variables mentioned by the constraint
must be reachable from the type after the '=>'
I hope that makes my question a little clearer....
I'm not sure what you're driving at with that test function, but you can do something like this if you like:
{-# LANGUAGE ScopedTypeVariables #-}
class NamedType a where
name :: a -> String
instance NamedType Int where
name _ = "Int"
instance NamedType Integer where
name _ = "Integer"
instance NamedType q => NamedType (Zq q) where
name _ = "Zq (" ++ name (undefined :: q) ++ ")"
I would not be doing my Stack Overflow duty if I did not follow up this answer with a warning: what you are asking for is very, very strange. You are probably doing something in a very unidiomatic way, and will be fighting the language the whole way. I strongly recommend that your next question be a much broader design question, so that we can help guide you to a more idiomatic solution.
Edit
There is another half to your question, namely, how to write a test function that "pattern matches" on the input to check whether it's an Int, an Integer, a Zq type, etc. You provide this suggestive code snippet:
test :: (Num a) => a -> a
test (Integer x) = x+2
test (Int x) = x+1
test (Zq x) = x
There are a couple of things to clear up here.
Haskell has three levels of objects: the value level, the type level, and the kind level. Some examples of things at the value level include "Hello, world!", 42, the function \a -> a, or fix (\xs -> 0:1:zipWith (+) xs (tail xs)). Some examples of things at the type level include Bool, Int, Maybe, Maybe Int, and Monad m => m (). Some examples of things at the kind level include * and (* -> *) -> *.
The levels are in order; value level objects are classified by type level objects, and type level objects are classified by kind level objects. We write the classification relationship using ::, so for example, 32 :: Int or "Hello, world!" :: [Char]. (The kind level isn't too interesting for this discussion, but * classifies types, and arrow kinds classify type constructors. For example, Int :: * and [Int] :: *, but [] :: * -> *.)
Now, one of the most basic properties of Haskell is that each level is completely isolated. You will never see a string like "Hello, world!" in a type; similarly, value-level objects don't pass around or operate on types. Moreover, there are separate namespaces for values and types. Take the example of Maybe:
data Maybe a = Nothing | Just a
This declaration creates a new name Maybe :: * -> * at the type level, and two new names Nothing :: Maybe a and Just :: a -> Maybe a at the value level. One common pattern is to use the same name for a type constructor and for its value constructor, if there's only one; for example, you might see
newtype Wrapped a = Wrapped a
which declares a new name Wrapped :: * -> * at the type level, and simultaneously declares a distinct name Wrapped :: a -> Wrapped a at the value level. Some particularly common (and confusing examples) include (), which is both a value-level object (of type ()) and a type-level object (of kind *), and [], which is both a value-level object (of type [a]) and a type-level object (of kind * -> *). Note that the fact that the value-level and type-level objects happen to be spelled the same in your source is just a coincidence! If you wanted to confuse your readers, you could perfectly well write
newtype Huey a = Louie a
newtype Louie a = Dewey a
newtype Dewey a = Huey a
where none of these three declarations are related to each other at all!
Now, we can finally tackle what goes wrong with test above: Integer and Int are not value constructors, so they can't be used in patterns. Remember -- the value level and type level are isolated, so you can't put type names in value definitions! By now, you might wish you had written test' instead:
test' :: Num a => a -> a
test' (x :: Integer) = x + 2
test' (x :: Int) = x + 1
test' (Zq x :: Zq a) = x
...but alas, it doesn't quite work like that. Value-level things aren't allowed to depend on type-level things. What you can do is to write separate functions at each of the Int, Integer, and Zq a types:
testInteger :: Integer -> Integer
testInteger x = x + 2
testInt :: Int -> Int
testInt x = x + 1
testZq :: Num a => Zq a -> Zq a
testZq (Zq x) = Zq x
Then we can call the appropriate one of these functions when we want to do a test. Since we're in a statically-typed language, exactly one of these functions is going to be applicable to any particular variable.
Now, it's a bit onerous to remember to call the right function, so Haskell offers a slight convenience: you can let the compiler choose one of these functions for you at compile time. This mechanism is the big idea behind classes. It looks like this:
class Testable a where test :: a -> a
instance Testable Integer where test = testInteger
instance Testable Int where test = testInt
instance Num a => Testable (Zq a) where test = testZq
Now, it looks like there's a single function called test which can handle any of Int, Integer, or numeric Zq's -- but in fact there are three functions, and the compiler is transparently choosing one for you. And that's an important insight. The type of test:
test :: Testable a => a -> a
...looks at first blush like it is a function that takes a value that could be any Testable type. But in fact, it's a function that can be specialized to any Testable type -- and then only takes values of that type! This difference explains yet another reason the original test function didn't work. You can't have multiple patterns with variables at different types, because the function only ever works on a single type at a time.
The ideas behind the classes NamedType and Testable above can be generalized a bit; if you do, you get the Typeable class suggested by hammar above.
I think now I've rambled more than enough, and likely confused more things than I've clarified, but leave me a comment saying which parts were unclear, and I'll do my best.
Is there a function that returns the type of an algebraic parameter (a 'show' for types)?
I think Data.Typeable may be what you're looking for.
Prelude> :m + Data.Typeable
Prelude Data.Typeable> typeOf (1 :: Int)
Int
Prelude Data.Typeable> typeOf (1 :: Integer)
Integer
Note that this will not work on any type, just those which have a Typeable instance.
Using the extension DeriveDataTypeable, you can have the compiler automatically derive these for your own types:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data Foo = Bar
deriving Typeable
*Main> typeOf Bar
Main.Foo
I didn't quite get what you're trying to do in the second half of your question, but hopefully this should be of some help.

Resources