[GHC] #12620: Allow the user to prevent floating and CSE

GHC ghc-devs at haskell.org
Thu Oct 6 01:34:23 UTC 2016


#12620: Allow the user to prevent floating and CSE
-------------------------------------+-------------------------------------
        Reporter:  nomeata           |                Owner:
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #9520, #8457      |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by edsko):

 I take your point re `<expensive>` though. After it, it's common enough to
 have something like

 {{{#!hs
 x <- someConduit
 if <expensive>
   then thisConduit
   else thatConduit
 }}}

 However, I still think we need something more compositional than
 `oneShot`. As michaelt_ points out on Reddit,

 {{{#!hs
 module Main (main) where
 import GHC.Magic

 data Sink = Await (Maybe Char -> Sink) | Done Int

 countFrom :: Int -> Sink
 countFrom n = let k = countFrom $! n + 1
               in Await $ oneShot $ \mi -> case mi of
                   Nothing ->  Done n
                   Just _  -> k

 feedFrom :: Int -> Sink -> IO ()
 feedFrom _ (Done n)  = print n
 feedFrom 0 (Await f) = feedFrom 0       (case f $ Nothing of  a -> a)
 feedFrom n (Await f) = feedFrom (n - 1) (case f $ Just 'A' of a -> a)

 main :: IO ()
 main = let a = feedFrom 10000000 (countFrom 0) in a >> a
 }}}

 doesn't have a space leak. If `oneShot` was compositional, that would be
 awesome; we could put the `oneShot` in the library and then forget about
 it. Sadly, though perhaps not unexpectedly, this variation _does_ have a
 space leak again:

 {{{#!hs
 module Main (main) where
 import GHC.Magic

 data Sink = Await (Maybe Char -> Sink) | Done Int

 await :: (Maybe Char -> Sink) -> Sink
 {-# NOINLINE await #-}
 await f = Await (oneShot f)

 countFrom :: Int -> Sink
 countFrom n = let k = countFrom $! n + 1
               in await $ \mi -> case mi of
                   Nothing ->  Done n
                   Just _  -> k

 feedFrom :: Int -> Sink -> IO ()
 feedFrom _ (Done n)  = print n
 feedFrom 0 (Await f) = feedFrom 0       (case f $ Nothing of  a -> a)
 feedFrom n (Await f) = feedFrom (n - 1) (case f $ Just 'A' of a -> a)

 main :: IO ()
 main = let a = feedFrom 10000000 (countFrom 0) in a >> a
 }}}

 Insisting that users write

 {{{#!hs
 await >>= oneShot (\mi -> ...)
 }}}

 instead of

 {{{#!hs
 do mi <- await ; ...
 }}}

 doesn't seem like a good solution.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12620#comment:27>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list