fix DEBUG build
[ghc-hetmet.git] / compiler / cmm / OptimizationFuel.hs
1 {-# LANGUAGE TypeFamilies #-}
2 -- | Optimisation fuel is used to control the amount of work the optimiser does.
3 --
4 -- Every optimisation step consumes a certain amount of fuel and stops when
5 -- it runs out of fuel.  This can be used e.g. to debug optimiser bugs: Run
6 -- the optimiser with varying amount of fuel to find out the exact number of
7 -- steps where a bug is introduced in the output.
8 module OptimizationFuel
9     ( OptimizationFuel, amountOfFuel, tankFilledTo, anyFuelLeft, oneLessFuel
10     , OptFuelState, initOptFuelState
11     , FuelConsumer, FuelUsingMonad, FuelState
12     , fuelGet, fuelSet, lastFuelPass, setFuelPass
13     , fuelExhausted, fuelDec1, tryWithFuel
14     , runFuelIO, fuelConsumingPass
15     , FuelUniqSM
16     , liftUniq
17     )
18 where
19
20 import Data.IORef
21 import Control.Monad
22 import StaticFlags (opt_Fuel)
23 import UniqSupply
24 #ifdef DEBUG
25 import Panic
26 #endif
27
28 import Compiler.Hoopl
29 import Compiler.Hoopl.GHC (getFuel, setFuel)
30
31 #include "HsVersions.h"
32
33
34 -- We limit the number of transactions executed using a record of flags
35 -- stored in an HscEnv. The flags store the name of the last optimization
36 -- pass and the amount of optimization fuel remaining.
37 data OptFuelState =
38   OptFuelState { pass_ref :: IORef String
39                , fuel_ref :: IORef OptimizationFuel
40                }
41 initOptFuelState :: IO OptFuelState
42 initOptFuelState =
43   do pass_ref' <- newIORef "unoptimized program"
44      fuel_ref' <- newIORef (tankFilledTo opt_Fuel)
45      return OptFuelState {pass_ref = pass_ref', fuel_ref = fuel_ref'}
46
47 type FuelConsumer a = OptimizationFuel -> (a, OptimizationFuel)
48
49 tankFilledTo :: Int -> OptimizationFuel
50 amountOfFuel :: OptimizationFuel -> Int
51
52 anyFuelLeft :: OptimizationFuel -> Bool
53 oneLessFuel :: OptimizationFuel -> OptimizationFuel
54
55 #ifdef DEBUG
56 newtype OptimizationFuel = OptimizationFuel Int
57   deriving Show
58
59 tankFilledTo = OptimizationFuel
60 amountOfFuel (OptimizationFuel f) = f
61
62 anyFuelLeft (OptimizationFuel f) = f > 0
63 oneLessFuel (OptimizationFuel f) = ASSERT (f > 0) (OptimizationFuel (f - 1))
64 #else
65 -- type OptimizationFuel = State# () -- would like this, but it won't work
66 data OptimizationFuel = OptimizationFuel
67   deriving Show
68 tankFilledTo _ = OptimizationFuel
69 amountOfFuel _ = maxBound
70
71 anyFuelLeft _ = True
72 oneLessFuel _ = OptimizationFuel
73 #endif
74
75 data FuelState = FuelState { fs_fuel :: OptimizationFuel, fs_lastpass :: String }
76 newtype FuelUniqSM a = FUSM { unFUSM :: FuelState -> UniqSM (a, FuelState) }
77
78 fuelConsumingPass :: String -> FuelConsumer a -> FuelUniqSM a
79 fuelConsumingPass name f = do setFuelPass name
80                               fuel <- fuelGet
81                               let (a, fuel') = f fuel
82                               fuelSet fuel'
83                               return a
84
85 runFuelIO :: OptFuelState -> FuelUniqSM a -> IO a
86 runFuelIO fs (FUSM f) =
87     do pass <- readIORef (pass_ref fs)
88        fuel <- readIORef (fuel_ref fs)
89        u    <- mkSplitUniqSupply 'u'
90        let (a, FuelState fuel' pass') = initUs_ u $ f (FuelState fuel pass)
91        writeIORef (pass_ref fs) pass'
92        writeIORef (fuel_ref fs) fuel'
93        return a
94
95 instance Monad FuelUniqSM where
96   FUSM f >>= k = FUSM (\s -> f s >>= \(a, s') -> unFUSM (k a) s')
97   return a     = FUSM (\s -> return (a, s))
98
99 instance MonadUnique FuelUniqSM where
100     getUniqueSupplyM = liftUniq getUniqueSupplyM
101     getUniqueM       = liftUniq getUniqueM
102     getUniquesM      = liftUniq getUniquesM
103
104 liftUniq :: UniqSM x -> FuelUniqSM x
105 liftUniq x = FUSM (\s -> x >>= (\u -> return (u, s)))
106
107 class Monad m => FuelUsingMonad m where
108   fuelGet      :: m OptimizationFuel
109   fuelSet      :: OptimizationFuel -> m ()
110   lastFuelPass :: m String
111   setFuelPass  :: String -> m ()
112
113 fuelExhausted :: FuelUsingMonad m => m Bool
114 fuelExhausted = fuelGet >>= return . anyFuelLeft
115
116 fuelDec1 :: FuelUsingMonad m => m ()
117 fuelDec1 = fuelGet >>= fuelSet . oneLessFuel
118
119 tryWithFuel :: FuelUsingMonad m => a -> m (Maybe a)
120 tryWithFuel r = do f <- fuelGet
121                    if anyFuelLeft f then fuelSet (oneLessFuel f) >> return (Just r)
122                                     else return Nothing
123
124 instance FuelUsingMonad FuelUniqSM where
125   fuelGet          = extract fs_fuel
126   lastFuelPass     = extract fs_lastpass
127   fuelSet fuel     = FUSM (\s -> return ((), s { fs_fuel     = fuel }))
128   setFuelPass pass = FUSM (\s -> return ((), s { fs_lastpass = pass }))
129
130 extract :: (FuelState -> a) -> FuelUniqSM a
131 extract f = FUSM (\s -> return (f s, s))
132
133 instance FuelMonad FuelUniqSM where
134   getFuel = liftM amountOfFuel fuelGet
135   setFuel = fuelSet . tankFilledTo
136
137 -- Don't bother to checkpoint the unique supply; it doesn't matter
138 instance CheckpointMonad FuelUniqSM where
139     type Checkpoint FuelUniqSM = FuelState
140     checkpoint = FUSM $ \fuel -> return (fuel, fuel) 
141     restart fuel = FUSM $ \_ -> return ((), fuel)
142