Why don't impredicative types allow for heterogenous lists? [duplicate] - haskell

A friend of mine posed a seemingly innocuous Scala language question last week that I didn't have a good answer to: whether there's an easy way to declare a collection of things belonging to some common typeclass. Of course there's no first-class notion of "typeclass" in Scala, so we have to think of this in terms of traits and context bounds (i.e. implicits).
Concretely, given some trait T[_] representing a typeclass, and types A, B and C, with corresponding implicits in scope T[A], T[B] and T[C], we want to declare something like a List[T[a] forAll { type a }], into which we can throw instances of A, B and C with impunity. This of course doesn't exist in Scala; a question last year discusses this in more depth.
The natural follow-up question is "how does Haskell do it?" Well, GHC in particular has a type system extension called impredicative polymorphism, described in the "Boxy Types" paper. In brief, given a typeclass T one can legally construct a list [forall a. T a => a]. Given a declaration of this form, the compiler does some dictionary-passing magic that lets us retain the typeclass instances corresponding to the types of each value in the list at runtime.
Thing is, "dictionary-passing magic" sounds a lot like "vtables." In an object-oriented language like Scala, subtyping is a much more simple, natural mechanism than the "Boxy Types" approach. If our A, B and C all extend trait T, then we can simply declare List[T] and be happy. Likewise, as Miles notes in a comment below, if they all extend traits T1, T2 and T3 then I can use List[T1 with T2 with T3] as an equivalent to the impredicative Haskell [forall a. (T1 a, T2 a, T3 a) => a].
However, the main, well-known disadvantage with subtyping compared to typeclasses is tight coupling: my A, B and C types have to have their T behavior baked in. Let's assume this is a major dealbreaker, and I can't use subtyping. So the middle ground in Scala is pimps^H^H^H^H^Himplicit conversions: given some A => T, B => T and C => T in implicit scope, I can again quite happily populate a List[T] with my A, B and C values...
... Until we want List[T1 with T2 with T3]. At that point, even if we have implicit conversions A => T1, A => T2 and A => T3, we can't put an A into the list. We could restructure our implicit conversions to literally provide A => T1 with T2 with T3, but I've never seen anybody do that before, and it seems like yet another form of tight coupling.
Okay, so my question finally is, I suppose, a combination of a couple questions that were previously asked here: "why avoid subtyping?" and "advantages of subtyping over typeclasses" ... is there some unifying theory that says impredicative polymorphism and subtype polymorphism are one and the same? Are implicit conversions somehow the secret love-child of the two? And can somebody articulate a good, clean pattern for expressing multiple bounds (as in the last example above) in Scala?

You're confusing impredicative types with existential types. Impredicative types allow you to put polymorphic values in a data structure, not arbitrary concrete ones. In other words [forall a. Num a => a] means that you have a list where each element works as any numeric type, so you can't put e.g. Int and Double in a list of type [forall a. Num a => a], but you can put something like 0 :: Num a => a in it. Impredicative types is not what you want here.
What you want is existential types, i.e. [exists a. Num a => a] (not real Haskell syntax), which says that each element is some unknown numeric type. To write this in Haskell, however, we need to introduce a wrapper data type:
data SomeNumber = forall a. Num a => SomeNumber a
Note the change from exists to forall. That's because we're describing the constructor. We can put any numeric type in, but then the type system "forgets" which type it was. Once we take it back out (by pattern matching), all we know is that it's some numeric type. What's happening under the hood, is that the SomeNumber type contains a hidden field which stores the type class dictionary (aka. vtable/implicit), which is why we need the wrapper type.
Now we can use the type [SomeNumber] for a list of arbitrary numbers, but we need to wrap each number on the way in, e.g. [SomeNumber (3.14 :: Double), SomeNumber (42 :: Int)]. The correct dictionary for each type is looked up and stored in the hidden field automatically at the point where we wrap each number.
The combination of existential types and type classes is in some ways similar to subtyping, since the main difference between type classes and interfaces is that with type classes the vtable travels separately from the objects, and existential types packages objects and vtables back together again.
However, unlike with traditional subtyping, you're not forced to pair them one to one, so we can write things like this which packages one vtable with two values of the same type.
data TwoNumbers = forall a. Num a => TwoNumbers a a
f :: TwoNumbers -> TwoNumbers
f (TwoNumbers x y) = TwoNumbers (x+y) (x*y)
list1 = map f [TwoNumbers (42 :: Int) 7, TwoNumbers (3.14 :: Double) 9]
-- ==> [TwoNumbers (49 :: Int) 294, TwoNumbers (12.14 :: Double) 28.26]
or even fancier things. Once we pattern match on the wrapper, we're back in the land of type classes. Although we don't know which type x and y are, we know that they're the same, and we have the correct dictionary available to perform numeric operations on them.
Everything above works similarly with multiple type classes. The compiler will simply generate hidden fields in the wrapper type for each vtable and bring them all into scope when we pattern match.
data SomeBoundedNumber = forall a. (Bounded a, Num a) => SBN a
g :: SomeBoundedNumber -> SomeBoundedNumber
g (SBN n) = SBN (maxBound - n)
list2 = map g [SBN (42 :: Int32), SBN (42 :: Int64)]
-- ==> [SBN (2147483605 :: Int32), SBN (9223372036854775765 :: Int64)]
As I'm very much a beginner when it comes to Scala, I'm not sure I can help with the final part of your question, but I hope this has at least cleared up some of the confusion and given you some ideas on how to proceed.

#hammar's answer is perfectly right. Here is the scala way of doint it. For the example i'll take Show as the type class and the values i and d to pack in a list :
// The type class
trait Show[A] {
def show(a : A) : String
}
// Syntactic sugar for Show
implicit final class ShowOps[A](val self : A)(implicit A : Show[A]) {
def show = A.show(self)
}
implicit val intShow = new Show[Int] {
def show(i : Int) = "Show of int " + i.toString
}
implicit val stringShow = new Show[String] {
def show(s : String) = "Show of String " + s
}
val i : Int = 5
val s : String = "abc"
What we want is to be able run the following code
val list = List(i, s)
for (e <- list) yield e.show
Building the list is easy but the list won't "remember" the exact type of each of its elements. Instead it will upcast each element to a common super type T. The more precise super super type between String and Int being Any, the type of the list is List[Any].
The problem is: what to forget and what to remember? We want to forget the exact type of the elements BUT we want to remember that they are all instances of Show. The following class does exactly that
abstract class Ex[TC[_]] {
type t
val value : t
implicit val instance : TC[t]
}
implicit def ex[TC[_], A](a : A)(implicit A : TC[A]) = new Ex[TC] {
type t = A
val value = a
val instance = A
}
This is an encoding of the existential :
val ex_i : Ex[Show] = ex[Show, Int](i)
val ex_s : Ex[Show] = ex[Show, String](s)
It pack a value with the corresponding type class instance.
Finally we can add an instance for Ex[Show]
implicit val exShow = new Show[Ex[Show]] {
def show(e : Ex[Show]) : String = {
import e._
e.value.show
}
}
The import e._ is required to bring the instance into scope. Thanks to the magic of implicits:
val list = List[Ex[Show]](i , s)
for (e <- list) yield e.show
which is very close to the expected code.

Related

Can I discharge a constraint, if I know the class is solvable for all types of a kind?

This might seem like a stupid question, but let's say I have a Haskell type class C (a :: K) defined for some fixed kind K, and I know I have instances C a for all types a :: K. Let's furthermore assume I have T :: K -> * and a value t :: C A => T A, is there any way to eliminate the constraint? I feel like this should be possible, but I can't come up with anything.
I'm mainly interested in the case where K is a data kind.
No.
The problem here is simple: foralls in Haskell are parametric polymorphism. This means that the same code must run no matter which type gets chosen. The thing I want to say next needs a way to pull out the C a => part of a type and talk about it in isolation, and there isn't really a way to do that in Haskell's syntax. But making up a type that's kinda like that is pretty standard:
data Dict c where Dict :: c => Dict c
Now the thing you are asking for, essentially, is:
magic :: forall a. Dict (C a)
Unfortunately, the code that you want this to represent -- the behaviors of the class methods -- is different for each type of the appropriate kind.
"Okay, okay," I hear you cry, "but when I write t :: C a => T a, isn't that running different code depending on the choice of a?". But no, it turns out, you aren't. There are two extant implementation schemes for typeclasses: dictionaries (alluded to above, and essentially the same as vtables if you're familiar with that from C++) and explicit type representations. In both cases, under the hood, <C> => <T> is actually a function -- taking the methods implementing the constraint <C> in the one case and a runtime representation of all the types mentioned in the constraint <C> in the other. And that function is the same function in all cases -- the dispatch to different code paths happens in the caller.
The type forall a. Dict (C a), on the other hand, has no such luxury: its type is not permitted to be a function under the hood, but must instead be a value of a specific data type.
Consider this module:
data K = A | B
class C (t::K) where
str :: String
instance C 'A where
str = "A"
instance C 'B where
str = "B"
type family F :: K
foo :: String
foo = str #F
Arguably, C t holds for all t::K, since we have the two instances. Then, however, we define a type family F::K which is, essentially, an unknown kind: it could be A, it could be B. Without a line such type instance F = ... defining F, it is impossible to define foo, since it could be "A" or "B".
Indeed, it is impossible to resolve this constraint.
Note that the type instance might even be defined in another module. Indeed, it is pretty common to define type families and type instances in distinct modules, like we do for type classes and their instances. It is impossible, however, to perform separate compilation when we have no information about the type instance.
The solution is, of course, deferring the constraint resolution by adding the constraint to foo:
foo :: C F => String
foo = str #F

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.

Practical applications of Rank 2 polymorphism?

I'm covering polymorphism and I'm trying to see the practical uses of such a feature.
My basic understanding of Rank 2 is:
type MyType = ∀ a. a -> a
subFunction :: a -> a
subFunction el = el
mainFunction :: MyType -> Int
mainFunction func = func 3
I understand that this is allowing the user to use a polymorphic function (subFunction) inside mainFunction and strictly specify it's output (Int). This seems very similar to GADT's:
data Example a where
ExampleInt :: Int -> Example Int
ExampleBool :: Bool -> Example Bool
1) Given the above, is my understanding of Rank 2 polymorphism correct?
2) What are the general situations where Rank 2 polymorphism can be used, as opposed to GADT's, for example?
If you pass a polymorphic function as and argument to a Rank2-polymorphic function, you're essentially passing not just one function but a whole family of functions – for all possible types that fulfill the constraints.
Typically, those forall quantifiers come with a class constraint. For example, I might wish to do number arithmetic with two different types simultaneously (for comparing precision or whatever).
data FloatCompare = FloatCompare {
singlePrecision :: Float
, doublePrecision :: Double
}
Now I might want to modify those numbers through some maths operation. Something like
modifyFloat :: (Num -> Num) -> FloatCompare -> FloatCompare
But Num is not a type, only a type class. I could of course pass a function that would modify any particular number type, but I couldn't use that to modify both a Float and a Double value, at least not without some ugly (and possibly lossy) converting back and forth.
Solution: Rank-2 polymorphism!
modifyFloat :: (∀ n . Num n => n -> n) -> FloatCompare -> FloatCompare
mofidyFloat f (FloatCompare single double)
= FloatCompare (f single) (f double)
The best single example of how this is useful in practice are probably lenses. A lens is a “smart accessor function” to a field in some larger data structure. It allows you to access fields, update them, gather results... while at the same time composing in a very simple way. How it works: Rank2-polymorphism; every lens is polymorphic, with the different instantiations corresponding to the “getter” / “setter” aspects, respectively.
The go-to example of an application of rank-2 types is runST as Benjamin Hodgson mentioned in the comments. This is a rather good example and there are a variety of examples using the same trick. For example, branding to maintain abstract data type invariants across multiple types, avoiding confusion of differentials in ad, a region-based version of ST.
But I'd actually like to talk about how Haskell programmers are implicitly using rank-2 types all the time. Every type class whose methods have universally quantified types desugars to a dictionary with a field with a rank-2 type. In practice, this is virtually always a higher-kinded type class* like Functor or Monad. I'll use a simplified version of Alternative as an example. The class declaration is:
class Alternative f where
empty :: f a
(<|>) :: f a -> f a -> f a
The dictionary representing this class would be:
data AlternativeDict f = AlternativeDict {
empty :: forall a. f a,
(<|>) :: forall a. f a -> f a -> f a }
Sometimes such an encoding is nice as it allows one to use different "instances" for the same type, perhaps only locally. For example, Maybe has two obvious instances of Alternative depending on whether Just a <|> Just b is Just a or Just b. Languages without type classes, such as Scala, do indeed use this encoding.
To connect to leftaroundabout's reference to lenses, you can view the hierarchy there as a hierarchy of type classes and the lens combinators as simply tools for explicitly building the relevant type class dictionaries. Of course, the reason it isn't actually a hierarchy of type classes is that we usually will have multiple "instances" for the same type. E.g. _head and _head . _tail are both "instances" of Traversal' s a.
* A higher-kinded type class doesn't necessarily lead to this, and it can happen for a type class of kind *. For example:
-- Higher-kinded but doesn't require universal quantification.
class Sum c where
sum :: c Int -> Int
-- Not higher-kinded but does require universal quantification.
class Length l where
length :: [a] -> l
If you are using modules in Haskell, you are already using Rank-2 types. Theoretically speaking, modules are records with rank-2 type properties.
For example, the Foo module below in Haskell ...
module Foo(id) where
id :: forall a. a -> a
id x = x
import qualified Foo
main = do
putStrLn (Foo.id "hello")
return ()
... can actually be thought as a record as follows:
type FooType = FooType {
id :: forall a. a -> a
}
Foo :: FooType
Foo = Foo {
id = \x -> x
}
P/S (unrelated this question): from a language design perspective, if you are going to support module system, then you might as well support higher-rank types (i.e. allow arbitrary quantification of type variables on any level) to reduce duplication of efforts (i.e. type checking a module should be almost the same as type checking a record with higher rank types).

What is the purpose of Rank2Types?

I am not really proficient in Haskell, so this might be a very easy question.
What language limitation do Rank2Types solve? Don't functions in Haskell already support polymorphic arguments?
It's hard to understand higher-rank polymorphism unless you study System F directly, because Haskell is designed to hide the details of that from you in the interest of simplicity.
But basically, the rough idea is that polymorphic types don't really have the a -> b form that they do in Haskell; in reality, they look like this, always with explicit quantifiers:
id :: ∀a.a → a
id = Λt.λx:t.x
If you don't know the "∀" symbol, it's read as "for all"; ∀x.dog(x) means "for all x, x is a dog." "Λ" is capital lambda, used for abstracting over type parameters; what the second line says is that id is a function that takes a type t, and then returns a function that's parametrized by that type.
You see, in System F, you can't just apply a function like that id to a value right away; first you need to apply the Λ-function to a type in order to get a λ-function that you apply to a value. So for example:
(Λt.λx:t.x) Int 5 = (λx:Int.x) 5
= 5
Standard Haskell (i.e., Haskell 98 and 2010) simplifies this for you by not having any of these type quantifiers, capital lambdas and type applications, but behind the scenes GHC puts them in when it analyzes the program for compilation. (This is all compile-time stuff, I believe, with no runtime overhead.)
But Haskell's automatic handling of this means that it assumes that "∀" never appears on the left-hand branch of a function ("→") type. Rank2Types and RankNTypes turn off those restrictions and allow you to override Haskell's default rules for where to insert forall.
Why would you want to do this? Because the full, unrestricted System F is hella powerful, and it can do a lot of cool stuff. For example, type hiding and modularity can be implemented using higher-rank types. Take for example a plain old function of the following rank-1 type (to set the scene):
f :: ∀r.∀a.((a → r) → a → r) → r
To use f, the caller first must choose what types to use for r and a, then supply an argument of the resulting type. So you could pick r = Int and a = String:
f Int String :: ((String → Int) → String → Int) → Int
But now compare that to the following higher-rank type:
f' :: ∀r.(∀a.(a → r) → a → r) → r
How does a function of this type work? Well, to use it, first you specify which type to use for r. Say we pick Int:
f' Int :: (∀a.(a → Int) → a → Int) → Int
But now the ∀a is inside the function arrow, so you can't pick what type to use for a; you must apply f' Int to a Λ-function of the appropriate type. This means that the implementation of f' gets to pick what type to use for a, not the caller of f'. Without higher-rank types, on the contrary, the caller always picks the types.
What is this useful for? Well, for many things actually, but one idea is that you can use this to model things like object-oriented programming, where "objects" bundle some hidden data together with some methods that work on the hidden data. So for example, an object with two methods—one that returns an Int and another that returns a String, could be implemented with this type:
myObject :: ∀r.(∀a.(a → Int, a -> String) → a → r) → r
How does this work? The object is implemented as a function that has some internal data of hidden type a. To actually use the object, its clients pass in a "callback" function that the object will call with the two methods. For example:
myObject String (Λa. λ(length, name):(a → Int, a → String). λobjData:a. name objData)
Here we are, basically, invoking the object's second method, the one whose type is a → String for an unknown a. Well, unknown to myObject's clients; but these clients do know, from the signature, that they will be able to apply either of the two functions to it, and get either an Int or a String.
For an actual Haskell example, below is the code that I wrote when I taught myself RankNTypes. This implements a type called ShowBox which bundles together a value of some hidden type together with its Show class instance. Note that in the example at the bottom, I make a list of ShowBox whose first element was made from a number, and the second from a string. Since the types are hidden by using the higher-rank types, this doesn't violate type checking.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ImpredicativeTypes #-}
type ShowBox = forall b. (forall a. Show a => a -> b) -> b
mkShowBox :: Show a => a -> ShowBox
mkShowBox x = \k -> k x
-- | This is the key function for using a 'ShowBox'. You pass in
-- a function #k# that will be applied to the contents of the
-- ShowBox. But you don't pick the type of #k#'s argument--the
-- ShowBox does. However, it's restricted to picking a type that
-- implements #Show#, so you know that whatever type it picks, you
-- can use the 'show' function.
runShowBox :: forall b. (forall a. Show a => a -> b) -> ShowBox -> b
-- Expanded type:
--
-- runShowBox
-- :: forall b. (forall a. Show a => a -> b)
-- -> (forall b. (forall a. Show a => a -> b) -> b)
-- -> b
--
runShowBox k box = box k
example :: [ShowBox]
-- example :: [ShowBox] expands to this:
--
-- example :: [forall b. (forall a. Show a => a -> b) -> b]
--
-- Without the annotation the compiler infers the following, which
-- breaks in the definition of 'result' below:
--
-- example :: forall b. [(forall a. Show a => a -> b) -> b]
--
example = [mkShowBox 5, mkShowBox "foo"]
result :: [String]
result = map (runShowBox show) example
PS: for anybody reading this who's wondered how come ExistentialTypes in GHC uses forall, I believe the reason is because it's using this sort of technique behind the scenes.
Do not functions in Haskell already support polymorphic arguments?
They do, but only of rank 1. This means that while you can write a function that takes different types of arguments without this extension, you can't write a function that uses its argument as different types in the same invocation.
For example the following function can't be typed without this extension because g is used with different argument types in the definition of f:
f g = g 1 + g "lala"
Note that it's perfectly possible to pass a polymorphic function as an argument to another function. So something like map id ["a","b","c"] is perfectly legal. But the function may only use it as monomorphic. In the example map uses id as if it had type String -> String. And of course you can also pass a simple monomorphic function of the given type instead of id. Without rank2types there is no way for a function to require that its argument must be a polymorphic function and thus also no way to use it as a polymorphic function.
Luis Casillas's answer gives a lot of great info about what rank 2 types mean, but I'll just expand on one point he didn't cover. Requiring an argument to be polymorphic doesn't just allow it to be used with multiple types; it also restricts what that function can do with its argument(s) and how it can produce its result. That is, it gives the caller less flexibility. Why would you want to do that? I'll start with a simple example:
Suppose we have a data type
data Country = BigEnemy | MediumEnemy | PunyEnemy | TradePartner | Ally | BestAlly
and we want to write a function
f g = launchMissilesAt $ g [BigEnemy, MediumEnemy, PunyEnemy]
that takes a function that's supposed to choose one of the elements of the list it's given and return an IO action launching missiles at that target. We could give f a simple type:
f :: ([Country] -> Country) -> IO ()
The problem is that we could accidentally run
f (\_ -> BestAlly)
and then we'd be in big trouble! Giving f a rank 1 polymorphic type
f :: ([a] -> a) -> IO ()
doesn't help at all, because we choose the type a when we call f, and we just specialize it to Country and use our malicious \_ -> BestAlly again. The solution is to use a rank 2 type:
f :: (forall a . [a] -> a) -> IO ()
Now the function we pass in is required to be polymorphic, so \_ -> BestAlly won't type check! In fact, no function returning an element not in the list it is given will typecheck (although some functions that go into infinite loops or produce errors and therefore never return will do so).
The above is contrived, of course, but a variation on this technique is key to making the ST monad safe.
Higher-rank types aren't as exotic as the other answers have made out. Believe it or not, many object-oriented languages (including Java and C#!) feature them. (Of course, no one in those communities knows them by the scary-sounding name "higher-rank types".)
The example I'm going to give is a textbook implementation of the Visitor pattern, which I use all the time in my daily work. This answer is not intended as an introduction to the visitor pattern; that knowledge is readily available elsewhere.
In this fatuous imaginary HR application, we wish to operate on employees who may be full-time permanent staff or temporary contractors. My preferred variant of the Visitor pattern (and indeed the one which is relevant to RankNTypes) parameterises the visitor's return type.
interface IEmployeeVisitor<T>
{
T Visit(PermanentEmployee e);
T Visit(Contractor c);
}
class XmlVisitor : IEmployeeVisitor<string> { /* ... */ }
class PaymentCalculator : IEmployeeVisitor<int> { /* ... */ }
The point is that a number of visitors with different return types can all operate on the same data. This means IEmployee must express no opinion as to what T ought to be.
interface IEmployee
{
T Accept<T>(IEmployeeVisitor<T> v);
}
class PermanentEmployee : IEmployee
{
// ...
public T Accept<T>(IEmployeeVisitor<T> v)
{
return v.Visit(this);
}
}
class Contractor : IEmployee
{
// ...
public T Accept<T>(IEmployeeVisitor<T> v)
{
return v.Visit(this);
}
}
I wish to draw your attention to the types. Observe that IEmployeeVisitor universally quantifies its return type, whereas IEmployee quantifies it inside its Accept method - that is to say, at a higher rank. Translating clunkily from C# to Haskell:
data IEmployeeVisitor r = IEmployeeVisitor {
visitPermanent :: PermanentEmployee -> r,
visitContractor :: Contractor -> r
}
newtype IEmployee = IEmployee {
accept :: forall r. IEmployeeVisitor r -> r
}
So there you have it. Higher-rank types show up in C# when you write types containing generic methods.
For those familiar with object oriented languages, a higher-rank function is simply a generic function that expects as its argument another generic function.
E.g. in TypeScript you could write:
type WithId<T> = T & { id: number }
type Identifier = <T>(obj: T) => WithId<T>
type Identify = <TObj>(obj: TObj, f: Identifier) => WithId<TObj>
See how the generic function type Identify demands a generic function of the type Identifier? This makes Identify a higher-rank function.

How to type cast

C#:
static int F(object x)
{
return x is string ? 1 : 2;
}
Haskell?
The tricky bit seems to me that Haskell does not have a root type object.
Edited: I do not care about converting to string. I want to know how to typecast (for example to see if an object is a Customer or an Order.
In Haskell, all types that allow a conversion to a string instantiate the Show typeclass which provides
show :: Show a => a -> String
So your whole code is nothing but
f x = show x
or
f = show
with the same generic type f :: Show a => a -> String (Forall types a that are conversible to a string, take a value of this type and return a string).
Note that you don't have to do an explicit, run-time type-check like in C#; the generic template is resolved at compile-time. You don't need a polymorphic root type - A cast like in C# would in fact be somewhat complicated and against the language's conception. Instead of allowing arbitrary casts between types, it defined typeclasses for certain meaningful conversions.
Note that compatibility is checked at compile-time:
-- Working
f 1
f "Hallo"
f (1, 2)
f [1, 2, 3]
-- Not working
f (\x -> x + 1)
In response to your edited question:
As I said before, arbitrary conversions aren't allowed in Haskell (without very very unsafe code). And since Haskell is not object-oriented, there is no inheritance relationship that required any cast. There simply aren't meaningless object values that needed runtime-checking/casting. For expressing alternatives, you'll have to define a union type, a typeclass or use the Either type.
In what case do you encounter an object that is a Customer or an Order? A value of that type is simply nonsensical. Please clarify again.
As to your logger example:
You'll need a typeclass:
class Loggable a where
writeToLog :: a -> IO ()
Dario's right, generally in Haskell you want to create a type class to dispatch on something's type. That being said, there is a type safe way to cast in Haskell. This is part of the Scrap your boilerplate generic programming library that allows you to write the "interesting" parts of manipulations of complex nested data types while SYB fills in the blanks. Brain meltingly awesome. Here's a presentation on it in ppt or html.
Here's what the cast looks like:
cast :: (Typeable a, Typeable b) => a -> Maybe b
ghci> (cast 'a') :: Maybe Char
Just 'a'
ghci> (cast 'a') :: Maybe Bool
Nothing
ghci> (cast True) :: Maybe Bool
Just True
Casting and is/instanceof make sense in languages that feature subtyping. Your question can be answered in several ways:
Haskell does not have subtyping and so is/instanceof make no sense in Haskell; there are only explicit conversions. There is no object type from which all types extend.
Haskell's type classes offer ad-hoc polymorphism and help in overloading a single name for many conversions. For example (as others have pointed out) show is the overloaded name for converting any type to a String. Type classes can also be used to make certain conversions (seem) implicit.
Using type classes, the authors of the generic Scrap Your Boilerplate library have created a safe cast function (also pointed out by others).
The most straightforward way is to use Data.Typeable, as Dario observes, which covers all the standard types, though you need to pass "Deriving Typeable", or otherwise implement typeOf for your own type definitions to be covered. This is not standard Haskell 98, but it is in ghc since 6.2.2.
Your code could be realised:
stringtyperep :: TypeRep
stringtyperep = typeOf "somestring"
F :: (Typeable 'a) =>'a -> Integer
F x | (typeOf x == stringtyperep) = 1
F x = 2
In general, OO-style type reflection is better done with generic programming, but this would not be a good example for that.
Additionally, all types in typeclass Typeable can be "cast" into Data.Dynamic.
If you want to have objects that can either be Customers or Orders, then you'd introduce a new datatype "Customer|Order" so that each object carries a type tag saying which it is.
I don't know the Haskell syntax offhand, but in F# it would be
type CustOrOrd =
| Cust of Customer
| Ord of Order
let F (x:CustOrOrd) : int =
match x with
| Cust c -> 1
| Ord o -> 2
let thing1 = Cust someCustomer
let thing2 = Ord someOrder
// can call F on thing1 or thing2
More generally, in Haskell if you want to do something like a fixed OO type hierarchy (for a fixed set of highly related types, to be able to treat them as the same type in some cases), you may use a union type as above. On the other hand, for common operations across a variety of unrelated types (like ToString/Show) you might use a Haskell type class.
This is something I've tried before, and I don't think you can do it.
Introduction to Haskell Pure Functions
Haskell takes a very different
approach. It starts by performing type
analysis with a type checker to
understand your program at compile
time. The type checker strictly
prohibits type casting and does not
allow type errors to be ignored.
Because types are checked at compile
time, and there is no escape from the
type checker, Haskell is frequently
described as both statically typed and
strongly typed.
Define Object yourself
If your use-case is quite simple, it's probably best just to define the Object type yourself, thus:
data Type = String | Integer | List | Bool
deriving (Eq, Show)
class Object a where
typeOf :: a -> Type
instance Object String where typeOf _ = String
instance Object Integer where typeOf _ = Integer
instance Object [a] where typeOf _ = List
instance Object Bool where typeOf _ = Bool
f :: (Object a, Num b) => a -> b
f x = if typeOf x == String then 1 else 2
Obviously you'll have to write an instance declaration for every type that you might want to use as an Object in your function that uses typeOf. This could get tricky when you try to define instances for tuples, because in Haskell two tuples are of different types if they don't have the same number of elements, so you might have to write an infinite number of instance declarations, rather like this:
data Type = String | Integer | List | Bool | Tuple
deriving (Eq, Show)
instance Object () where typeOf _ = Tuple
instance Object (a) where typeOf _ = Tuple
instance Object (a,b) where typeOf _ = Tuple
instance Object (a,b,c) where typeOf _ = Tuple
instance Object (a,b,c,d) where typeOf _ = Tuple
instance Object (a,b,c,d,e) where typeOf _ = Tuple
instance Object (a,b,c,d,e,f) where typeOf _ = Tuple
instance Object (a,b,c,d,e,f,g) where typeOf _ = Tuple
Use Data.Typeable
If your usage gets more complicated, you might try Data.Typeable:
import Data.Typeable
f :: (Typeable a, Num b) => a -> b
f x = if typeOf x == typeOf (undefined::String) then 1 else 2
You can replace the (undefined::String) with just "" if you prefer; whichever reads easier for you.
In C# it's likely more efficient not to do the cast:
return x == null ? null : x.ToString();
In Haskell there's the "show" type class, anything that implements the type class can have show called on it and so no casting is needed.

Resources