Language extension idea (was Re: [Haskell-cafe] Re: OCaml list sees...)

Tom Pledger tpledger at ihug.co.nz
Sat Oct 9 04:08:16 EDT 2004


MR K P SCHUPKE wrote:
[...]

>I dont see why you cannot change the "implementation"
>of lists without changing the "interface"... Good old lists will
>behave like good old lists - just the implementation would try
>and take advantage of blocking of the data wherever possible.
>
>Perhaps a pragma to change the implementation of lists would ne
>be a sensible way of selecting the implementation.
>

A phrase of the form "an X to change the implementation of Y" makes me 
think of X="instance" and Y="a class".

Something along these lines:

    class List l a | l -> a where
        nil :: l
        cons :: a -> l -> l

But that's not of much use, because there isn't a class method to 
recover the elements of a List. We could add more methods (corresponding 
to null, head, and tail), but perhaps it would be neater if class 
members could be data constructors?

    import Prelude hiding (null, head, tail)
    import Data.PackedString

    class List l a | l -> a where
        -- note the capital letters in Nil and Cons
        Nil  :: l
        Cons :: a -> l -> l

    instance List PackedString Char where
        -- construction
        Nil  = nilPS
        Cons = consPS
        -- pattern matching; not sure of a good syntax for this,
        -- but try reusing the reserved word 'case' as a function name
        case ifNil ifCons ps
            = if nilPS ps then ifNil else ifCons (headPS ps) (tailPS ps)
        -- cf. Prelude.maybe, Prelude.either

    instance List [a] a where
        -- construction
        Nil  = []
        Cons = (:)
        -- pattern matching
        case ifNil ifCons []     = ifNil
        case ifNil ifCons (x:xs) = ifCons x xs

    null :: (List l a) => l -> Bool
    null Nil = True
    null _   = False

    head :: (List l a) => l -> a
    head (Cons x _) = x

    tail :: (List l a) => l -> l
    tail (Cons _ xs) = xs

Here are a few more questions which I'm not (yet) qualified to answer:

Would such a language extension be messy to implement? Or would it 
perhaps fit neatly with current dictionary-passing schemes?

Would there be other major uses for it, besides a class of list-shaped 
things? (Remember the first message in the "OCaml list sees..." thread? 
Part of the cited text was "Haskell strings are lists of characters 
[...] It's annoying that strings aren't normally processed this way in 
OCaml". I, like other posters, wonder whether Haskell could get the best 
of both worlds.)

Does Template Haskell, which I haven't studied yet, already do something 
equivalent?

Regards,
Tom




More information about the Haskell-Cafe mailing list