Why can't I use record selectors with an existentially quantified type? - haskell

When using Existential types, we have to use a pattern-matching syntax for extracting the foralled value. We can't use the ordinary record selectors as functions. GHC reports an error and suggest using pattern-matching with this definition of yALL:
{-# LANGUAGE ExistentialQuantification #-}
data ALL = forall a. Show a => ALL { theA :: a }
-- data ok
xALL :: ALL -> String
xALL (ALL a) = show a
-- pattern matching ok
-- ABOVE: heaven
-- BELOW: hell
yALL :: ALL -> String
yALL all = show $ theA all
-- record selector failed
forall.hs:11:19:
Cannot use record selector `theA' as a function due to escaped type variables
Probable fix: use pattern-matching syntax instead
In the second argument of `($)', namely `theA all'
In the expression: show $ theA all
In an equation for `yALL': yALL all = show $ theA all
Some of my data take more than 5 elements. It's hard to maintain the code if I
use pattern-matching:
func1 (BigData _ _ _ _ elemx _ _) = func2 elemx
Is there a good method to make code like that maintainable or to wrap it up so that I can use some kind of selectors?

Existential types work in a more elaborate manner than regular types. GHC is (rightly) forbidding you from using theA as a function. But imagine there was no such prohibition. What type would that function have? It would have to be something like this:
-- Not a real type signature!
theA :: ALL -> t -- for a fresh type t on each use of theA; t is an instance of Show
To put it very crudely, forall makes GHC "forget" the type of the constructor's arguments; all that the type system knows is that this type is an instance of Show. So when you try to extract the value of the constructor's argument, there is no way to recover the original type.
What GHC does, behind the scenes, is what the comment to the fake type signature above says—each time you pattern match against the ALL constructor, the variable bound to the constructor's value is assigned a unique type that's guaranteed to be different from every other type. Take for example this code:
case ALL "foo" of
ALL x -> show x
The variable x gets a unique type that is distinct from every other type in the program and cannot be matched with any type variable. These unique types are not allowed to escape to the top level—which is the reason why theA cannot be used as a function.

You can use record syntax in pattern matching,
func1 BigData{ someField = elemx } = func2 elemx
works and is much less typing for huge types.

Related

Can we tweak "a -> a" function in Haskell?

In Haskell id function is defined on type level as id :: a -> a and implemented as just returning its argument without any modification, but if we have some type introspection with TypeApplications we can try to modify values without breaking type signature:
{-# LANGUAGE AllowAmbiguousTypes, ScopedTypeVariables, TypeApplications #-}
module Main where
class TypeOf a where
typeOf :: String
instance TypeOf Bool where
typeOf = "Bool"
instance TypeOf Char where
typeOf = "Char"
instance TypeOf Int where
typeOf = "Int"
tweakId :: forall a. TypeOf a => a -> a
tweakId x
| typeOf #a == "Bool" = not x
| typeOf #a == "Int" = x+1
| typeOf #a == "Char" = x
| otherwise = x
This fail with error:
"Couldn't match expected type ‘a’ with actual type ‘Bool’"
But I don't see any problems here (type signature satisfied):
My question is:
How can we do such a thing in a Haskell?
If we can't, that is theoretical\philosophical etc reasons for this?
If this implementation of tweak_id is not "original id", what are theoretical roots that id function must not to do any modifications on term level. Or can we have many implementations of id :: a -> a function (I see that in practice we can, I can implement such a function in Python for example, but what the theory behind Haskell says to this?)
You need GADTs for that.
{-# LANGUAGE ScopedTypeVariables, TypeApplications, GADTs #-}
import Data.Typeable
import Data.Type.Equality
tweakId :: forall a. Typeable a => a -> a
tweakId x
| Just Refl <- eqT #a #Int = x + 1
-- etc. etc.
| otherwise = x
Here we use eqT #type1 #type2 to check whether the two types are equal. If they are, the result is Just Refl and pattern matching on that Refl is enough to convince the type checker that the two types are indeed equal, so we can use x + 1 since x is now no longer only of type a but also of type Int.
This check requires runtime type information, which we usually do not have due to Haskell's type erasure property. The information is provided by the Typeable type class.
This can also be achieved using a user-defined class like your TypeOf if we make it provide a custom GADT value. This can work well if we want to encode some constraint like "type a is either an Int, a Bool, or a String" where we statically know what types to allow (we can even recursively define a set of allowed types in this way). However, to allow any type, including ones that have not yet been defined, we need something like Typeable. That is also very convenient since any user-defined type is automatically made an instance of Typeable.
This fail with error: "Couldn't match expected type ‘a’ with actual type ‘Bool’"But I don't see any problems here
Well, what if I add this instance:
instance TypeOf Float where
typeOf = "Bool"
Do you see the problem now? Nothing prevents somebody from adding such an instance, no matter how silly it is. And so the compiler can't possibly make the assumption that having checked typeOf #a == "Bool" is sufficient to actually use x as being of type Bool.
You can squelch the error if you are confident that nobody will add malicious instances, by using unsafe coercions.
import Unsafe.Coerce
tweakId :: forall a. TypeOf a => a -> a
tweakId x
| typeOf #a == "Bool" = unsafeCoerce (not $ unsafeCoerce x)
| typeOf #a == "Int" = unsafeCoerce (unsafeCoerce x+1 :: Int)
| typeOf #a == "Char" = unsafeCoerce (unsafeCoerce x :: Char)
| otherwise = x
but I would not recommend this. The correct way is to not use strings as a poor man's type representation, but instead the standard Typeable class which is actually tamper-proof and comes with suitable GADTs so you don't need manual unsafe coercions. See chi's answer.
As an alternative, you could also use type-level strings and a functional dependency to make the unsafe coercions safe:
{-# LANGUAGE DataKinds, FunctionalDependencies
, ScopedTypeVariables, UnicodeSyntax, TypeApplications #-}
import GHC.TypeLits (KnownSymbol, symbolVal)
import Data.Proxy (Proxy(..))
import Unsafe.Coerce
class KnownSymbol t => TypeOf a t | a->t, t->a
instance TypeOf Bool "Bool"
instance TypeOf Int "Int"
tweakId :: ∀ a t . TypeOf a t => a -> a
tweakId x = case symbolVal #t Proxy of
"Bool" -> unsafeCoerce (not $ unsafeCoerce x)
"Int" -> unsafeCoerce (unsafeCoerce x + 1 :: Int)
_ -> x
The trick is that the fundep t->a makes writing another instance like
instance TypeOf Float "Bool"
a compile error right there.
Of course, really the most sensible approach is probably to not bother with any kind of manual type equality at all, but simply use the class right away for the behaviour changes you need:
class Tweakable a where
tweak :: a -> a
instance Tweakable Bool where
tweak = not
instance Tweakable Int where
tweak = (+1)
instance Tweakable Char where
tweak = id
The other answers are both very good for covering the ways you can do something like this in Haskell. But I thought it was worth adding something speaking more to this part of the question:
If we can't, that is theoretical\philosophical etc reasons for this?
Actually Haskellers do generally rely quite strongly on the theory that forbids something like your tweakId from existing with type forall a. a -> a. (Even though there are ways to cheat, using things like unsafeCoerce; this is usually considered bad style if you haven't done something like in leftaroundabout's answer, where a class with functional dependencies ensures the unsafe coerce is always valid)
Haskell uses parametric polymorphism1. That means we can write code that works on multiple types because it will treat them all the same; the code only uses operations that will work regardless of the specific type it is invoked on. This is expressed in Haskell types by using type variables; a function with a variable in its type can be used with any type at all substituted for the variable, because every single operation in the function definition will work regardless of what type is chosen.
About the simplest example is indeed the function id, which might be defined like this:
id :: forall a. a -> a
id x = x
Because it's parametrically polymorphic, we can simply choose any type at all we like and use id as if it was defined on that type. For example as if it were any of the following:
id :: Bool -> Bool
id x = x
id :: Int -> Int
id x = x
id :: Maybe (Int -> [IO Bool]) -> Maybe (Int -> [IO Bool])
id x = x
But to ensure that the definition does work for any type, the compiler has to check a very strong restriction. Our id function can only use operations that don't depend on any property of any specific type at all. We can't call not x because the x might not be a Bool, we can't call x + 1 because the x might not be a number, can't check whether x is equal to anything because it might not be a type that supports equality, etc, etc. In fact there is almost nothing you can do with x in the body of id. We can't even ignore x and return some other value of type a; this would require us to write an expression for a value that can be of any type at all and the only things that can do that are things like undefined that don't evaluate to a value at all (because they throw exceptions). It's often said that in fact there is only one valid function with type forall a. a -> a (and that is id)2.
This restriction on what you can do with values whose type contains variables isn't just a restriction for the sake of being picky, it's actually a huge part of what makes Haskell types useful. It means that just looking at the type of a function can often tell you quite a bit about what it can possibly do, and once you get used to it Haskellers rely on this kind of thinking all the time. For example, consider this function signature:
map :: forall a b. (a -> b) -> [a] -> [b]
Just from this type (and the assumption that the code doesn't do anything dumb like add in extra undefined elements of the list) I can tell:
All of the items in the resulting list come are results of the function input; map will have no other way of producing values of type b to put in the list (except undefined, etc).
All of the items in the resulting list correspond to something in the input list mapped through the function; map will have no way of getting any a values to feed to the function (except undefined, etc)
If any items of the input list are dropped or re-ordered, it will be done in a "blind" way that isn't considering the elements at all, only their position in the list; map ultimately has no way of testing any property of the a and b values to decide which order they should go in. For example it might leave out the third element, or swap the 2nd and 76th elements if there are at least 100 elements, etc. But if it applies rules like that it will have to always apply them, regardless of the actual items in the list. It cannot e.g. drop the 4th element if it is less than the 5th element, or only keep outputs from the function that are "truthy", etc.
None of this would be true if Haskell allowed parametrically polymorphic types to have Python-like definitions that check the type of their arguments and then run different code. Such a definition for map could check if the function is supposed to return integers and if so return [1, 2, 3, 4] regardless of the input list, etc. So the type checker would be enforcing a lot less (and thus catching fewer mistakes) if it worked this way.
This kind of reasoning is formalised in the concept of free theorems; it's literally possible to derive formal proofs about a piece of code from its type (and thus get theorems for free). You can google this if you're interested in further reading, but Haskellers generally use this concept informally rather doing real proofs.
Sometimes we do need non-parametric polymorphism. The main tool Haskell provides for that is type classes. If a type variable has a class constraint, then there will be an interface of class methods provided by that constraint. For example the Eq a constraint allows (==) :: a -> a -> Bool to be used, and your own TypeOf a constraint allows typeOf #a to be used. Type class methods do allow you to run different code for different types, so this breaks parametricity. Even just adding Eq a to the type of map means I can no longer assume property 3 from above.
map :: forall a b. Eq a => (a -> b) -> [a] -> [b]
Now map can tell whether some of the items in the original list are equal to each other, so it can use that to decide whether to include them in the result, and in what order. Likewise Monoid a or Monoid b would allow map to break the first two properties by using mempty :: a to produce new values that weren't in the list originally or didn't come from the function. If I add Typeable constraints I can't assume anything, because the function could do all of the Python-style checking of types to apply special-case logic, make use of existing values it knows about if a or b happen to be those types, etc.
So something like your tweakId cannot be given the type forall a. a -> a, for theoretical reasons that are also extremely practically important. But if you need a function that behaves like your tweakId adding a class constraint was the right thing to do to break out of the constraints of parametricity. However simply being able to get a String for each type isn't enough; typeOf #a == "Int" doesn't tell the type checker that a can be used in operations requiring an Int. It knows that in that branch the equality check returned True, but that's just a Bool; the type checker isn't able to reason backwards to why this particular Bool is True and deduce that it could only have happened if a were the type Int. But there are alternative constructs using GADTs that do give the type checker additional knowledge within certain code branches, allowing you to check types at runtime and use different code for each type. The class Typeable is specifically designed for this, but it's a hammer that completely bypasses parametricity; I think most Haskellers would prefer to keep more type-based reasoning intact where possible.
1 Parametric polymorphism is in contrast to class-based polymorphism you may have seen in OO languages (where each class says how a method is implemented for objects of that specific class), or ad-hoc polymophism (as seen in C++) where you simply define multiple definitions with the same name but different types and the types at each application determine which definition is used. I'm not covering those in detail, but the key distinction is both of them allow the definition to have different code for each supported type, rather than guaranteeing the same code will process all supported types.
2 It's not 100% true that there's only one valid function with type forall a. a -> a unless you hide some caveats in "valid". But if you don't use any unsafe features (like unsafeCoerce or the foreign language interface), then a function with type forall a. a -> a will either always throw an exception or it will return its argument unchanged.
The "always throws an exception" isn't terribly useful so we usually assume an unknown function with that type isn't going to do that, and thus ignore this possibility.
There are multiple ways to implement "returns its argument unchanged", like id x = head . head . head $ [[[x]]], but they can only differ from the normal id in being slower by building up some structure around x and then immediately tearing it down again. A caller that's only worrying about correctness (rather than performance) can treat them all the same.
Thus, ignoring the "always undefined" possibility and treating all of the dumb elaborations of id x = x the same, we come to the perspective where we can say "there's only one function with forall a. a -> a".

What does a stand for in a data type declaration?

Normally when using type declarations we do:
function_name :: Type -> Type
However in an exercise I am trying to solve there is the following structure:
function_name :: Type a -> Type a
or explicitly as in the exercise
alphabet :: DFA a -> Alphabet a
alphabet = undefined
What does a stand for?
Short answer: it's a type variable.
At the computation level, the way we define functions is to use variables to refer to their arguments. Like this:
f x = x + 3
Here x is a variable, and its value will be chosen when the function is called. Haskell has a similar (but not identical...) mechanism in its type sublanguage. For example, you can write things like:
type F x = (x, Int, x)
type Endo a = a -> a -> a
Here again x is a variable in the first one (and a in the second), and its value will be chosen at use sites. One can also use this mechanism when defining new types. (The previous two examples just give new names to existing types, but the following does more.) One of the most basic nontrivial examples of this is the Maybe family of types:
data Maybe a = Nothing | Just a
The things on the right of the = are computation-level, so you can mostly ignore them for now, but on the left we are declaring a new family of types Maybe which accepts other types as an argument. For example, Maybe Int, Maybe (Bool, String), Maybe (Endo Char), and even passing in expressions that have variables like Maybe (x, Int, x) are all possible.
Syntactically, type constructors (things which are defined as part of the program text and that we expect the compiler to look up the definition for) start with an upper case letter and type variables (things which will be instantiated later and so don't currently have a concrete definition) start with lower case letters.
So, in the type signature you showed:
alphabet :: DFA a -> Alphabet a
I suspect there are actually two constructs new to you, not just one: first, the type variable a that you asked about, and second, the concept of type application, where we apply at the type level one "function-like" type to another. (Outside of this answer, people say "parameterized" instead of "function-like".)
...and, believe it or not, there is even a type system for types that makes sure you don't write things like these:
Int a -- Int is not parameterized, so shouldn't be applied to arguments
Int Char -- ditto
Maybe -> String -- Maybe is parameterized, so should be applied to
-- arguments, but isn't

Result type of a polyvariadic function in haskell

While studying polyvariadic functions in Haskell I stumbled across the following SO questions:
How to create a polyvariadic haskell function?
Haskell, polyvariadic function and type inference
and thought I will give it a try by implementing a function which takes a variable number of strings and concatenates/merges them into a single string:
{-# LANGUAGE FlexibleInstances #-}
class MergeStrings r where
merge :: String -> r
instance MergeStrings String where
merge = id
instance (MergeStrings r) => MergeStrings (String -> r) where
merge acc = merge . (acc ++)
This works so far if I call merge with at least one string argument and if I provide the final type.
foo :: String
foo = merge "a" "b" "c"
Omitting the final type results in an error, i.e., compiling the following
bar = merge "a" "b" "c"
results in
test.hs:12:7: error:
• Ambiguous type variable ‘t0’ arising from a use of ‘merge’
prevents the constraint ‘(MergeStrings t0)’ from being solved.
Relevant bindings include bar :: t0 (bound at test.hs:12:1)
Probable fix: use a type annotation to specify what ‘t0’ should be.
These potential instances exist:
instance MergeStrings r => MergeStrings (String -> r)
-- Defined at test.hs:6:10
instance MergeStrings String -- Defined at test.hs:4:10
• In the expression: merge "a" "b" "c"
In an equation for ‘bar’: bar = merge "a" "b" "c"
|
12 | bar = merge "a" "b" "c"
|
The error message makes perfect sense since I could easily come up with, for example
bar :: String -> String
bar = merge "a" "b" "c"
baz = bar "d"
rendering bar not into a single string but into a function which takes and returns one string.
Is there a way to tell Haskell that the result type must be of type String? For example, Text.Printf.printf "hello world" evaluates to type String without explicitly defining.
printf works without type annotation because of type defaulting in GHCi. The same mechanism that allows you to eval show $ 1 + 2 without specifying concrete types.
GHCi tries to evaluate expressions of type IO a, so you just need to add appropriate instance for MergeStrings:
instance (a ~ ()) => MergeStrings (IO a) where
merge = putStrLn
Brad (in a comment) and Max are not wrong saying that the defaulting of printf "…" … to IO ( ) is the reason for it working in ghci without type annotations. But it is not the end of the story. There are things we can do to make your definition of bar work.
First, I should mention the «monomorphism restriction» — an obscure and unintuitive type inference rule we have in Haskell. For whatever reason, the designers of Haskell decided that a top level definition without a type signature should have no polymorphic variables in its inferred type — that is, be monomorphic. bar is polymorphic, so you can see that it would be affected.
Some type classes (particularly numbers) have defaulting rules that allow you to say x = 13 without a type signature and have it inferred that x :: Integer — or whatever other type you set as default. Type defaulting is only available for a few blessed classes, so you cannot have it for your own class, and without a designated default GHC cannot decide what particular monomorphic type to choose.
But you can do other things, beside defaulting, to make the type checker happy — either:
Disable the monomorphism restriction.
Assign an explicit polymorphic type signature: bar :: MergeStrings r => r
Now bar is polymorphic and works as you would expect. See:
λ putStrLn bar
abc
λ putStrLn (bar "x")
abcx
λ putStrLn (bar "x" "y")
abcxy
You can also use defaulting to make expressions such as show bar work. Since Show is among the classes that you can default when extended default rules are enabled, you can issue default (String) in the module where you want to use show bar and it will work as you would expect.

Why can't I use the type `Show a => [Something -> a]`?

I have a record type say
data Rec {
recNumber :: Int
, recName :: String
-- more fields of various types
}
And I want to write a toString function for Rec :
recToString :: Rec -> String
recToString r = intercalate "\t" $ map ($ r) fields
where fields = [show . recNumber, show . recName]
This works. fields has type [Rec -> String]. But I'm lazy and I would prefer writing
recToString r = intercalate "\t" $ map (\f -> show $ f r) fields
where fields = [recNumber, recName]
But this doesn't work. Intuitively I would say fields has type Show a => [Rec -> a] and this should be ok. But Haskell doesn't allow it.
I'd like to understand what is going on here. Would I be right if I said that in the first case I get a list of functions such that the 2 instances of show are actually not the same function, but Haskell is able to determine which is which at compile time (which is why it's ok).
[show . recNumber, show . recName]
^-- This is show in instance Show Number
^-- This is show in instance Show String
Whereas in the second case, I only have one literal use of show in the code, and that would have to refer to multiple instances, not determined at compile time ?
map (\f -> show $ f r) fields
^-- Must be both instances at the same time
Can someone help me understand this ? And also are there workarounds or type system expansions that allow this ?
The type signature doesn't say what you think it says.
This seems to be a common misunderstanding. Consider the function
foo :: Show a => Rec -> a
People frequently seem to think this means that "foo can return any type that it wants to, so long as that type supports Show". It doesn't.
What it actually means is that foo must be able to return any possible type, because the caller gets to choose what the return type should be.
A few moments' thought will reveal that foo actually cannot exist. There is no way to turn a Rec into any possible type that can ever exist. It can't be done.
People often try to do something like Show a => [a] to mean "a list of mixed types but they all have Show". That obviously doesn't work; this type actually means that the list elements can be any type, but they still have to be all the same.
What you're trying to do seems reasonable enough. Unfortunately, I think your first example is about as close as you can get. You could try using tuples and lenses to get around this. You could try using Template Haskell instead. But unless you've got a hell of a lot of fields, it's probably not even worth the effort.
The type you actually want is not:
Show a => [Rec -> a]
Any type declaration with unbound type variables has an implicit forall. The above is equivalent to:
forall a. Show a => [Rec -> a]
This isn't what you wan't, because the a must be specialized to a single type for the entire list. (By the caller, to any one type they choose, as MathematicalOrchid points out.) Because you want the a of each element in the list to be able to be instantiated differently... what you are actually seeking is an existential type.
[exists a. Show a => Rec -> a]
You are wishing for a form of subtyping that Haskell does not support very well. The above syntax is not supported at all by GHC. You can use newtypes to sort of accomplish this:
{-# LANGUAGE ExistentialQuantification #-}
newtype Showy = forall a. Show a => Showy a
fields :: [Rec -> Showy]
fields = [Showy . recNumber, Showy . recName]
But unfortunatley, that is just as tedious as converting directly to strings, isn't it?
I don't believe that lens is capable of getting around this particular weakness of the Haskell type system:
recToString :: Rec -> String
recToString r = intercalate "\t" $ toListOf (each . to fieldShown) fields
where fields = (recNumber, recName)
fieldShown f = show (f r)
-- error: Couldn't match type Int with [Char]
Suppose the fields do have the same type:
fields = [recNumber, recNumber]
Then it works, and Haskell figures out which show function instance to use at compile time; it doesn't have to look it up dynamically.
If you manually write out show each time, as in your original example, then Haskell can determine the correct instance for each call to show at compile time.
As for existentials... it depends on implementation, but presumably, the compiler cannot determine which instance to use statically, so a dynamic lookup will be used instead.
I'd like to suggest something very simple instead:
recToString r = intercalate "\t" [s recNumber, s recName]
where s f = show (f r)
All the elements of a list in Haskell must have the same type, so a list containing one Int and one String simply cannot exist. It is possible to get around this in GHC using existential types, but you probably shouldn't (this use of existentials is widely considered an anti-pattern, and it doesn't tend to perform terribly well). Another option would be to switch from a list to a tuple, and use some weird stuff from the lens package to map over both parts. It might even work.

Type Signature of functions with Lists in haskell

I am just beginning to learn Haskell and am following the book "Learnyouahaskell".I have come across this example
tell :: (Show a) => [a] -> String
tell [] = "The list is empty"
I understand that (Show a) here is a class constraint and the type of parameter , in this case a has to be able to be "showable" .
Considering that a here is a list and not an element of the list , why am i unable to declare the function like :-
tell :: (Show a) =>a->String
Edit 1:-from the answers below i seem to understand that one would need to specify the concrete type of a for pattern matching. Considering this,what would be a correct implementation of the below:-
pm :: (Show a) =>a->String
pm 'g'="wow"
It gives me the error as below
Could not deduce (a ~ Char)
from the context (Show a)
bound by the type signature for pm :: Show a => a -> String
at facto.hs:31:7-26
`a' is a rigid type variable bound by
the type signature for pm :: Show a => a -> String at facto.hs:31:7
In the pattern: 'g'
In an equation for `pm': pm 'g' = "wow"
Failed, modules loaded: none.
I understand from the error message that it s not able to deduce the concrete type of a , but then how can it be declared using Show.
I know I can solve the above like this:-
pmn :: Char->String
pmn 'g'="wow"
But I am just trying to understand the Show typeclass properly
List does implement Show type class but when you say: Show a => a -> String It means the function will accept any type which implements Show AND most importantly you can only call show class functions on a nothing else, your function will never know the concrete type of a. Whereas you are trying to call list pattern matching on a
Update for new edit in question:
The correct implementation would be: pm c ="wow". You can call any Show type class functions on parameter c. You cannot pattern match as you were trying before because you dont know the exact type of parameter, you only know that it implements Show type class. But when you specific Char as the type then the pattern matching works
In both signatures, a isn't a list -- it's any type at all, and you don't get to pick which (except that it must be an instance of Show).
In
tell₁ :: Show a => [a] -> String
tell₁ [] = "The list is empty"
... -- (remember to match the non-empty list case too!)
You're matching on the list of as, not on a value of type a itself.
If you wrote
tell₂ :: Show a => a -> String
tell₂ [] = "The list is empty"
...
You would be assuming that the type a is the type of lists (of something). But it could be any type at all, such as Bool.
(But it's possible that I don't understand your question -- you haven't really said what the problem is. When asking a question like this you should generally specify what you did, what you expected, and what happened. None of these is really specified here, so people can only guess at what you might've meant.)
The problem isn't with Show. Indeed if we try:
tell2 :: a -> String
tell2 [] = "The list is empty"
We get a type check error. Lets see what it says:
test.hs:5:7:
Couldn't match expected type `a' with actual type `[t0]'
`a' is a rigid type variable bound by
the type signature for tell2 :: a -> String at test.hs:4:10
In the pattern: []
In an equation for `tell2': tell2 [] = "The list is empty"
Now we ask ourselves, what is this does this so-called 'type' construct really mean? When you write tell2 :: a -> String, you are saying is that for any type that is exactly a, tell2 will give us a String. [a] (or [c] or [foo] - the name doesn't matter) is not exactly a. This may seem like an arbitrary distinction, and as far as I know, it is. Let's see what happens when we write
tell2 [] = "The list is empty"
> :t tell2
> tell2 :: [t] -> [Char]
As you well know there is no difference between writing t and a, and [Char] is just a type synonym for String, so the type we wrote and the type GHC infers are identical.
Well, not quite. When you, yourself, the programmer, specify the type of a function manually in your source, the type variables in your type signature become rigid. What does that mean exactly?
from https://research.microsoft.com/en-us/um/people/simonpj/papers/gadt/:
"Instead of "user-specified type", we use the briefer term rigid
type to describe a type that is completely specified, in some
direct fashion, by a programmer-supplied type annotation."
So a rigid type is any type specified by a programmer type signature.
All other types are "wobbly"[1]
So, just by virtue of the fact that you wrote it out, the type signature has become different. And in this new type grammar, we have that a /= [b]. For rigid type signatures, GHC will infer the very least amount of information it can. It must infer that a ~ [b] from the pattern binding; however it cannot make this inference from the type signature you have provided.
Lets look at the error GHC gives for the original function:
test.hs:2:6:
Could not deduce (a ~ [t0])
from the context (Show a)
bound by the type signature for tell :: Show a => a -> String
at test.hs:1:9-29
`a' is a rigid type variable bound by
We see again rigid type variable etc., but in this case GHC also claims it could not deduce something. (By the way - a ~ b === a == b in the type grammar). The type checker is actually looking for a constraint in the type that would make the function valid; it doesn't find it and is nice enough to tell you exactly what it would need to make it valid:
{-# LANGUAGE GADTs #-}
tell :: (a ~ [t0], Show a) => a -> String
tell [] = "The list is empty"
If we insert GHC's suggestion verbatim, it type checks, since now GHC doesn't need to make any inferences; we have told it exactly what a is.
As soon as you pattern match on 'g', eg
pm 'g' = "wow"
your function no longer has a type of (Show a) => a -> String; instead it has has a concrete type for 'a', namely Char, so it becomes Char -> String
This is in direct conflict with the explicit type signature you gave it, which states your function works with any type 'a' (as long as that type is an instance of Show).
You can't pattern match in this case, since you are pattern matching on an Int, Char, etc. But you can use the show function in the Prelude:
pm x = case show x of
"'g'" -> "My favourite Char"
"1" -> "My favourite Int"
_ -> show x
As you may have guessed, show is a bit magical ;). There's actually a whole bunch of show functions implemented for each type that is an instance of the Show typeclass.
tell :: (Show a) =>a->String
This says tell accepts a value of any type a that is showable. You can call it on anything showable. Which implies that inside the implementation of tell, you have to be able to operate on anything at all (that is showable).
You might think that this would be an okay implementation for that type signature:
tell [] = "The list is empty"
Because lists are indeed showable, and so are valid values for the first parameter. But there I'm checking whether the argument is an empty list; only values of the list type can be matched against list patterns (such as the empty list pattern), so this doesn't make sense if I'd called tell 1 or tell True or tell (1, 'c'), etc.
Inside tell, that type a could be any type that is an instance of Show. So the only things I can do with that value are things that are valid to do with all types that are instances of Show. Which basically means you can only pass it to other similar functions with a generic Show a => a parameter.1
Your confusion is stemming from this misconception "Considering that a here is a list and not an element of the list" about the type signature tell :: (Show a) => [a] -> String. Here a is in fact an element of the list, not the list itself.
That type signature reads "tell takes a single paramter, which is a list of some showable type, and returns a string". This version of tell knows it receives a list, so it can do listy things with its argument. It's the things inside the list which are members of some unknown type.
1 Most of those functions will also be unable to do anything with the value other than pass it on to another Show function, but sooner or later the value will either be ignored or passed to one of the actual functions in the Show typeclass; these have specialised implementations for each type so each specialised version gets to know what type it's operating on, which is the only way anything can eventually be done.

Resources