Strange behavior of type parameters in "type" versus "newtype": is this a bug or a feature? - haskell

I'm writing a typeclass to add type reflection to Haskell data types. Part of it looks like this:
type VarName a = Text
class Reflective a where
-- | A reflective type may have a fixed name, or it may be a union
-- where each variant has a distinct name.
reflectiveName :: a -> VarName a
-- | One default value of the type for each reflective name.
reflectiveDefaults :: [a]
The idea is that if I write
data ExampleType = Foo Int | Bar String
then in the Reflective instance reflectiveName will return either "Foo" or "Bar" as appropriate, and reflectiveDefaults will return [Foo 0, Bar ""]
So now I can write a function to give me all the names of the variants:
reflectiveNames :: (Reflective a) => [VarName a]
reflectiveNames = map reflectiveName reflectiveDefaults
and I can call it like this:
exampleNames = reflectiveNames :: [VarName ExampleType]
When I compile this I get the following error in the type declaration for reflectiveNames:
• Could not deduce (Reflective a0)
from the context: Reflective a
bound by the type signature for:
reflectiveNames :: Reflective a => [VarName a]
The type variable ‘a0’ is ambiguous
However if I replace the VarName with a newtype:
newtype VarName a = VarName Text
then it works.
Is this a feature of the Haskell type system, or is it a bug in GHC? And if the former, why is it inventing a new type variable a0?

Why this fails for a type...
If you write type then you do not construct a new type, you construct an alias. So you defined:
type VarName a = Text
Hence now each time you write VarName SomeType, you have basically written Text. So VarName Char ~ VarName Int ~ Text (the tilde ~ means that the two types are equal).
Type aliases are useful however since they typically minimize the code (frequently the name of the alias is shorter than its counterpart), it reduces the complexity of signatures (one does not have to remember a large hierarchy of types), and finally it can be used if some types are not yet fully decided (for example time can be modelled as an Int32, Int64, etc.) and we want to define some placeholder to easily change a large number of signatures.
But the point is that each time you write a VarName Char for example, Haskell will replace this with Text. So now if we take a look at your function, you have written:
reflectiveNames :: Reflective a => [Text]
reflectiveNames = map reflectiveName reflectiveDefaults
Now there is a problem with this function: there is a type variable a (in Reflective a), but nowhere in the signature do we use this type parameter. The problem is that Haskell does not know what a to fill in in case you call this function, and that is a real problem (here), since the semantics of reflectiveName and reflectiveDefaults can be completely different for an a ~ Char, then for an a ~ Int. The compiler can not just "pick" a type for a, since that would mean that two different Haskell compilers, could end up with functions that generate different output, and thus a different program (usually one of the fundamental desired aspects of a programming language is unambiguity, the fact that there are no two semantically different programs that map on the same source code).
... and why it works for a newtype
Now why doesn't this happen if we use newtype? Basically a newtype is the same as a data declaration, except for some small details: behind the curtains for example, Haskell will not produce such constructor, it will simply store the value that is wrapped inside the constructor but it will see the value as a different type. The newtype definition
newtype VarName a = VarName Text
is thus (conceptually) almost equivalent to:
data VarName a = VarName Text
Although Haskell will (given it is a compiler that can deal with such optimization) factor the constructor away, we can conceptually assume that it is there.
But the main difference is that we did not define a type signature: we defined a new type, so the function signature stays:
reflectiveNames :: Reflective a => [VarName a]
reflectiveNames = map reflectiveName reflectiveDefaults
and we can not just write Text instead of VarName a, since a Text is not a VarName a. It also means that Haskell can perfectly derive what a is. If we would for instance trigger reflectiveNames :: [VarName Char], then it know that a is a Char, and it will thus use the instance of Reflective for a ~ Char. There is no ambiguity. Of course we can define aliasses like:
type Foo = VarName Char -- a ~ Char
type Bar b = VarName Int -- a ~ Int
But then still a is resolved to Char and Int respectively. Since this is a new type, we will always carry the type of a through the code, and hence the code is unambiguous.

Related

Clarification of Terms around Haskell Type system

Type system in haskell seem to be very Important and I wanted to clarify some terms revolving around haskell type system.
Some type classes
Functor
Applicative
Monad
After using :info I found that Functor is a type class, Applicative is a type class with => (deriving?) Functor and Monad deriving Applicative type class.
I've read that Maybe is a Monad, does that mean Maybe is also Applicative and Functor?
-> operator
When i define a type
data Maybe = Just a | Nothing
and check :t Just I get Just :: a -> Maybe a. How to read this -> operator?
It confuses me with the function where a -> b means it evaluates a to b (sort of returns a maybe) – I tend to think lhs to rhs association but it turns when defining types?
The term type is used in ambiguous ways, Type, Type Class, Type Constructor, Concrete Type etc... I would like to know what they mean to be exact
Indeed the word “type” is used in somewhat ambiguous ways.
The perhaps most practical way to look at it is that a type is just a set of values. For example, Bool is the finite set containing the values True and False.Mathematically, there are subtle differences between the concepts of set and type, but they aren't really important for a programmer to worry about. But you should in general consider the sets to be infinite, for example Integer contains arbitrarily big numbers.
The most obvious way to define a type is with a data declaration, which in the simplest case just lists all the values:
data Colour = Red | Green | Blue
There we have a type which, as a set, contains three values.
Concrete type is basically what we say to make it clear that we mean the above: a particular type that corresponds to a set of values. Bool is a concrete type, that can easily be understood as a data definition, but also String, Maybe Integer and Double -> IO String are concrete types, though they don't correspond to any single data declaration.
What a concrete type can't have is type variables†, nor can it be an incompletely applied type constructor. For example, Maybe is not a concrete type.
So what is a type constructor? It's the type-level analogue to value constructors. What we mean mathematically by “constructor” in Haskell is an injective function, i.e. a function f where if you're given f(x) you can clearly identify what was x. Furthermore, any different constructors are assumed to have disjoint ranges, which means you can also identify f.‡
Just is an example of a value constructor, but it complicates the discussion that it also has a type parameter. Let's consider a simplified version:
data MaybeInt = JustI Int | NothingI
Now we have
JustI :: Int -> MaybeInt
That's how JustI is a function. Like any function of the same signature, it can be applied to argument values of the right type, like, you can write JustI 5.What it means for this function to be injective is that I can define a variable, say,
quoxy :: MaybeInt
quoxy = JustI 9328
and then I can pattern match with the JustI constructor:
> case quoxy of { JustI n -> print n }
9328
This would not be possible with a general function of the same signature:
foo :: Int -> MaybeInt
foo i = JustI $ negate i
> case quoxy of { foo n -> print n }
<interactive>:5:17: error: Parse error in pattern: foo
Note that constructors can be nullary, in which case the injective property is meaningless because there is no contained data / arguments of the injective function. Nothing and True are examples of nullary constructors.
Type constructors are the same idea as value constructors: type-level functions that can be pattern-matched. Any type-name defined with data is a type constructor, for example Bool, Colour and Maybe are all type constructors. Bool and Colour are nullary, but Maybe is a unary type constructor: it takes a type argument and only the result is then a concrete type.
So unlike value-level functions, type-level functions are kind of by default type constructors. There are also type-level functions that aren't constructors, but they require -XTypeFamilies.
A type class may be understood as a set of types, in the same vein as a type can be seen as a set of values. This is not quite accurate, it's closer to true to say a class is a set of type constructors but again it's not as useful to ponder the mathematical details – better to look at examples.
There are two main differences between type-as-set-of-values and class-as-set-of-types:
How you define the “elements”: when writing a data declaration, you need to immediately describe what values are allowed. By contrast, a class is defined “empty”, and then the instances are defined later on, possibly in a different module.
How the elements are used. A data type basically enumerates all the values so they can be identified again. Classes meanwhile aren't generally concerned with identifying types, rather they specify properties that the element-types fulfill. These properties come in the form of methods of a class. For example, the instances of the Num class are types that have the property that you can add elements together.
You could say, Haskell is statically typed on the value level (fixed sets of values in each type), but duck-typed on the type level (classes just require that somebody somewhere implements the necessary methods).
A simplified version of the Num example:
class Num a where
(+) :: a -> a -> a
instance Num Int where
0 + x = x
x + y = ...
If the + operator weren't already defined in the prelude, you would now be able to use it with Int numbers. Then later on, perhaps in a different module, you could also make it usable with new, custom number types:
data MyNumberType = BinDigits [Bool]
instance Num MyNumberType where
BinDigits [] + BinDigits l = BinDigits l
BinDigits (False:ds) + BinDigits (False:es)
= BinDigits (False : ...)
Unlike Num, the Functor...Monad type classes are not classes of types, but of 1-ary type constructors. I.e. every functor is a type constructor taking one argument to make it a concrete type. For instance, recall that Maybe is a 1-ary type constructor.
class Functor f where
fmap :: (a->b) -> f a -> f b
instance Functor Maybe where
fmap f (Just a) = Just (f a)
fmap _ Nothing = Nothing
As you have concluded yourself, Applicative is a subclass of Functor. D being a subclass of C means basically that D is a subset of the set of type constructors in C. Therefore, yes, if Maybe is an instance of Monad it also is an instance of Functor.
†That's not quite true: if you consider the _universal quantor_ explicitly as part of the type, then a concrete type can contain variables. This is a bit of an advanced subject though.
‡This is not guaranteed to be true if the -XPatternSynonyms extension is used.

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.

Clarification on Existential Types in Haskell

I am trying to understand Existential types in Haskell and came across a PDF http://www.ii.uni.wroc.pl/~dabi/courses/ZPF15/rlasocha/prezentacja.pdf
Please correct my below understandings that I have till now.
Existential Types not seem to be interested in the type they contain but pattern matching them say that there exists some type we don't know what type it is until & unless we use Typeable or Data.
We use them when we want to Hide types (ex: for Heterogeneous Lists) or we don't really know what the types at Compile Time.
GADT's provide the clear & better syntax to code using Existential Types by providing implicit forall's
My Doubts
In Page 20 of above PDF it is mentioned for below code that it is impossible for a Function to demand specific Buffer. Why is it so? When I am drafting a Function I exactly know what kind of buffer I gonna use eventhough I may not know what data I gonna put into that.
What's wrong in Having :: Worker MemoryBuffer Int If they really want to abstract over Buffer they can have a Sum type data Buffer = MemoryBuffer | NetBuffer | RandomBuffer and have a type like :: Worker Buffer Int
data Worker x = forall b. Buffer b => Worker {buffer :: b, input :: x}
data MemoryBuffer = MemoryBuffer
memoryWorker = Worker MemoryBuffer (1 :: Int)
memoryWorker :: Worker Int
As Haskell is a Full Type Erasure language like C then How does it know at Runtime which function to call. Is it something like we gonna maintain few information and pass in a Huge V-Table of Functions and at runtime it gonna figure out from V-Table? If it is so then what sort of Information it gonna store?
GADT's provide the clear & better syntax to code using Existential Types by providing implicit forall's
I think there's general agreement that the GADT syntax is better. I wouldn't say that it's because GADTs provide implicit foralls, but rather because the original syntax, enabled with the ExistentialQuantification extension, is potentially confusing/misleading. That syntax, of course, looks like:
data SomeType = forall a. SomeType a
or with a constraint:
data SomeShowableType = forall a. Show a => SomeShowableType a
and I think the consensus is that the use of the keyword forall here allows the type to be easily confused with the completely different type:
data AnyType = AnyType (forall a. a) -- need RankNTypes extension
A better syntax might have used a separate exists keyword, so you'd write:
data SomeType = SomeType (exists a. a) -- not valid GHC syntax
The GADT syntax, whether used with implicit or explicit forall, is more uniform across these types, and seems to be easier to understand. Even with an explicit forall, the following definition gets across the idea that you can take a value of any type a and put it inside a monomorphic SomeType':
data SomeType' where
SomeType' :: forall a. (a -> SomeType') -- parentheses optional
and it's easy to see and understand the difference between that type and:
data AnyType' where
AnyType' :: (forall a. a) -> AnyType'
Existential Types not seem to be interested in the type they contain but pattern matching them say that there exists some type we don't know what type it is until & unless we use Typeable or Data.
We use them when we want to Hide types (ex: for Heterogeneous Lists) or we don't really know what the types at Compile Time.
I guess these aren't too far off, though you don't have to use Typeable or Data to use existential types. I think it would be more accurate to say an existential type provides a well-typed "box" around an unspecified type. The box does "hide" the type in a sense, which allows you to make a heterogeneous list of such boxes, ignoring the types they contain. It turns out that an unconstrained existential, like SomeType' above is pretty useless, but a constrained type:
data SomeShowableType' where
SomeShowableType' :: forall a. (Show a) => a -> SomeShowableType'
allows you to pattern match to peek inside the "box" and make the type class facilities available:
showIt :: SomeShowableType' -> String
showIt (SomeShowableType' x) = show x
Note that this works for any type class, not just Typeable or Data.
With regard to your confusion about page 20 of the slide deck, the author is saying that it's impossible for a function that takes an existential Worker to demand a Worker having a particular Buffer instance. You can write a function to create a Worker using a particular type of Buffer, like MemoryBuffer:
class Buffer b where
output :: String -> b -> IO ()
data Worker x = forall b. Buffer b => Worker {buffer :: b, input :: x}
data MemoryBuffer = MemoryBuffer
instance Buffer MemoryBuffer
memoryWorker = Worker MemoryBuffer (1 :: Int)
memoryWorker :: Worker Int
but if you write a function that takes a Worker as argument, it can only use the general Buffer type class facilities (e.g., the function output):
doWork :: Worker Int -> IO ()
doWork (Worker b x) = output (show x) b
It can't try to demand that b be a particular type of buffer, even via pattern matching:
doWorkBroken :: Worker Int -> IO ()
doWorkBroken (Worker b x) = case b of
MemoryBuffer -> error "try this" -- type error
_ -> error "try that"
Finally, runtime information about existential types is made available through implicit "dictionary" arguments for the typeclasses that are involved. The Worker type above, in addtion to having fields for the buffer and input, also has an invisible implicit field that points to the Buffer dictionary (somewhat like v-table, though it's hardly huge, as it just contains a pointer to the appropriate output function).
Internally, the type class Buffer is represented as a data type with function fields, and instances are "dictionaries" of this type:
data Buffer' b = Buffer' { output' :: String -> b -> IO () }
dBuffer_MemoryBuffer :: Buffer' MemoryBuffer
dBuffer_MemoryBuffer = Buffer' { output' = undefined }
The existential type has a hidden field for this dictionary:
data Worker' x = forall b. Worker' { dBuffer :: Buffer' b, buffer' :: b, input' :: x }
and a function like doWork that operates on existential Worker' values is implemented as:
doWork' :: Worker' Int -> IO ()
doWork' (Worker' dBuf b x) = output' dBuf (show x) b
For a type class with only one function, the dictionary is actually optimized to a newtype, so in this example, the existential Worker type includes a hidden field that consists of a function pointer to the output function for the buffer, and that's the only runtime information needed by doWork.
In Page 20 of above PDF it is mentioned for below code that it is impossible for a Function to demand specific Buffer. Why is it so?
Because Worker, as defined, takes only one argument, the type of the "input" field (type variable x). E.g. Worker Int is a type. The type variable b, instead, is not a parameter of Worker, but is a sort of "local variable", so to speak. It can not be passed as in Worker Int String -- that would trigger a type error.
If we instead defined:
data Worker x b = Worker {buffer :: b, input :: x}
then Worker Int String would work, but the type is no longer existential -- we now always have to pass the buffer type as well.
As Haskell is a Full Type Erasure language like C then How does it know at Runtime which function to call. Is it something like we gonna maintain few information and pass in a Huge V-Table of Functions and at runtime it gonna figure out from V-Table? If it is so then what sort of Information it gonna store?
This is roughly correct. Briefly put, each time you apply constructor Worker, GHC infers the b type from the arguments of Worker, and then searches for an instance Buffer b. If that is found, GHC includes an additional pointer to the instance in the object. In its simplest form, this is not too different from the "pointer to vtable" which is added to each object in OOP when virtual functions are present.
In the general case, it can be much more complex, though. The compiler might use a different representation and add more pointers instead of a single one (say, directly adding the pointers to all the instance methods), if that speeds up code. Also, sometimes the compiler needs to use multiple instances to satisfy a constraint. E.g., if we need to store the instance for Eq [Int] ... then there is not one but two: one for Int and one for lists, and the two needs to be combined (at run time, barring optimizations).
It is hard to guess exactly what GHC does in each case: that depends on a ton of optimizations which might or might not trigger.
You could try googling for the "dictionary based" implementation of type classes to see more about what's going on. You can also ask GHC to print the internal optimized Core with -ddump-simpl and observe the dictionaries being constructed, stored, and passed around. I have to warn you: Core is rather low level, and can be hard to read at first.

How does the :: operator syntax work in the context of bounded typeclass?

I'm learning Haskell and trying to understand the reasoning behind it's syntax design at the same time. Most of the syntax is beautiful.
But since :: normally is like a type annotation, How is it that this works:
Input: minBound::Int
Output: -2147483648
There is no separate operator: :: is a type annotation in that example. Perhaps the best way to understand this is to consider this code:
main = print (f minBound)
f :: Int -> Int
f = id
This also prints -2147483648. The use of minBound is inferred to be an Int because it is the parameter to f. Once the type has been inferred, the value for that type is known.
Now, back to:
main = print (minBound :: Int)
This works in the same way, except that minBound is known to be an Int because of the type annotation, rather than for some more complex reason. The :: isn't some binary operation; it just directs the compiler that the expression minBound has the type Int. Once again, since the type is known, the value can be determined from the type class.
:: still means "has type" in that example.
There are two ways you can use :: to write down type information. Type declarations, and inline type annotations. Presumably you've been used to seeing type declarations, as in:
plusOne :: Integer -> Integer
plusOne = (+1)
Here the plusOne :: Integer -> Integer line is a separate declaration about the identifier plusOne, informing the compiler what its type should be. It is then actually defined on the following line in another declaration.
The other way you can use :: is that you can embed type information in the middle of any expression. Any expression can be followed by :: and then a type, and it means the same thing as the expression on its own except with the additional constraint that it must have the given type. For example:
foo = ('a', 2) :: (Char, Integer)
bar = ('a', 2 :: Integer)
Note that for foo I attached the entire expression, so it is very little different from having used a separate foo :: (Char, Integer) declaration. bar is more interesting, since I gave a type annotation for just the 2 but used that within a larger expression (for the whole pair). 2 :: Integer is still an expression for the value 2; :: is not an operator that takes 2 as input and computes some result. Indeed if the 2 were already used in a context that requires it to be an Integer then the :: Integer annotation changes nothing at all. But because 2 is normally polymorphic in Haskell (it could fit into a context requiring an Integer, or a Double, or a Complex Float) the type annotation pins down that the type of this particular expression is Integer.
The use is that it avoids you having to restructure your code to have a separate declaration for the expression you want to attach a type to. To do that with my simple example would have required something like this:
two :: Integer
two = 2
baz = ('a', two)
Which adds a relatively large amount of extra code just to have something to attach :: Integer to. It also means when you're reading bar, you have to go read a whole separate definition to know what the second element of the pair is, instead of it being clearly stated right there.
So now we can answer your direct question. :: has no special or particular meaning with the Bounded type class or with minBound in particular. However it's useful with minBound (and other type class methods) because the whole point of type classes is to have overloaded names that do different things depending on the type. So selecting the type you want is useful!
minBound :: Int is just an expression using the value of minBound under the constraint that this particular time minBound is used as an Int, and so the value is -2147483648. As opposed to minBound :: Char which is '\NUL', or minBound :: Bool which is False.
None of those options mean anything different from using minBound where there was already some context requiring it to be an Int, or Char, or Bool; it's just a very quick and simple way of adding that context if there isn't one already.
It's worth being clear that both forms of :: are not operators as such. There's nothing terribly wrong with informally using the word operator for it, but be aware that "operator" has a specific meaning in Haskell; it refers to symbolic function names like +, *, &&, etc. Operators are first-class citizens of Haskell: we can bind them to variables1 and pass them around. For example I can do:
(|+|) = (+)
x = 1 |+| 2
But you cannot do this with ::. It is "hard-wired" into the language, just as the = symbol used for introducing definitions is, or the module Main ( main ) where syntax for module headers. As such there are lots of things that are true about Haskell operators that are not true about ::, so you need to be careful not to confuse yourself or others when you use the word "operator" informally to include ::.
1 Actually an operator is just a particular kind of variable name that is applied by writing it between two arguments instead of before them. The same function can be bound to operator and ordinary variables, even at the same time.
Just to add another example, with Monads you can play a little like this:
import Control.Monad
anyMonad :: (Monad m) => Int -> m Int
anyMonad x = (pure x) >>= (\x -> pure (x*x)) >>= (\x -> pure (x+2))
$> anyMonad 4 :: [Int]
=> [18]
$> anyMonad 4 :: Either a Int
=> Right 18
$> anyMonad 4 :: Maybe Int
=> Just 18
it's a generic example telling you that the functionality may change with the type, another example:

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

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.

Resources