[Haskell-cafe] Re: how to write a list builder? fixpoint?

Graham Klyne GK at ninebynine.org
Wed Jun 2 06:31:34 EDT 2004


[moved to Haskell-cafe]

This makes my head hurt!  Let me see if I get this right.

When the type checker sees:

    build' as a a2 ...

then it invokes the second instance of BuildList (i.e. BuildList a (a->r)) 
and returns the value:

    build'(a:as) a2 ...

But when it sees just:

   build' as a

(as a value, not used as a function application), then the type checker 
invokes the first instance and returns:

   reverse$ a:as

So they key here appears to be that the type-checker can distinguish 
between function application and other uses of an expression?

#g
--

At 18:18 01/06/04 -0700, oleg at pobox.com wrote:

> > Is it possible to write a function to build a list [a]?
> > so that I can write [a,b,c,d] as "getBuilt $ build a b c d"?
>
>Yes, in the format very close to desired.
>
> > {-# OPTIONS -fglasgow-exts #-}
> > {-# OPTIONS -fallow-undecidable-instances #-}
> >
> > module Foo where
> >
> > class BuildList a r  | r-> a where
> >     build' :: [a] -> a -> r
> >
> > instance BuildList a [a] where
> >     build' l x = reverse$ x:l
> >
> > instance BuildList a r => BuildList a (a->r) where
> >     build' l x y = build'(x:l) y
>
>That's it. It works both on GHC and Hugs.
>
>*Foo> build' [] True :: [Bool]
>[True]
>*Foo> build' [] True False :: [Bool]
>[True,False]
>*Foo> build' [] True False False :: [Bool]
>[True,False,False]
>*Foo> build' [] 'a' 'b' 'c' 'd' 'e' :: [Char]
>"abcde"
>*Foo> build' [] (1::Int) :: [Int]
>[1]
>*Foo> build' [] (1::Int) (2::Int) :: [Int]
>[1,2]
>*Foo> build' [] (1::Int) (2::Int) (3::Int) :: [Int]
>[1,2,3]
>
>Note that the type annotation [Bool] etc. at the end is required: it
>is the delimiter of the list. Who would have thought that the type
>annotation can play the role of Nil...
>
>_______________________________________________
>Haskell mailing list
>Haskell at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell

------------
Graham Klyne
For email:
http://www.ninebynine.org/#Contact



More information about the Haskell-Cafe mailing list