Use sharing in the Alternative instance of Maybe

Hello, When looking at the Alternative instance of Maybe I noticed that the <|> combinator doesn't share it's first argument when it could. So I propose to make the following change: instance Alternative Maybe where empty = Nothing - Nothing <|> p = p - Just x <|> _ = Just x + Nothing <|> r = r + l <|> _ = l Since this isn't a change in the API, I guess this doesn't need to go through the library submission process. http://hackage.haskell.org/trac/ghc/ticket/5699 Cheers, Bas

On Wed, Dec 14, 2011 at 1:49 PM, Bas van Dijk
Hello,
When looking at the Alternative instance of Maybe I noticed that the <|> combinator doesn't share it's first argument when it could. So I propose to make the following change:
instance Alternative Maybe where empty = Nothing - Nothing <|> p = p - Just x <|> _ = Just x + Nothing <|> r = r + l <|> _ = l
Since this isn't a change in the API, I guess this doesn't need to go through the library submission process.
http://hackage.haskell.org/trac/ghc/ticket/5699
Cheers,
Bas
+1 Out of curiosity, does this actually bypass an extra allocation, or is GHC smart enough to notice the possibility to share? Michael

On 14 December 2011 12:51, Michael Snoyman
Out of curiosity, does this actually bypass an extra allocation, or is GHC smart enough to notice the possibility to share?
With optimizations on, GHC seems to be smart enough. Since the optimized core of: plus1 Nothing r = r plus1 (Just x) _ = Just x Looks like: Maybe.plus1 = \ (@ a_acI) (ds_dcO :: Data.Maybe.Maybe a_acI) (r_abo :: Data.Maybe.Maybe a_acI) -> case ds_dcO of wild_X6 { Data.Maybe.Nothing -> r_abo; Data.Maybe.Just x_abp -> wild_X6 } Which is equivalent to the optimized core of: plus2 Nothing r = r plus2 l _ = l Which looks like: Maybe.plus2 = \ (@ t_acG) (ds_dcK :: Data.Maybe.Maybe t_acG) (r_abq :: Data.Maybe.Maybe t_acG) -> case ds_dcK of wild_X7 { Data.Maybe.Nothing -> r_abq; Data.Maybe.Just ipv_scU -> wild_X7 } With -O0 the core of plus1 looks like: Maybe.plus1 = \ (@ a_acG) (ds_dcM :: Data.Maybe.Maybe a_acG) (r_abm :: Data.Maybe.Maybe a_acG) -> case ds_dcM of _ { Data.Maybe.Nothing -> r_abm; Data.Maybe.Just x_abn -> Data.Maybe.Just @ a_acG x_abn } Cheers, Bas

On Wed, Dec 14, 2011 at 2:17 PM, Bas van Dijk
On 14 December 2011 12:51, Michael Snoyman
wrote: Out of curiosity, does this actually bypass an extra allocation, or is GHC smart enough to notice the possibility to share?
With optimizations on, GHC seems to be smart enough. Since the optimized core of:
plus1 Nothing r = r plus1 (Just x) _ = Just x
Looks like:
Maybe.plus1 = \ (@ a_acI) (ds_dcO :: Data.Maybe.Maybe a_acI) (r_abo :: Data.Maybe.Maybe a_acI) -> case ds_dcO of wild_X6 { Data.Maybe.Nothing -> r_abo; Data.Maybe.Just x_abp -> wild_X6 }
Which is equivalent to the optimized core of:
plus2 Nothing r = r plus2 l _ = l
Which looks like:
Maybe.plus2 = \ (@ t_acG) (ds_dcK :: Data.Maybe.Maybe t_acG) (r_abq :: Data.Maybe.Maybe t_acG) -> case ds_dcK of wild_X7 { Data.Maybe.Nothing -> r_abq; Data.Maybe.Just ipv_scU -> wild_X7 }
With -O0 the core of plus1 looks like:
Maybe.plus1 = \ (@ a_acG) (ds_dcM :: Data.Maybe.Maybe a_acG) (r_abm :: Data.Maybe.Maybe a_acG) -> case ds_dcM of _ { Data.Maybe.Nothing -> r_abm; Data.Maybe.Just x_abn -> Data.Maybe.Just @ a_acG x_abn }
Cheers,
Bas
Thank you, that's good to know. Michael

Am 14.12.2011 13:17, schrieb Bas van Dijk:
On 14 December 2011 12:51, Michael Snoyman
wrote: Out of curiosity, does this actually bypass an extra allocation, or is GHC smart enough to notice the possibility to share?
With optimizations on, GHC seems to be smart enough. Since the optimized core of:
plus1 Nothing r = r plus1 (Just x) _ = Just x
I suggest to directly write this using case: l <|> r = case l of Nothing -> r Just _ -> l C.
Looks like:
Maybe.plus1 = \ (@ a_acI) (ds_dcO :: Data.Maybe.Maybe a_acI) (r_abo :: Data.Maybe.Maybe a_acI) -> case ds_dcO of wild_X6 { Data.Maybe.Nothing -> r_abo; Data.Maybe.Just x_abp -> wild_X6 }
Which is equivalent to the optimized core of:
plus2 Nothing r = r plus2 l _ = l
Which looks like:
Maybe.plus2 = \ (@ t_acG) (ds_dcK :: Data.Maybe.Maybe t_acG) (r_abq :: Data.Maybe.Maybe t_acG) -> case ds_dcK of wild_X7 { Data.Maybe.Nothing -> r_abq; Data.Maybe.Just ipv_scU -> wild_X7 }
With -O0 the core of plus1 looks like:
Maybe.plus1 = \ (@ a_acG) (ds_dcM :: Data.Maybe.Maybe a_acG) (r_abm :: Data.Maybe.Maybe a_acG) -> case ds_dcM of _ { Data.Maybe.Nothing -> r_abm; Data.Maybe.Just x_abn -> Data.Maybe.Just @ a_acG x_abn }
Cheers,
Bas

Christian Maeder
Am 14.12.2011 13:17, schrieb Bas van Dijk:
On 14 December 2011 12:51, Michael Snoyman
wrote: Out of curiosity, does this actually bypass an extra allocation, or is GHC smart enough to notice the possibility to share?
With optimizations on, GHC seems to be smart enough. Since the optimized core of:
plus1 Nothing r = r plus1 (Just x) _ = Just x
I suggest to directly write this using case:
l <|> r = case l of Nothing -> r Just _ -> l
Why not plus1 Nothing r = r plus1 l@(Just x) _ = l or the equivalent written with <|>? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Am 15.12.2011 11:02, schrieb Jon Fairbairn:
Christian Maeder
writes: Am 14.12.2011 13:17, schrieb Bas van Dijk:
On 14 December 2011 12:51, Michael Snoyman
wrote: Out of curiosity, does this actually bypass an extra allocation, or is GHC smart enough to notice the possibility to share?
With optimizations on, GHC seems to be smart enough. Since the optimized core of:
plus1 Nothing r = r plus1 (Just x) _ = Just x
I suggest to directly write this using case:
l<|> r = case l of Nothing -> r Just _ -> l
Why not
plus1 Nothing r = r plus1 l@(Just x) _ = l
or the equivalent written with<|>?
Obviously, that's a matter of taste. I consider multiple fundefs as unnecessary syntactic sugar basically for pretty printed text books and maybe for teaching. In teaching, I find that beginners tend to be less able to use appropriate case expressions, though. (Also many list comprehensions are mere map or filter expressions) In a single fundef all arguments are uniquely named. It's clear when an argument is not used at all. In multiple fundefs you can get warnings for unused arguments for the particular case, which may be an advantage but als makes corresponding arguments look different. (Consistent naming of arguments is not enforced.) In fact, I would not even mind much if I had to write my definitions like: plus1 = \ l r -> case l of ... I claim, that multiple fundefs provoked this discussed non-sharing code (and the fall-through case). Cheers Christian
participants (4)
-
Bas van Dijk
-
Christian Maeder
-
Jon Fairbairn
-
Michael Snoyman