Constructor that lifts (via DataKinds) to * -> A - haskell

Given an ADT like
data K = A | B Bool
the DataKinds extension allows us to lift it into kinds and types/type constructors
K :: BOX
'A :: K
'B :: 'Bool -> K
Is there a way to add a constructor to K that lifts to the type constructor
'C :: * -> K
?

As Conor states, this is not directly possible. You can, however, define
data K a = ... | C a
Then this promotes to
C :: a -> K a
If you then use K *, you can achieve what you want.

At the moment, I'm afraid not. I haven't spotted an obvious workaround, either.
This ticket documents the prospects for the declaration of data kinds, born kind, rather than being data types with kindness thrust upon them. It would be entirely reasonable for the constructors of such things to pack up types as you propose. We're not there yet, but it doesn't look all that problematic.
My eyes are on a greater prize. I would like * to be perfectly sensible type of runtime values, so that the kind you want could exist by promotion as we have it today. Combine that with the mooted notion of pi-type (non-parametric abstraction over the portion of the language that's effectively shared by types and values) and we might get a more direct way to make ad hoc type abstractions than we have with Data.Typeable. The usual forall would remain parametric.

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

How to think about the lack of laws

I am a mathematician who works a lot with category theory, and I've been using Haskell for a while to perform certain computations etc., but I am definitely not a programmer. I really love Haskell and want to become much more fluent in it, and the type system is something that I find especially great to have in place when writing programs.
However, I've recently been trying to implement category theoretic things, and am running into problems concerning the fact that you seemingly can't have class method laws in Haskell. In case my terminology here is wrong, what I mean is that I can write
class Monoid c where
id :: c -> c
m :: c -> c -> c
but I can't write some law along the lines of
m (m x y) z == m x $ m y z
From what I gather, this is due to the lack of dependent types in Haskell, but I'm not sure how exactly this is the case (having now read a bit about dependent types). It also seems that the convention is just to include laws like this in comments and hope that you don't accidentally cook up some instance that doesn't satisfy them.
How should I change my approach to Haskell to deal with this problem? Is there a nice mathematical/type-theoretic solution (for example, require the existence of an associator that is an isomorphism (though then the question is, how do we encode isomorphisms without a law?)); is there some 'hack' (using extensions such as DataKinds); should I be drastic and switch to using something like Idris instead; or is the best response to just change the way I think about using Haskell (i.e. accept that these laws can't be implemented in a Haskelly way)?
(bonus) How exactly does the lack of laws come from not supporting dependent types?
You want to require that:
m (m x y) z = m x (m y z) -- (1)
But to require this you need a way to check it. So you, or your compiler (or proof assistant), need to construct a proof of this. And the question is, what type is a proof of (1)?
One could imagine some Proof type but then maybe you could just construct a proof that 0 = 0 instead of a proof of (1) and both would have type Proof. So you’d need a more general type. I can’t decide how to break up the rest of the question so I’ll go for a super brief explanation of the Curry-Howard isomorphism followed by an explanation of how to prove two things are equal and then how dependent types are relevant.
The Curry-Howard isomorphism says that propositions are isomorphic to types and proofs are isomorphic to programs: a type corresponds to a proposition and a proof of that proposition corresponds to a program constructing a value inhabiting that type. Ignoring how many propositions might be expressed as types, an example would be that the type A * B (written (A, B) in Haskell) corresponds to the proposition “A and B,” while the type A + B (written Either A B in Haskell) corresponds to the proposition “A or B.” Finally the type A -> B corresponds to “A implies B,” as a proof of this is a program which takes evidence of A and gives you evidence of B. One should note that there isn’t a way to express not A but one could imagine adding a type Not A with builtins of type Either a (Not a) for the law of the excluded middle as well as Not (Not a) -> a, and a * Not a -> Void (where Void is a type which cannot be inhabited and therefore corresponds to false), but then one can’t really run these programs to get constructivist proofs.
Now we will ignore some realities of Haskell and imagine that there aren’t ways round these rules (in particular undefined :: a says everything is true, and unsafeCoerce :: a -> b says that anything implies anything else, or just other functions that don’t return where their existence does not imply the corresponding proof).
So we know how to combine propositions but what might a proposition be? Well one could be to say that two types are equal. In Haskell this corresponds to the GADT
data Eq a b where Refl :: Eq c c
Where this constructor corresponds to the reflexive property of equality.
[side note: if you’re still interested so far, you may be interested to look up Voevodsky’s univalent foundations, depending on how much the idea of “Homotopy type theory” interests you]
So can we prove something now? How about the transitive property of equality:
trans :: Eq a b -> Eq b c -> Eq a c
trans x y =
case x of
Refl -> -- by this match being successful, the compiler now knows that a = b
case y of
Refl -> -- and now b = c and so the compiler knows a = c
Refl -- the compiler knows that this is of type Eq d d, and as it knows a = c, this typechecks as Eq a c
This feels like one hasn’t really proven anything (especially as this mainly relies on the compiler knowing the transitive and symmetric properties), but one gets a similar feeling when proving simple things in logic as well.
So now how might you prove the original proposition (1)? Well let’s imagine we want a type c to be a monoid then we should also prove that $\forall x,y,z:c, m (m x y) z = m x (m y z).$ So we need a way to express m (m x y) z as a type. Strictly speaking this isn’t dependent types (this can be done with DataKinds to promote values and type families instead of functions). But you do need dependent types to have types depend on values. Specifically if you have a type Nat of natural numbers and a type family Vec :: Nat -> * (* is the kind (read type) of all types) of fixed length vectors, you could define a dependently typed function mkVec :: (n::Nat) -> Vec n. Observe how the type of the output depends on the value of the input.
So your law needs to have functions promoted to type level (skipping the questions about how one defines type equality and value equality), as well as dependent types (made up syntax):
class Monoid c where
e :: c
(*) :: c -> c -> c
idl :: (x::c) -> Eq x (e * x)
idr :: (x::c) -> Eq x (x * e)
assoc :: (x::c) -> (y::c) -> (z::c) -> Eq ((x * y) * z) (x * (y * z))
Observe how types tend to become large with dependent types and proofs. In a language missing typeclasses one could put such values into a record.
Final note on the theory of dependent types and how these correspond to the curry Howard isomorphism.
Dependent types can be considered an answer to the question: what types correspond to the propositions $\forall x\in S\quad P(x)$ and $\exists y\in T\quad Q(y)?$
The answer is that you create new ways to make types: the dependent product and the dependent sum (coproduct). The dependent product expresses “for all values $x$ of type $S,$ there is a value of type $P(x).$” A normal product would be a dependent product with $S=2,$ a type inhabited by two values. A dependent product might be written (x:T) -> P x. A dependent sum says “some value $y$ of type $T$, paired with a value of type $Q(y).$” this might be written (y:T) * Q y.
One can think of these as a generalisation of arbitrarily indexed (co)products from Set to general categories, where one might sensibly write e.g. $\prod_\Lambda X(\lambda),$ and sometimes such notation is used in type theory.

What exactly are GHC type coercions?

I have been looking up haskell's core language to understand how it works. One feature that I found during my internet searches were type coercions. I know that they are used to implement GADTs, but I don't understand much else. All descriptions I found online were quite high level for me, although I have a decent understanding of system F, though. Can anyone explain type coercions in an understandable manner to me, please?
Basically Haskell compiles by evaluating to this simple core language. In an effort to keep in simple it's generally not desirable to add constructs like GADTs or type classes directly to the language so instead they are compiled away at the very front end of the compiler into the simpler but more general (and verbose) constructs provided by core. Also keep in mind that Core is typed so we have to make sure we can encode all of these things in a typed way, a significant complication.
In order to encode GADTs they get elaborated to normal data types with existentials and coercions. The basic idea is that a coercion is a type with what is called an equality kind, written t ~ t'. This type is meant to witness evidence that even though we may not know it, t and t' are the same type under the hood. They're passed around just like any other type so there's nothing special in how that is handled. There's also a suite of type constructors for manipulating these types constitution little proofs about equality, like sym :: t ~ t' -> t' ~ t for example. Finally, there is an operator at the term level which takes a term of type t and a type of kind t ~ t' and is typed as a term of type t'. eg cast e T :: t' but this term behaves identically to e. We've just used our proof that t' and t are the same to cast e to make the type checker happy.
That's the basic idea
Kinds representing equality
Types representing proofs of equality
cast at the term level to use these proofs
Also note that by isolating proofs to the type level they cannot end up having a runtime cost as types are going to be erased down the line.
I think a nice reference on all of this is System F with Type Equality Coercions but of course all of SPJ's publications could help.
#jozefg deserves the answer, but here's an example of GADTs desugaring to existential quantification. Not quite Core yet, but a step toward it.
data Foo :: * -> * where
Bar :: Int -> Foo Int
Oink :: b -> c -> d -> Foo (f b)
via
data Foo a where
Bar :: (a ~ Int) => Int -> Foo a
Oink :: (a ~ f b) => b -> c -> d -> Foo a
to
data Foo a
= (a ~ Int) => Bar Int
| forall b c d f. (a ~ f b) => Oink b c d
Courtesy of /u/MitchellSalad on /r/haskell.

What exactly is the kind "*" in Haskell?

In Haskell, (value-level) expressions are classified into types, which can be notated with :: like so: 3 :: Int, "Hello" :: String, (+ 1) :: Num a => a -> a. Similarly, types are classified into kinds. In GHCi, you can inspect the kind of a type expression using the command :kind or :k:
> :k Int
Int :: *
> :k Maybe
Maybe :: * -> *
> :k Either
Either :: * -> * -> *
> :k Num
Num :: * -> Constraint
> :k Monad
Monad :: (* -> *) -> Constraint
There are definitions floating around that * is the kind of "concrete types" or "values" or "runtime values." See, for example, Learn You A Haskell. How true is that? We've had a few questions about kinds that address the topic in passing, but it'd be nice to have a canonical and precise explanation of *.
What exactly does * mean? And how does it relate to other more complex kinds?
Also, do the DataKinds or PolyKinds extensions change the answer?
First off, * is not a wildcard! It's also typically pronounced "star."
Bleeding edge note: There is as of Feb. 2015 a proposal to simplify GHC's subkind system (in 7.12 or later). That page contains a good discussion of the GHC 7.8/7.10 story. Looking forward, GHC may drop the distinction between types and kinds, with * :: *. See Weirich, Hsu, and Eisenberg, System FC with Explicit Kind Equality.
The Standard: A description of type expressions.
The Haskell 98 report defines * in this context as:
The symbol * represents the kind of all nullary type constructors.
In this context, "nullary" simply means that the constructor takes no parameters. Either is binary; it can be applied to two parameters: Either a b. Maybe is unary; it can be applied to one parameter: Maybe a. Int is nullary; it can be applied to no parameters.
This definition is a little bit incomplete on its own. An expression containing a fully-applied unary, binary, etc. type constructor also has kind *, e.g. Maybe Int :: *.
In GHC: Something that contains values?
If we poke around the GHC documentation, we get something closer to the "can contain a runtime value" definition. The GHC Commentary page "Kinds" states that "'*' is the kind of boxed values. Things like Int and Maybe Float have kind *." The GHC user's guide for version 7.4.1, on the other hand, stated that * is the kind of "lifted types". (That passage wasn't retained when the section was revised for
PolyKinds.)
Boxed values and lifted types are a bit different. According to the GHC Commentary page "TypeType",
A type is unboxed iff its representation is other than a pointer. Unboxed types are also unlifted.
A type is lifted iff it has bottom as an element. Closures always have lifted types: i.e. any let-bound identifier in Core must have a lifted type. Operationally, a lifted object is one that can be entered. Only lifted types may be unified with a type variable.
So ByteArray#, the type of raw blocks of memory, is boxed because it is represented as a pointer, but unlifted because bottom is not an element.
> undefined :: ByteArray#
Error: Kind incompatibility when matching types:
a0 :: *
ByteArray# :: #
Therefore it appears that the old User's Guide definition is more accurate than the GHC Commentary one: * is the kind of lifted types. (And, conversely, # is the kind of unlifted types.)
Note that if types of kind * are always lifted, for any type t :: * you can construct a "value" of sorts with undefined :: t or some other mechanism to create bottom. Therefore even "logically uninhabited" types like Void can have a value, i.e. bottom.
So it seems that, yes, * represents the kind of types that can contain runtime values, if undefined is your idea of a runtime value. (Which isn't a totally crazy idea, I don't think.)
GHC Extensions?
There are several extensions which liven up the kind system a bit. Some of these are mundane: KindSignatures lets us write kind annotations, like type annotations.
ConstraintKinds adds the kind Constraint, which is, roughly, the kind of the left-hand side of =>.
DataKinds lets us introduce new kinds besides * and #, just as we can introduce new types with data, newtype, and type.
With DataKinds every data declaration (terms and conditions may apply) generates a promoted kind declaration. So
data Bool = True | False
introduces the usual value constructor and type name; additionally, it produces a new kind, Bool, and two types: True :: Bool and False :: Bool.
PolyKinds introduces kind variables. This just a way to say "for any kind k" just like we say "for any type t" at the type level. As regards our friend * and whether it still means "types with values", I suppose you could say a type t :: k where k is a kind variable could contain values, if k ~ * or k ~ #.
In the most basic form of the kind language, where there are only the kind * and the kind constructor ->, then * is the kind of things that can stand in a type-of relationship to values; nothing with a different kind can be a type of values.
Types exist to classify values. All values with the same type are interchangeable for the purpose of type-checking, so the type checker only has to care about types, not specific values. So we have the "value level" where all the actual values live, and the "type level" where their types live. The "type-of" relationship forms links between the two levels, with a single type being the type of (usually) many values. Haskell makes these two levels quite explicit; it's why you can have declarations like data Foo = Foo Int Chat Bool where you've declared a type-level thing Foo (a type with kind *) and a value-level thing Foo (a constructor with type Int -> Char -> Bool -> Foo). The two Foos involved simply refer to different entities on different levels, and Haskell separates these so completely that it can always tell what level you're referring to and thus can allow (sometimes confusingly) things on the different levels to have the same name.
But as soon as we introduce types that themselves have structure (like Maybe Int, which is a type constructor Maybe applied to a type Int), then we have things that exist at the type level which do not actually stand in a type-of relationship to any values. There are no values whose type is just Maybe, only values with type Maybe Int (and Maybe Bool, Maybe (), even Maybe Void, etc). So we need to classify our type-level things for the same reason we need to classify our values; only certain type-expressions actually represent something that can be the type of values, but many of them work interchangeably for the purpose of "kind-checking" (whether it's a correct type for the value-level thing it's declared to be the type of is a problem for a different level).1
So * (which is often stated to be pronounced "type") is the basic kind; it's the kind of all type-level things that can be stated to be the type of values. Int has values; therefore its type is *. Maybe does not have values, but it takes an argument and produces a type that has values; this gets us a kind like ___ -> *. We can fill in the blank by observing that Maybe's argument is used as the type of the value appearing in Just a, so its argument must also be a type of values (with kind *), and so Maybe must have kind * -> *. And so on.
When you're dealing with kinds that only involve stars and arrows, then only type-expressions of kind * are types of values. Any other kind (e.g. * -> (* -> * -> *) -> (* -> *)) only contains other "type-level entities" that are not actual types that contain values.
PolyKinds, as I understand it, doesn't really change this picture at all. It just allows you to make polymorphic declarations at the kind-level, meaning it adds variables to our kind language (in addition to stars and arrows). So now I can contemplate type-level things of kind k -> *; this could be instantiated to work as either kind * -> * or (* -> *) -> * or (* -> (* -> *)) -> *. We've gained exactly the same kind of power as having (a -> b) -> [a] -> [b] at the type level gained us; we can write one map function with a type that contains variables, instead of having to write every possible map function separately. But there's still only one kind that contains type-level things that are the types of values: *.
DataKinds also introduces new things to the kind language. Effectively what it does though is to let us declare arbitrary new kinds, which contain new type-level entities (just as ordinary data declarations allow us to declare arbitrary new types, which contain new value-level entities). But it doesn't let us declare things with a correspondence of entities across all 3 levels; if I have data Nat :: Z | S Nat and use DataKinds to lift it to the kind level, then we have two different things named Nat that exist on the type level (as the type of value-level Z, S Z, S (S Z), etc), and at the kind level (as the kind of type-level Z, S Z, S (S Z)). The type-level Z is not the type of any values though; the value Z inhabits the type-level Nat (which in turn is of kind *), not the type-level Z. So DataKinds adds new user defined things to the kind language, which can be the kind of new user-defined things at the type level, but it remains the case that the only type-level things that can be the types of values are of kind *.
The only addition to the kind language that I'm aware of which truly does change this are the kinds mentioned in #ChristianConkle's answer, such as # (I believe there are a couple more now too? I'm not really terribly knowledgeable about "low level" types such as ByteArray#). These are the kinds of types that have values that GHC needs to know to treat differently (such as not assuming they can be boxed and lazily evaluated), even when polymorphic functions are involved, so we can't just attach the knowledge that they need to be treated differently to these values' types, or it would be lost when calling polymorphic functions on them.
1 The word "type" can thus be a little confusing. Sometimes it is used to refer to things that actually stand in a type-of relationship to things on the value level (this is the interpretation used when people say "Maybe is not a type, it's a type-constructor"). And sometimes it's used to refer to anything that exists at the type-level (under this interpretation Maybe is in fact a type). In this post I'm trying to very explicitly refer to "type-level things" rather than use "type" as a short-hand.
For beginners that are trying to learn about kinds (you can think of them as the type of a type) I recommend this chapter of the Learn you a Haskell book.
I personally think of kinds in this way:
You have concrete types, e.g. Int, Bool,String, [Int], Maybe Int or Either Int String.
All of these have the kind *. Why? Because they can't take any more types as a parameter; an Int, is an Int; a Maybe Int is a Maybe Int. What about Maybe or [] or Either, though?
When you say Maybe, you do not have a concrete type, because you didn't specify its parameter. Maybe Int or Maybe String are different but both have a * kind, but Maybe is waiting for a type of kind * to return a kind *. To clarify, let's look at what GHCI's :kind command can tell us:
Prelude> :kind Maybe Int
Maybe Int :: *
Prelude> :kind Maybe
Maybe :: * -> *
With lists it's the same:
Prelude> :k [String]
[String] :: *
Prelude> :k []
[] :: * -> *
What about Either?
Prelude> :k Either Int String
Either Int String :: *
Prelude> :k Either Int
Either Int :: * -> *
You could think of intuitively think of Either as a function that takes parameters, but the parameters are types:
Prelude> :k Either Int
Either Int :: * -> *
means Either Int is waiting for a type parameter.

Functions don't just have types: They ARE Types. And Kinds. And Sorts. Help put a blown mind back together

I was doing my usual "Read a chapter of LYAH before bed" routine, feeling like my brain was expanding with every code sample. At this point I was convinced that I understood the core awesomeness of Haskell, and now just had to understand the standard libraries and type classes so that I could start writing real software.
So I was reading the chapter about applicative functors when all of a sudden the book claimed that functions don't merely have types, they are types, and can be treated as such (For example, by making them instances of type classes). (->) is a type constructor like any other.
My mind was blown yet again, and I immediately jumped out of bed, booted up the computer, went to GHCi and discovered the following:
Prelude> :k (->)
(->) :: ?? -> ? -> *
What on earth does it mean?
If (->) is a type constructor, what are the value constructors? I can take a guess, but would have no idea how define it in traditional data (->) ... = ... | ... | ... format. It's easy enough to do this with any other type constructor: data Either a b = Left a | Right b. I suspect my inability to express it in this form is related to the extremly weird type signature.
What have I just stumbled upon? Higher kinded types have kind signatures like * -> * -> *. Come to think of it... (->) appears in kind signatures too! Does this mean that not only is it a type constructor, but also a kind constructor? Is this related to the question marks in the type signature?
I have read somewhere (wish I could find it again, Google fails me) about being able to extend type systems arbitrarily by going from Values, to Types of Values, to Kinds of Types, to Sorts of Kinds, to something else of Sorts, to something else of something elses, and so on forever. Is this reflected in the kind signature for (->)? Because I've also run into the notion of the Lambda cube and the calculus of constructions without taking the time to really investigate them, and if I remember correctly it is possible to define functions that take types and return types, take values and return values, take types and return values, and take values which return types.
If I had to take a guess at the type signature for a function which takes a value and returns a type, I would probably express it like this:
a -> ?
or possibly
a -> *
Although I see no fundamental immutable reason why the second example couldn't easily be interpreted as a function from a value of type a to a value of type *, where * is just a type synonym for string or something.
The first example better expresses a function whose type transcends a type signature in my mind: "a function which takes a value of type a and returns something which cannot be expressed as a type."
You touch so many interesting points in your question, so I am
afraid this is going to be a long answer :)
Kind of (->)
The kind of (->) is * -> * -> *, if we disregard the boxity GHC
inserts. But there is no circularity going on, the ->s in the
kind of (->) are kind arrows, not function arrows. Indeed, to
distinguish them kind arrows could be written as (=>), and then
the kind of (->) is * => * => *.
We can regard (->) as a type constructor, or maybe rather a type
operator. Similarly, (=>) could be seen as a kind operator, and
as you suggest in your question we need to go one 'level' up. We
return to this later in the section Beyond Kinds, but first:
How the situation looks in a dependently typed language
You ask how the type signature would look for a function that takes a
value and returns a type. This is impossible to do in Haskell:
functions cannot return types! You can simulate this behaviour using
type classes and type families, but let us for illustration change
language to the dependently typed language
Agda. This is a
language with similar syntax as Haskell where juggling types together
with values is second nature.
To have something to work with, we define a data type of natural
numbers, for convenience in unary representation as in
Peano Arithmetic.
Data types are written in
GADT style:
data Nat : Set where
Zero : Nat
Succ : Nat -> Nat
Set is equivalent to * in Haskell, the "type" of all (small) types,
such as Natural numbers. This tells us that the type of Nat is
Set, whereas in Haskell, Nat would not have a type, it would have
a kind, namely *. In Agda there are no kinds, but everything has
a type.
We can now write a function that takes a value and returns a type.
Below is a the function which takes a natural number n and a type,
and makes iterates the List constructor n applied to this
type. (In Agda, [a] is usually written List a)
listOfLists : Nat -> Set -> Set
listOfLists Zero a = a
listOfLists (Succ n) a = List (listOfLists n a)
Some examples:
listOfLists Zero Bool = Bool
listOfLists (Succ Zero) Bool = List Bool
listOfLists (Succ (Succ Zero)) Bool = List (List Bool)
We can now make a map function that operates on listsOfLists.
We need to take a natural number that is the number of iterations
of the list constructor. The base cases are when the number is
Zero, then listOfList is just the identity and we apply the function.
The other is the empty list, and the empty list is returned.
The step case is a bit move involving: we apply mapN to the head
of the list, but this has one layer less of nesting, and mapN
to the rest of the list.
mapN : {a b : Set} -> (a -> b) -> (n : Nat) ->
listOfLists n a -> listOfLists n b
mapN f Zero x = f x
mapN f (Succ n) [] = []
mapN f (Succ n) (x :: xs) = mapN f n x :: mapN f (Succ n) xs
In the type of mapN, the Nat argument is named n, so the rest of
the type can depend on it. So this is an example of a type that
depends on a value.
As a side note, there are also two other named variables here,
namely the first arguments, a and b, of type Set. Type
variables are implicitly universally quantified in Haskell, but
here we need to spell them out, and specify their type, namely
Set. The brackets are there to make them invisible in the
definition, as they are always inferable from the other arguments.
Set is abstract
You ask what the constructors of (->) are. One thing to point out
is that Set (as well as * in Haskell) is abstract: you cannot
pattern match on it. So this is illegal Agda:
cheating : Set -> Bool
cheating Nat = True
cheating _ = False
Again, you can simulate pattern matching on types constructors in
Haskell using type families, one canoical example is given on
Brent Yorgey's blog.
Can we define -> in the Agda? Since we can return types from
functions, we can define an own version of -> as follows:
_=>_ : Set -> Set -> Set
a => b = a -> b
(infix operators are written _=>_ rather than (=>)) This
definition has very little content, and is very similar to doing a
type synonym in Haskell:
type Fun a b = a -> b
Beyond kinds: Turtles all the way down
As promised above, everything in Agda has a type, but then
the type of _=>_ must have a type! This touches your point
about sorts, which is, so to speak, one layer above Set (the kinds).
In Agda this is called Set1:
FunType : Set1
FunType = Set -> Set -> Set
And in fact, there is a whole hierarchy of them! Set is the type of
"small" types: data types in haskell. But then we have Set1,
Set2, Set3, and so on. Set1 is the type of types which mentions
Set. This hierarchy is to avoid inconsistencies such as Girard's
paradox.
As noticed in your question, -> is used for types and kinds in
Haskell, and the same notation is used for function space at all
levels in Agda. This must be regarded as a built in type operator,
and the constructors are lambda abstraction (or function
definitions). This hierarchy of types is similar to the setting in
System F omega, and more
information can be found in the later chapters of
Pierce's Types and Programming Languages.
Pure type systems
In Agda, types can depend on values, and functions can return types,
as illustrated above, and we also had an hierarchy of
types. Systematic investigation of different systems of the lambda
calculi is investigated in more detail in Pure Type Systems. A good
reference is
Lambda Calculi with Types by Barendregt,
where PTS are introduced on page 96, and many examples on page 99 and onwards.
You can also read more about the lambda cube there.
Firstly, the ?? -> ? -> * kind is a GHC-specific extension. The ? and ?? are just there to deal with unboxed types, which behave differently from just * (which has to be boxed, as far as I know). So ?? can be any normal type or an unboxed type (e.g. Int#); ? can be either of those or an unboxed tuple. There is more information here: Haskell Weird Kinds: Kind of (->) is ?? -> ? -> *
I think a function can't return an unboxed type because functions are lazy. Since a lazy value is either a value or a thunk, it has to be boxed. Boxed just means it is a pointer rather than just a value: it's like Integer() vs int in Java.
Since you are probably not going to be using unboxed types in LYAH-level code, you can imagine that the kind of -> is just * -> * -> *.
Since the ? and ?? are basically just more general version of *, they do not have anything to do with sorts or anything like that.
However, since -> is just a type constructor, you can actually partially apply it; for example, (->) e is an instance of Functor and Monad. Figuring out how to write these instances is a good mind-stretching exercise.
As far as value constructors go, they would have to just be lambdas (\ x ->) or function declarations. Since functions are so fundamental to the language, they get their own syntax.

Resources