module GHC.RTS.Events.Analysis
( Machine (..)
, validate
, validates
, simulate
, Profile (..)
, profile
, profileIndexed
, profileRouted
, extractIndexed
, refineM
, profileM
, indexM
, toList
, toMaybe
, Process (..)
, routeM
)
where
import GHC.RTS.Events
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
data Machine s i = Machine
{ initial :: s
, final :: s -> Bool
, alpha :: i -> Bool
, delta :: s -> i -> Maybe s
}
step :: Machine s i -> s -> i -> Either (s, i) s
step m s i
| final m s = Right s
| alpha m i = case delta m s i of
Just s' -> Right s'
Nothing -> Left (s, i)
| otherwise = Right s
validate :: Machine s i -> [i] -> Either (s, i) s
validate m = foldl (>>=) (Right (initial m)) . map (flip (step m))
validates :: Machine s i -> [i] -> [Either (s, i) s]
validates m = scanl (>>=) (Right (initial m)) . map (flip (step m))
data Process e a
= Done
| Fail e
| Prod a (Process e a)
deriving Show
toList :: Process e a -> [a]
toList (Fail _) = []
toList Done = []
toList (Prod a as) = a : toList as
toMaybe :: Process e a -> Maybe e
toMaybe (Fail e) = Just e
toMaybe Done = Nothing
toMaybe (Prod _ as) = toMaybe as
analyse :: Machine s i
-> (s -> i -> Maybe o)
-> [i]
-> Process (s, i) o
analyse machine extract = go (initial machine)
where
go _ [] = Done
go s (i:is)
| final machine s = Done
| alpha machine i =
case delta machine s i of
Nothing -> Fail (s, i)
Just s' ->
case extract s i of
Nothing -> go s' is
Just o -> Prod o (go s' is)
| otherwise = go s is
refineM :: (i -> j) -> Machine s j -> Machine s i
refineM refine machine = Machine
{ initial = initial machine
, final = final machine
, alpha = alpha machine . refine
, delta = \s -> delta machine s . refine
}
simulate :: Machine s i -> [i] -> Process (s, i) (s, i)
simulate machine = analyse machine (\s i -> delta machine s i >>= \s' -> return (s', i))
data Profile s = Profile
{ profileState :: s
, profileTime :: Timestamp
} deriving (Show)
profileM :: Ord s
=> (i -> Timestamp)
-> Machine s i
-> Machine (Profile s) i
profileM timer machine = Machine
{ initial = Profile (initial machine) 0
, final = final machine . profileState
, alpha = alpha machine
, delta = profileMDelta
}
where
profileMDelta (Profile s _) i = do
s' <- delta machine s i
return $ Profile s' (timer i)
extractProfile :: (i -> Timestamp)
-> Profile s
-> i
-> Maybe (s, Timestamp, Timestamp)
extractProfile timer p i = Just (profileState p, profileTime p, timer i - profileTime p)
profile :: (Ord s, Eq s)
=> Machine s i
-> (i -> Timestamp)
-> [i]
-> Process (Profile s, i) (s, Timestamp, Timestamp)
profile machine timer =
analyse (profileM timer machine)
(extractProfile timer)
profileIndexed :: (Ord k, Ord s, Eq s)
=> Machine s i
-> (i -> Maybe k)
-> (i -> Timestamp)
-> [i]
-> Process (Map k (Profile s), i) (k, (s, Timestamp, Timestamp))
profileIndexed machine index timer =
analyse (indexM index (profileM timer machine))
(extractIndexed (extractProfile timer) index)
extractIndexed :: Ord k => (s -> i -> Maybe o) -> (i -> Maybe k) -> (Map k s -> i -> Maybe (k, o))
extractIndexed extract index m i = do
k <- index i
s <- M.lookup k m
o <- extract s i
return (k, o)
indexM :: Ord k
=> (i -> Maybe k)
-> Machine s i
-> Machine (Map k s) i
indexM index machine = Machine
{ initial = M.empty
, final = indexMFinal
, alpha = indexMAlpha
, delta = indexMDelta
}
where
indexMFinal = const False
indexMAlpha = alpha machine
indexMDelta m i = do
k <- index i
let state = fromMaybe (initial machine) (M.lookup k m)
state' <- delta machine state i
return $ M.insert k state' m
profileRouted :: (Ord k, Ord s, Eq s, Eq r)
=> Machine s i
-> Machine r i
-> (r -> i -> Maybe k)
-> (i -> Timestamp)
-> [i]
-> Process ((Map k (Profile s), r), i) (k, (s, Timestamp, Timestamp))
profileRouted machine router index timer =
analyse (routeM router index (profileM timer machine))
(extractRouted (extractProfile timer) index)
extractRouted :: Ord k => (s -> i -> Maybe o) -> (r -> i -> Maybe k) -> ((Map k s, r) -> i -> Maybe (k, o))
extractRouted extract index (m, r) i = do
k <- index r i
s <- M.lookup k m
o <- extract s i
return (k, o)
routeM :: (Ord k)
=> Machine r i
-> (r -> i -> Maybe k)
-> Machine s i
-> Machine (Map k s, r) i
routeM router index machine = Machine
{ initial = (M.empty, initial router)
, final = routeMFinal
, alpha = routeMAlpha
, delta = routeMDelta
}
where
routeMFinal = const False
routeMAlpha i = alpha router i || alpha machine i
routeMDelta (m, r) i = do
r' <- if alpha router i
then delta router r i
else return r
m' <- if alpha machine i
then case index r' i of
Just k -> do
s' <- delta machine (fromMaybe (initial machine) (M.lookup k m)) i
return $ M.insert k s' m
Nothing -> return m
else return m
return (m', r')