"class []" proposal Re: [Haskell-cafe] One thought: Num to 0 as ? to list?

Bulat Ziganshin bulat.ziganshin at gmail.com
Mon Aug 14 03:50:54 EDT 2006


Hello Marc,

Sunday, August 13, 2006, 10:36:39 PM, you wrote:

> In other words: why not overload (:) ?

i have such proposal, more or less complete:


1) define [] as type class and [] and ':' as operations of this class:

class [] c where
  []   :: c a              -- creates empty container
  (:)  :: a -> c a -> c a  -- prepends new element to the head of container
  head :: c a -> a         -- returns first container's element
  tail :: c a -> c a       -- returns remaining container's elements

  

2) allow to use type classes in type declarations like the types
itself. for example, allow the following:

f :: Num a => a -> Int
write as
f :: Num -> Int

and following:

sequence :: Monad m => [m a] -> m [a]
write as
sequence :: [Monad a] -> Monad [a]



these two changes together will change the meaning of existing list
functions declarations, making them polymorphic functions that are
ready to work with any container which is an instance of [] class.
For example, the following declaration:

foldr :: (a -> b -> b) -> b -> [a] -> b

now will be treated as:

foldr :: ([] c) => (a -> b -> b) -> b -> c a -> b




3) translate pattern matching on the left side of function equations
to the equivalent pattern guards:

foldr k z []     = z
foldr k z (x:xs) = x `k` foldr k z xs

turns into:

foldr k z xx | xx==[]                   = z
             | x<-head xx, xs<-tail xx  = x `k` foldrL k z xs



4) improve Haskell defaulting mechanism to allow declaring default
container type used when there is not enough context:

default [] => List

main = print (head [1,2,3])

Here, [1,2,3] desugared into 1:2:3:[]. Because there is no
information which allow to decide which container should be used, we
defaults to use List instance:

type List a = Cons a (List a) | Nil

instance [] List where .....



Some Haskeller once said that lists are widely used in Haskell primarily
because they are supported much better than any other data structure.
All these changes together will allow to use any other container with
the same easy as lists.

i have attached a file which implements the idea without language
changes. at the last end, it computes length and sum of two
containers - list and array slice - using the same polymorphic
functions:

lengthL xs = foldrL (\_->(+1)) 0 xs
sumL  xs   = foldrL (+) 0 xs


Of course, this idea is not yet completely developed. Two problems that i
see just now is dealing with pattern matching failures (f.e. trying to
call 'head' for empty list) and building an hierarchy of classes
representing various list features. at least, array slices don't
support efficient ':' implementation.



-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com
-------------- next part --------------
A non-text attachment was scrubbed...
Name: ListLike.hs
Type: application/octet-stream
Size: 1361 bytes
Desc: not available
Url : http://www.haskell.org//pipermail/haskell-cafe/attachments/20060814/7b257245/ListLike-0001.obj


More information about the Haskell-Cafe mailing list