> Hi,
>
> Printing the core one of my programs I see:
>
>   data Prelude;1() a =
>     Preluse;1() a
>
> What is this?  A single element tuple?  I didn't think Haskell had
> these.  My program has a monad similar to IO.  It appears these
> Prelude;1() things are created in the lambda lifted version of f1.
> Perhaps is it the parenthesis around (System m)?

Indeed Yhc has the 1 tuple. You can't write it in any programs but the compiler does generate things that use it. The reason is that classes are implemented as tuples of functions. For example

instance Eq MyData where
    x == y = False
    x /= y = True

f :: [MyData] -> MyData -> Bool
f ds d = elem d ds

elem :: Eq a => a -> [a] -> Bool
elem x [] = False
elem x (y:ys) | x == y = True
              | otherwise = elem x ys

this is compiled into something along the lines of

dict_Eq_MyData = ( eq_Eq_MyData, neq_Eq_MyData )
eq_Eq_MyData x y = False
neq_Eq_MyData x y = True

(==) (eq,neq) = eq

f ds d = elem dict_Eq_MyData d ds

elem dict x zs =
   case zs of
     [] -> False
     (:) y ys -> if ((==) dict) x y then True
                                    else elem dict x ys

The question is, what do you get when your class only has one method? The answer is a one-tuple.

dict_OneMethodClass_MyData = 1( ... )

I can't see specifically why your example would create one-tuples as arguments to f1. However you can bet that it is related to class dictionaries, since (as far as I know) that is the only way one-tuples can be created.

data Return a = Return a World
data System a = System (World -> Return a)
data World = World
instance Monad System where
  (System m) >>= k = System f1
    where
    f1 w = f2 w'
      where
      Return r w' = m w
      System f2 = k r

  return a = System (\ w -> Return a w)

This should compiled into something like:

dict_Monad_System =
  ( bind_Monad_System, seq_default, return_Monad_System, fail_default )

bind_Monad_System n k =
  case n of
    System m -> System (f1 m k)

return_Monad_System a = System (lambda1 a)

f1 m k w =
    let Return r w' = m w
        System f2 = k r
    in f2 w             

lambda1 a w = Return a w

At least if my hand lambda lifting is correct :) As I say, I can't see how you'd end up with a 1-tuple being passed to f1. Though if you paste the Yhc-Core that you get then I'd be happy to look at it :)

It's a bit difficult to correlate arguments of lifted lambdas to the
original source.  Is there a convention YHC uses for adding the extra
arguments to lifted lambdas?

Additional arguments tend to get added to the front of the function, if I remember correctly. Simply because it makes life easier with currying.

Hope that helps :)


Tom


P.S. you can make your 'System' type a 'newtype' rather than a 'data', which will make it a bit quicker :) Also your 'Return' type probably doesn't actually need to return the 'World' since there is no way it could sensibly be modified. Thus the following would probably be equivalent/better.

data Return a = Return a
newtype System = System (World -> Return a)

but note that the 'Return' type couldn't be a newtype because that would change the semantics from Lazy to Strict.
_______________________________________________
Yhc mailing list
Yhc@haskell.org
http://www.haskell.org/mailman/listinfo/yhc

Reply via email to