Hi !

Can anyone tell me whether it's possible to force Haskell to evaluate an
expression strict ? Consider the following Haskell program:

---------------------------------------------------------------------------

module Mergesort where

data Sequ a = Empty
            | Cons (a,Sequ a)

mergesort :: ((a, a) -> Bool) -> (Sequ a) -> Sequ a
mergesort(leq)(Empty)=Empty
mergesort(leq)(Cons(a,Empty))=Cons(a,Empty)
mergesort(leq)(Cons(a,Cons(b,s)))=
   merge(leq)(
     mergesort(leq)(ext1(Cons(a,Cons(b,s)))),
     mergesort(leq)(ext2(Cons(a,Cons(b,s)))))

merge :: ((a, a) -> Bool) -> (Sequ a, Sequ a) -> Sequ a
merge(leq)(s,Empty)=s
merge(leq)(Empty,t)=t
merge(leq)(Cons(a,s),Cons(b,t)) | leq(b,a)
   = Cons(b,merge(leq)(Cons(a,s),t))
merge(leq)(Cons(a,s),Cons(b,t)) | not(leq(b,a))
   = Cons(a,merge(leq)(s,Cons(b,t)))

ext1 :: (Sequ a) -> Sequ a
ext1(Empty)=Empty
ext1(Cons(a,Empty))=Cons(a,Empty)
ext1(Cons(a,Cons(b,s)))=Cons(a,ext1(s))

ext2 :: (Sequ a) -> Sequ a
ext2(Empty)=Empty
ext2(Cons(a,Empty))=Empty
ext2(Cons(a,Cons(b,s)))=Cons(b,ext2(s))

foo :: ((a,a)->Bool) -> ((a,a)->Bool)
foo x = foo x

bott :: (a,a) -> Bool
bott=foo(\(x,y)->True)


dummya=mergesort(bott)(Cons("xyz",Empty))
dummyb=mergesort(bott)(Empty)

dummyc=mergesort(bott)(Cons("abc",Cons("xyz",Empty)))

---------------------------------------------------------------------------

Of course, due to the lazy evaluation of haskell, dummya and dummyb evaluate
to Cons("val", Empty) and Empty, resp., while dummyc evaluates to _!_ (bottom).
However, Haskell is used as the target language of the specification
language SPECTRUM, i.e. a distinguished substyle of SPECTRUM can be translated
into an executable Haskell program. SPECTRUM allows the specification of
non-strict functions, so a lazy functional language as target language has been
choosen. However, of course it would be desirable for the functions that were
specified to be strict that their Haskell counterpart behaves strict, too.
If the typevariable "a" would be restricted to range over the typeclass Eq,
the dirty trick of adding the guard

                n==n

to the definition of mergesort could be used. But this is not possible if
this restriction does not apply.

Please send the reply directly to my email-adress, because I don't subscribe
the mailing list up to now. I would also ask you to add me to your
mailing list.

Thanks in advance

Cornel               ([EMAIL PROTECTED])





Reply via email to