[Haskell] Re: how to write a list builder? fixpoint?
oleg at pobox.com
oleg at pobox.com
Tue Jun 1 21:18:03 EDT 2004
> 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...
More information about the Haskell
mailing list