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

oleg at pobox.com oleg at pobox.com
Wed Jun 2 19:38:26 EDT 2004


> Another question about overloading with type classes. It seems that these
> overloaded functions cannot be passed as higher-order function. Is that
> true? A higher order function can never be overloaded?
>
> In an example, how can I pass "build" as a function to another function
> that does some algorithm? (as the traditional Builder pattern in OO term)

A function that takes a polymorphic function and uses it
polymorphically has a higher-ranked type. Higher-ranked types cannot
be inferred (in general) and must be declared explicitly. In great
detail, this question is discussed in Ken Shan's survey
	http://www.eecs.harvard.edu/~ccshan/cs252/usage.pdf

As to your question: we can indeed pass 'build' to other
functions and use that argument as a function with the variable number of
arguments. Please see the function use_build in the code below. It
works both in GHC and Hugs.

P.S. Sorry I cannot reply directly to you: your ISP combined.com
blocks my mail.

{-# OPTIONS -fglasgow-exts #-}

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

--build :: forall r a. (BuildList a r) => a -> r
build x = build' [] x

-- build 'a' :: String
-- build 'a' 'b' :: String
-- build (1::Int) :: [Int]
-- build (1::Int) (2::Int) :: [Int]
-- build (1::Int) (2::Int) (3::Int) :: [Int]
  
-- polyvariadic functions -- functions with the variable number of
-- arguments -- are possible in Haskell after all...

-- Higher-ranked type: the signature is required
use_build::(forall r a. (BuildList a r) => a -> r) -> x -> x -> x -> x -> [[x]]
use_build bb a b c d =
  let t1 = bb a
      t2 = bb a b
      t3 = bb a b c
      t4 = bb a b c d
      t5 = bb a b c d a
  in [t1,t2,t3,t4,t5]
  
test = use_build build 'a' 'b' 'c' 'd'

-- *Foo> test
-- ["a","ab","abc","abcd","abcda"]


More information about the Haskell mailing list