Whitespace only in nativeGen/RegAlloc/Linear/Main.hs
[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, unlimitedFuel, anyFuelLeft, oneLessFuel
10     , OptFuelState, initOptFuelState
11     , FuelConsumer, FuelUsingMonad, FuelState
12     , fuelGet, fuelSet, lastFuelPass, setFuelPass
13     , fuelExhausted, fuelDec1, tryWithFuel
14     , runFuelIO, runInfiniteFuelIO, 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 import Panic
25
26 import Compiler.Hoopl
27 import Compiler.Hoopl.GHC (getFuel, setFuel)
28
29 #include "HsVersions.h"
30
31
32 -- We limit the number of transactions executed using a record of flags
33 -- stored in an HscEnv. The flags store the name of the last optimization
34 -- pass and the amount of optimization fuel remaining.
35 data OptFuelState =
36   OptFuelState { pass_ref :: IORef String
37                , fuel_ref :: IORef OptimizationFuel
38                }
39 initOptFuelState :: IO OptFuelState
40 initOptFuelState =
41   do pass_ref' <- newIORef "unoptimized program"
42      fuel_ref' <- newIORef (tankFilledTo opt_Fuel)
43      return OptFuelState {pass_ref = pass_ref', fuel_ref = fuel_ref'}
44
45 type FuelConsumer a = OptimizationFuel -> (a, OptimizationFuel)
46
47 tankFilledTo :: Int -> OptimizationFuel
48 amountOfFuel :: OptimizationFuel -> Int
49
50 anyFuelLeft :: OptimizationFuel -> Bool
51 oneLessFuel :: OptimizationFuel -> OptimizationFuel
52 unlimitedFuel :: OptimizationFuel
53
54 newtype OptimizationFuel = OptimizationFuel Int
55   deriving Show
56
57 tankFilledTo = OptimizationFuel
58 amountOfFuel (OptimizationFuel f) = f
59
60 anyFuelLeft (OptimizationFuel f) = f > 0
61 oneLessFuel (OptimizationFuel f) = ASSERT (f > 0) (OptimizationFuel (f - 1))
62 unlimitedFuel = OptimizationFuel infiniteFuel
63
64 data FuelState = FuelState { fs_fuel :: OptimizationFuel, fs_lastpass :: String }
65 newtype FuelUniqSM a = FUSM { unFUSM :: FuelState -> UniqSM (a, FuelState) }
66
67 fuelConsumingPass :: String -> FuelConsumer a -> FuelUniqSM a
68 fuelConsumingPass name f = do setFuelPass name
69                               fuel <- fuelGet
70                               let (a, fuel') = f fuel
71                               fuelSet fuel'
72                               return a
73
74 runFuelIO :: OptFuelState -> FuelUniqSM a -> IO a
75 runFuelIO fs (FUSM f) =
76     do pass <- readIORef (pass_ref fs)
77        fuel <- readIORef (fuel_ref fs)
78        u    <- mkSplitUniqSupply 'u'
79        let (a, FuelState fuel' pass') = initUs_ u $ f (FuelState fuel pass)
80        writeIORef (pass_ref fs) pass'
81        writeIORef (fuel_ref fs) fuel'
82        return a
83
84 -- ToDo: Do we need the pass_ref when we are doing infinite fueld
85 -- transformations?
86 runInfiniteFuelIO :: OptFuelState -> FuelUniqSM a -> IO a
87 runInfiniteFuelIO fs (FUSM f) =
88     do pass <- readIORef (pass_ref fs)
89        u <- mkSplitUniqSupply 'u'
90        let (a, FuelState _ pass') = initUs_ u $ f (FuelState unlimitedFuel pass)
91        writeIORef (pass_ref fs) pass'
92        return a
93
94 instance Monad FuelUniqSM where
95   FUSM f >>= k = FUSM (\s -> f s >>= \(a, s') -> unFUSM (k a) s')
96   return a     = FUSM (\s -> return (a, s))
97
98 instance MonadUnique FuelUniqSM where
99     getUniqueSupplyM = liftUniq getUniqueSupplyM
100     getUniqueM       = liftUniq getUniqueM
101     getUniquesM      = liftUniq getUniquesM
102
103 liftUniq :: UniqSM x -> FuelUniqSM x
104 liftUniq x = FUSM (\s -> x >>= (\u -> return (u, s)))
105
106 class Monad m => FuelUsingMonad m where
107   fuelGet      :: m OptimizationFuel
108   fuelSet      :: OptimizationFuel -> m ()
109   lastFuelPass :: m String
110   setFuelPass  :: String -> m ()
111
112 fuelExhausted :: FuelUsingMonad m => m Bool
113 fuelExhausted = fuelGet >>= return . anyFuelLeft
114
115 fuelDec1 :: FuelUsingMonad m => m ()
116 fuelDec1 = fuelGet >>= fuelSet . oneLessFuel
117
118 tryWithFuel :: FuelUsingMonad m => a -> m (Maybe a)
119 tryWithFuel r = do f <- fuelGet
120                    if anyFuelLeft f then fuelSet (oneLessFuel f) >> return (Just r)
121                                     else return Nothing
122
123 instance FuelUsingMonad FuelUniqSM where
124   fuelGet          = extract fs_fuel
125   lastFuelPass     = extract fs_lastpass
126   fuelSet fuel     = FUSM (\s -> return ((), s { fs_fuel     = fuel }))
127   setFuelPass pass = FUSM (\s -> return ((), s { fs_lastpass = pass }))
128
129 extract :: (FuelState -> a) -> FuelUniqSM a
130 extract f = FUSM (\s -> return (f s, s))
131
132 instance FuelMonad FuelUniqSM where
133   getFuel = liftM amountOfFuel fuelGet
134   setFuel = fuelSet . tankFilledTo
135
136 -- Don't bother to checkpoint the unique supply; it doesn't matter
137 instance CheckpointMonad FuelUniqSM where
138     type Checkpoint FuelUniqSM = FuelState
139     checkpoint = FUSM $ \fuel -> return (fuel, fuel) 
140     restart fuel = FUSM $ \_ -> return ((), fuel)
141