Homework 7

Recursive types and algebraic data types

This homework is written in literate Haskell; you can download the raw source to fill in yourself. You’re welcome to submit literate Haskell yourself, or to start fresh in a new file, literate or not.

Please submit homeworks via the DCI submission page.

We saw briefly in class the correspondence between datatype notation and recursive/algebraic type notation.

Let’s translate a Haskell datatype to algebraic types. We have the definition:

data IntList =
    Nil
  | Cons Int IntList

An IntList is either:

  • Nil, or
  • Cons n l, such that n is an Int and l is an IntList.

In algebraic types, we interpret ‘either’ using sums (written + in math and Either in Haskell). So in pseudo-Haskell, we have:

IntList = Nil + Cons Int IntList

Next, we don’t use constructor names in algebraic datatypes—we just represent the data. So Nil and Cons need to be replaced. Now, Nil has no arguments—the only information Nil provides is that it isn’t Cons. We can represent it using (), the unit type.

IntList = () + Cons Int IntList

Cons, on the other hand, has some arguments. We’ll represent them as a pair, using * (or × on paper, or (,) in Haskell).

IntList = () + (Int,IntList)

At this point, the only left to do is to get rid of the recursion. To do this, we use μ. The process is mechanical: if you have a definition of the form X = [some type t in terms of X], you translate it to X = μ α. t[α/X]. Here, that gives us:

X = mu alpha. () + (Int,alpha)

In general, translating to datatypes is a mechanical process. You’ll do some by hand in problem 1, but then you’ll make it automatic in problem 2.

Problem 1: understanding recursive and algebraic types

(a) 15 points

Translate the following datatype definitions to (possibly recursive) algebraic datatypes. You don’t need to show your work, but please format your answer like the demonstration above.

data Answer = Yes | No | Maybe

  fill in here

data MaybeInt = Nothing | Maybe Int


data Rope = Leaf String | Node Rope Int Rope

(b) 15 points

Translate the following algebraic datatypes to Haskell-style datatype definitions. You’ll have to come up with constructor names… what do you think they should be named? What would you name these types?

() + ()

  fill in here

mu alpha. Int + (alpha,alpha)

  fill in here

mu alpha. () + (Int,mu beta. () + (alpha,beta))

  fill in here

(c) 10 points

Consider the type μα. α. What kinds of values inhabit that type?

What about the type μα. α→α—what kinds of values inhabit that type?

HINT: One way to approach this kind of problem is to try to produce a typing derivation. Note that every type comes with terms that introduce values—-> comes with lambda, (,) comes with pairs, (+) comes with left and right—and terms that use, or eliminate, values—-> comes with application, (,) comes with fst and snd, and (+) comes with case analysis.

The corresponding introduction and elimination forms for μ types are fold and unfold.

When presented with a type, you can try to come up with values of that type by just applying introduction rules over and over. For example:

We want to find a term e such that:

. |- e : mu alpha. alpha -> alpha

so

. |- e : (mu alpha. alpha -> alpha) -> (mu alpha. alpha -> alpha)
----------------------------------------------------------------- 
. |- fold e : mu alpha. alpha -> alpha

Okay… what kind of e expression should e be if we want a value? Well, it’s got to have a -> type, so let’s make it a lambda:

x:(mu alpha. alpha -> alpha) |- e : (mu alpha. alpha -> alpha)
------------------------------------------------------------------------------------------------ 
. |- \x:(mu alpha. alpha -> alpha). e : (mu alpha. alpha -> alpha) -> (mu alpha. alpha -> alpha)
----------------------------------------------------------------- 
. |- fold (\x. e) : mu alpha. alpha -> alpha

Okay… what should e be now? Well, we have x around, so that could work.

What else? What happens if you unfold x? Well, we have:

x:(mu alpha. alpha -> alpha) |- x : mu alpha. alpha -> alpha
--------------------------------------------------------------------------------------------------- 
x:(mu alpha. alpha -> alpha) |- unfold x : (mu alpha. alpha -> alpha) -> (mu alpha. alpha -> alpha)

What can we do with this? We could apply it… but to what? Well, something that has type mu alpha. alpha -> alpha. Like… well, x!

So another possible value is fold (\x. (unfold x) x), if we erase the subscripts.

What other values inhabit this type?

Problem 2: translating datatype definitions to recursive types automatically 20 points

In this problem, we will automatically translate datatype definitions to recursive algebraic types.

module Hw07 where

import qualified Data.Set as Set
import Data.Set (Set)

import qualified Data.Map as Map
import Data.Map (Map, (!))

We’ll represent definitions using the Defn data structure. A datatype definition for our purposes consists of a name and a list of constructors with their arguments.

data Defn = Defn { dName :: String,
                   dCtors :: [(String,[Type])] }

We’ll represent arguments using the following language of types.

data Type = 
    TInt
  | TBool
  | TDatatype String
  | TArrow Type Type

By way of example, here’s a datatype definition for integer lists.

listDefn :: Defn
listDefn = Defn { dName = "IntList",
                  dCtors = [("Nil",[]),
                            ("Cons",[TInt,TDatatype "IntList"])] }

Here’s one for days of the week.

dayDefn :: Defn
dayDefn = Defn { dName = "Day",
                 dCtors = [("Sunday",[]),
                           ("Monday",[]),
                           ("Tuesday",[]),
                           ("Wednesday",[]),
                           ("Thursday",[]),
                           ("Friday",[]),
                           ("Saturday",[])] }

Write a Defn for binary trees with integers stored at the nodes.

treeDefn :: Defn
treeDefn = undefined -- fill in here

We’re going to translate datatype definitions to a language of recursive algebraic types, as below.

data RecType = 
    RTInt
  | RTBool
  | RTVar String
  | RTUnit
  | RTPair RecType RecType
  | RTSum RecType RecType
  | RTMu String RecType
  | RTArrow RecType RecType
    deriving Show

First, write a function to determine whether such types are well formed—i.e., whether or not they contain unbound variables. Here’s the interesting rules for type well formedness:

alpha in G
-------------- 
G |- alpha : *

G,alpha |- t : *
-------------------- 
G |- mu alpha. t : *

G |- t1 : *   G |- t2 : *
------------------------- 
G |- t1 -> t2 : *
wellFormed :: RecType -> Bool
wellFormed = undefined

Now write a function that takes a Defn and produces a RecType. You’ll need to simply follow the recipe above. You can assume that the constructors for a given Defn only refer back to the current definition: that is, if TDatatype s occurs in the argument list for a constructor when defining a Defn named n, then you may assume that s == n.

For example, listDefn above is fine, but you don’t need to deal with a definition like:

treeListDefn :: Defn
treeListDefn = Defn { dName = "TreeList",
                      dCtors = [("LEmpty",[]),
                                ("LNode",[TDatatype "TreeList",
                                          TDatatype "IntList",
                                          TDatatype "TreeList"])] }

Here we violate the assumption, because TDatatype "IntList" appears in the LNode constructor.

simpleDefnToRec :: Defn -> RecType
simpleDefnToRec (Defn name ctors) = 
  undefined

For extra credit: write a function that takes a Defn and produces a RecType, without any assumptions. You’ll need to change the interface from simpleDefnToRec. Feel free to come get help on this, but only after you’ve finished the rest of the assignment.

Problem 3: wearing the hair shirt: recursive datatypes in Haskell 20 points

newtype Mu f = Fold { unFold :: f (Mu f) }

Even if you don’t undersatnd this type, observe that Fold has the type f (Mu f) -> Mu f and unFold has the type Mu f -> f (Mu f). The type Mu f corresponds to μα. t, and the type f (Mu f) correspond to t[μα. t/α].

Here’s a definition for lists of arbitrary values:

data ListF a f = Nil | Cons a f
type List a = Mu (ListF a)

nil = Fold Nil
cons x xs = Fold $ Cons x xs

toList l = 
  case unFold l of
    Nil -> []
    Cons x xs -> x:toList xs

Write a similar definition for rose trees.

Write a preorder traversal of these rose trees. You’ll almost certainly want helper functions.

preorder :: RoseTree a -> List a
preorder t =
  undefined