[GHC] #13698: Add a more complete example for the special SPEC argument to the user guide
GHC
ghc-devs at haskell.org
Sun May 14 18:05:47 UTC 2017
#13698: Add a more complete example for the special SPEC argument to the user guide
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: task | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: newcomer | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets: SpecConstr
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
In the section for `-fspec-constr` in the user guide there is an example
of how to use `SPEC` to force a loop to be unrolled by spec constr.
However, this argument doesn't do anything until `foldl` is called with a
specific argument. It wasn't clear to me exactly how this worked as the
example was incomplete. Below is a complete file which shows how the
optimisation unrolls the list completely such that `res2 = 6` in core.
{{{
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ExistentialQuantification #-}
module Foo where
import GHC.Types
data Stream a = forall s.
Stream !(s -> Step a s) -- a stepper function
!s -- an initial state
data Step a s = Yield a !s
| Skip !s
| Done
s2 = Stream s [1,2,3]
s [] = Done
s (x:xs) = Yield x xs
res2 = Foo.foldl (+) 0 s2
foldl :: (a -> b -> a) -> a -> Stream b -> a
{-# INLINE foldl #-}
foldl f z (Stream step s) = foldl_loop SPEC z s
where
foldl_loop !sPEC z s = case step s of
Yield x s' -> foldl_loop sPEC (f z x) s'
Skip s' -> foldl_loop sPEC z s'
Done -> z
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13698>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list