Unit unboxed tuples

Tyson Whitehead twhitehead at gmail.com
Wed Jan 11 17:22:18 CET 2012


On January 11, 2012 08:41:04 Simon Marlow wrote:
> On 10/01/2012 16:18, Dan Doel wrote:
> > Does the difference have to do with unboxed types? For instance:
> >     foo :: () ->  Int#
> >     foo _ = foo ()
> >     bar :: () ->  (# Int# #)
> >     bar _ = (# foo () #)
> >     
> >     baz = case bar () of _ ->  5  -- 5
> >     quux = case foo () of _ ->  5 -- non-termination
> > 
> > Because in that case, either (# Int# #) is lifted, or the Int# is
> > effectively lifted when inside the unboxed tuple. The latter is a bit
> > of an oddity.
> 
> Unboxed types cannot be lifted, so in fact bar compiles to this:
> 
>    bar = \_ -> case foo () of x -> (# x #)
> 
> and both baz and quux diverge.

I tried both of these and it seems the lack of a constructor in the case 
expression results in the evaluation not being forced, so neither diverged.

Using a lifted type and adding a construct to the case did the trick though.

{-# LANGUAGE MagicHash, UnboxedTuples #-}

module Main where

import GHC.Exts

g :: () -> Int
g _ = g ()

f :: () -> (# Int #)
f _ = (# g () #)

main_baz :: IO ()
main_baz = putStrLn $ case g () of (I# _) -> "this one diverges"

main_quux :: IO ()
main_quux = putStrLn $ case f () of (# _ #) -> "this one doesn't diverge"

Cheers!  -Tyson



More information about the Glasgow-haskell-users mailing list