As an exercise, I am implementing in Haskell a 'cons' operation that forms a pair from two values of any type. Implementing the needed data type is easy enough:
data Nil = Nil deriving (Eq)
data Pair a b = Cons a b deriving (Eq)
car (Cons x _) = x
cdr (Cons _ y) = y
caar = car . car
cdar = cdr . car
cadr = car . cdr
cddr = cdr . cdr
*Main> cddr (Cons 55 (Cons (1,2,3,4) "hello, world!"))
"hello, world!"
*Main>
but inspired by this thread, I want to make the resulting pairs print out like Scheme lists would - including the infamous "improper list" (1 2 3 . 4). My implementation (see below) is working for Char's:
*Main> Cons 'a' (Cons 'b' (Cons 'c' Nil))
('a' 'b' 'c')
*Main> Cons 'a' (Cons 'b' 'c')
('a' 'b' . 'c')
*Main> Cons (Cons 'a' 'b')(Cons 'c' (Cons 'd' Nil))
(('a' . 'b') 'c' 'd')
It's not working so well for Int's (or any other data type). So my question is: how can I make this work for other data types? i.e., I want it to work like this:
*Main> Cons 5 (Cons "hello" (Cons False Nil))
(5 "hello" False)
My current full implementation follows:
data Nil = Nil deriving (Eq)
data Pair a b = Cons a b deriving (Eq)
car (Cons x _) = x
cdr (Cons _ y) = y
caar = car . car
cdar = cdr . car
cadr = car . cdr
cddr = cdr . cdr
instance Show Nil where show _ = "()"
class ShowPair a where
showRight::a->String
instance (Show a, ShowPair a, ShowPair b)=>Show (Pair a b) where
show (Cons car cdr) = "(" ++ (show car) ++ (showRight cdr) ++ ")"
instance (Show a, ShowPair a, ShowPair b)=>ShowPair (Pair a b) where
showRight (Cons car cdr) = " " ++ (show car) ++ (showRight cdr)
instance ShowPair Char where
showRight x = " . " ++ show x
instance ShowPair Int where
showRight x = " . " ++ show x
instance ShowPair Nil where
showRight _ = ""
Here's an option. First, enable these extensions by putting this line at the top of your file:
{-# LANGUAGE FlexibleInstances, OverlappingInstances, UndecidableInstances#-}
Next, remove your ShowPair
instances for Char
and Int
.
Now add a ShowPair
instance for anything with Show
:
instance Show a => ShowPair a where showRight = (" . " ++) . show
This now ensures that any type a
which is an instance of Show
is also an instance of ShowPair
where it is shown by prepending a .
to its normal string form. However, if a type has a more specific ShowPair
instance (e.g. Nil
), Haskell will use that one instead.
This is not part of standard Haskell, so you need to enable the three language extensions. Look at How to write an instance for all types in another type class? for more information on why you need the extensions.
Ben in the comments to the question mentions the native pair type, which I'm going to use in this answer. I'm also going to substitute your Nil
with the Haskell unit type ()
.
This is a bit outside what you're asking, but I think it's worth saying. It is difficult in Haskell to capture the notion of a "list" in Scheme unless you "cheat" and use an extension like Data.Dynamic
. This is because from the point of view of "pure," unextended Haskell, it is difficult if not impossible to assign all Scheme lists the same type. This means that while Scheme allows you to write functions that take any list, proper or improper, you're going to have a hard time doing the same in Haskell (and for good reason; improper "lists" should probably not exist anyway).
So for example, you've basically chosen to use (a, b)
as the type of Scheme-like pairs. Now suppose we have these Scheme lists:
(define zero '())
(define one '(1))
(define two '(1 2))
(define three '(1 2 3))
(define four '(1 2 3 4))
Here's a simple translation in terms of Haskell pairs, which corresponds to the way you're doing it:
zero :: ()
zero = ()
one :: (Integer, ())
one = (1, ())
two :: (Integer, (Integer, ()))
two = (1, (2, ()))
three :: (Integer, (Integer, (Integer, ())))
three = (1, (2, (3, ())))
four :: (Integer, (Integer, (Integer, (Integer, ()))))
four = (1, (2, (3, (4, ()))))
The key thing is that in Scheme you can easily write a function that ranges over all lists:
(define (reverse list)
(foldl cons '() list))
(define (filter pred? list)
(foldr (lambda (elem rest)
(if (pred? elem)
(cons elem rest)
rest))
'()
list))
(define (foldl fn init list)
(if (null? list)
init
(foldl fn (fn (car list) init) (cdr list))))
(define (foldr fn init list)
(if (null? list)
init
(fn (car list)
(foldr fn init (cdr list)))))
In this Haskell translation, you cannot do that easily at all, because "lists" of different lengths have different types. And it gets worse when you consider the difference between reverse
(which takes a list of length n and produces a list of length n) and filter
(which takes a list of length n and produces a list of length m ≤ n such that m can only be known at runtime).
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With