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
{ forall s i. Machine s i -> s
initial :: s
, forall s i. Machine s i -> s -> Bool
final :: s -> Bool
, forall s i. Machine s i -> i -> Bool
alpha :: i -> Bool
, forall s i. Machine s i -> s -> i -> Maybe s
delta :: s -> i -> Maybe s
}
step :: Machine s i -> s -> i -> Either (s, i) s
step :: forall s i. Machine s i -> s -> i -> Either (s, i) s
step Machine s i
m s
s i
i
| forall s i. Machine s i -> s -> Bool
final Machine s i
m s
s = forall a b. b -> Either a b
Right s
s
| forall s i. Machine s i -> i -> Bool
alpha Machine s i
m i
i = case forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s i
m s
s i
i of
Just s
s' -> forall a b. b -> Either a b
Right s
s'
Maybe s
Nothing -> forall a b. a -> Either a b
Left (s
s, i
i)
| Bool
otherwise = forall a b. b -> Either a b
Right s
s
validate :: Machine s i -> [i] -> Either (s, i) s
validate :: forall s i. Machine s i -> [i] -> Either (s, i) s
validate Machine s i
m = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(>>=) (forall a b. b -> Either a b
Right (forall s i. Machine s i -> s
initial Machine s i
m)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall s i. Machine s i -> s -> i -> Either (s, i) s
step Machine s i
m))
validates :: Machine s i -> [i] -> [Either (s, i) s]
validates :: forall s i. Machine s i -> [i] -> [Either (s, i) s]
validates Machine s i
m = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(>>=) (forall a b. b -> Either a b
Right (forall s i. Machine s i -> s
initial Machine s i
m)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall s i. Machine s i -> s -> i -> Either (s, i) s
step Machine s i
m))
data Process e a
= Done
| Fail e
| Prod a (Process e a)
deriving Int -> Process e a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall e a. (Show e, Show a) => Int -> Process e a -> ShowS
forall e a. (Show e, Show a) => [Process e a] -> ShowS
forall e a. (Show e, Show a) => Process e a -> String
showList :: [Process e a] -> ShowS
$cshowList :: forall e a. (Show e, Show a) => [Process e a] -> ShowS
show :: Process e a -> String
$cshow :: forall e a. (Show e, Show a) => Process e a -> String
showsPrec :: Int -> Process e a -> ShowS
$cshowsPrec :: forall e a. (Show e, Show a) => Int -> Process e a -> ShowS
Show
toList :: Process e a -> [a]
toList :: forall e a. Process e a -> [a]
toList (Fail e
_) = []
toList Process e a
Done = []
toList (Prod a
a Process e a
as) = a
a forall a. a -> [a] -> [a]
: forall e a. Process e a -> [a]
toList Process e a
as
toMaybe :: Process e a -> Maybe e
toMaybe :: forall e a. Process e a -> Maybe e
toMaybe (Fail e
e) = forall a. a -> Maybe a
Just e
e
toMaybe Process e a
Done = forall a. Maybe a
Nothing
toMaybe (Prod a
_ Process e a
as) = forall e a. Process e a -> Maybe e
toMaybe Process e a
as
analyse :: Machine s i
-> (s -> i -> Maybe o)
-> [i]
-> Process (s, i) o
analyse :: forall s i o.
Machine s i -> (s -> i -> Maybe o) -> [i] -> Process (s, i) o
analyse Machine s i
machine s -> i -> Maybe o
extract = s -> [i] -> Process (s, i) o
go (forall s i. Machine s i -> s
initial Machine s i
machine)
where
go :: s -> [i] -> Process (s, i) o
go s
_ [] = forall e a. Process e a
Done
go s
s (i
i:[i]
is)
| forall s i. Machine s i -> s -> Bool
final Machine s i
machine s
s = forall e a. Process e a
Done
| forall s i. Machine s i -> i -> Bool
alpha Machine s i
machine i
i =
case forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s i
machine s
s i
i of
Maybe s
Nothing -> forall e a. e -> Process e a
Fail (s
s, i
i)
Just s
s' ->
case s -> i -> Maybe o
extract s
s i
i of
Maybe o
Nothing -> s -> [i] -> Process (s, i) o
go s
s' [i]
is
Just o
o -> forall e a. a -> Process e a -> Process e a
Prod o
o (s -> [i] -> Process (s, i) o
go s
s' [i]
is)
| Bool
otherwise = s -> [i] -> Process (s, i) o
go s
s [i]
is
refineM :: (i -> j) -> Machine s j -> Machine s i
refineM :: forall i j s. (i -> j) -> Machine s j -> Machine s i
refineM i -> j
refine Machine s j
machine = Machine
{ initial :: s
initial = forall s i. Machine s i -> s
initial Machine s j
machine
, final :: s -> Bool
final = forall s i. Machine s i -> s -> Bool
final Machine s j
machine
, alpha :: i -> Bool
alpha = forall s i. Machine s i -> i -> Bool
alpha Machine s j
machine forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> j
refine
, delta :: s -> i -> Maybe s
delta = \s
s -> forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s j
machine s
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> j
refine
}
simulate :: Machine s i -> [i] -> Process (s, i) (s, i)
simulate :: forall s i. Machine s i -> [i] -> Process (s, i) (s, i)
simulate Machine s i
machine = forall s i o.
Machine s i -> (s -> i -> Maybe o) -> [i] -> Process (s, i) o
analyse Machine s i
machine (\s
s i
i -> forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s i
machine s
s i
i forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \s
s' -> forall (m :: * -> *) a. Monad m => a -> m a
return (s
s', i
i))
data Profile s = Profile
{ forall s. Profile s -> s
profileState :: s
, forall s. Profile s -> Timestamp
profileTime :: Timestamp
} deriving (Int -> Profile s -> ShowS
forall s. Show s => Int -> Profile s -> ShowS
forall s. Show s => [Profile s] -> ShowS
forall s. Show s => Profile s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Profile s] -> ShowS
$cshowList :: forall s. Show s => [Profile s] -> ShowS
show :: Profile s -> String
$cshow :: forall s. Show s => Profile s -> String
showsPrec :: Int -> Profile s -> ShowS
$cshowsPrec :: forall s. Show s => Int -> Profile s -> ShowS
Show)
profileM :: Ord s
=> (i -> Timestamp)
-> Machine s i
-> Machine (Profile s) i
profileM :: forall s i.
Ord s =>
(i -> Timestamp) -> Machine s i -> Machine (Profile s) i
profileM i -> Timestamp
timer Machine s i
machine = Machine
{ initial :: Profile s
initial = forall s. s -> Timestamp -> Profile s
Profile (forall s i. Machine s i -> s
initial Machine s i
machine) Timestamp
0
, final :: Profile s -> Bool
final = forall s i. Machine s i -> s -> Bool
final Machine s i
machine forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Profile s -> s
profileState
, alpha :: i -> Bool
alpha = forall s i. Machine s i -> i -> Bool
alpha Machine s i
machine
, delta :: Profile s -> i -> Maybe (Profile s)
delta = Profile s -> i -> Maybe (Profile s)
profileMDelta
}
where
profileMDelta :: Profile s -> i -> Maybe (Profile s)
profileMDelta (Profile s
s Timestamp
_) i
i = do
s
s' <- forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s i
machine s
s i
i
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s. s -> Timestamp -> Profile s
Profile s
s' (i -> Timestamp
timer i
i)
extractProfile :: (i -> Timestamp)
-> Profile s
-> i
-> Maybe (s, Timestamp, Timestamp)
i -> Timestamp
timer Profile s
p i
i = forall a. a -> Maybe a
Just (forall s. Profile s -> s
profileState Profile s
p, forall s. Profile s -> Timestamp
profileTime Profile s
p, i -> Timestamp
timer i
i forall a. Num a => a -> a -> a
- forall s. Profile s -> Timestamp
profileTime Profile s
p)
profile :: (Ord s, Eq s)
=> Machine s i
-> (i -> Timestamp)
-> [i]
-> Process (Profile s, i) (s, Timestamp, Timestamp)
profile :: forall s i.
(Ord s, Eq s) =>
Machine s i
-> (i -> Timestamp)
-> [i]
-> Process (Profile s, i) (s, Timestamp, Timestamp)
profile Machine s i
machine i -> Timestamp
timer =
forall s i o.
Machine s i -> (s -> i -> Maybe o) -> [i] -> Process (s, i) o
analyse (forall s i.
Ord s =>
(i -> Timestamp) -> Machine s i -> Machine (Profile s) i
profileM i -> Timestamp
timer Machine s i
machine)
(forall i s.
(i -> Timestamp)
-> Profile s -> i -> Maybe (s, Timestamp, Timestamp)
extractProfile i -> Timestamp
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 :: forall k s i.
(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 s i
machine i -> Maybe k
index i -> Timestamp
timer =
forall s i o.
Machine s i -> (s -> i -> Maybe o) -> [i] -> Process (s, i) o
analyse (forall k i s.
Ord k =>
(i -> Maybe k) -> Machine s i -> Machine (Map k s) i
indexM i -> Maybe k
index (forall s i.
Ord s =>
(i -> Timestamp) -> Machine s i -> Machine (Profile s) i
profileM i -> Timestamp
timer Machine s i
machine))
(forall k s i o.
Ord k =>
(s -> i -> Maybe o)
-> (i -> Maybe k) -> Map k s -> i -> Maybe (k, o)
extractIndexed (forall i s.
(i -> Timestamp)
-> Profile s -> i -> Maybe (s, Timestamp, Timestamp)
extractProfile i -> Timestamp
timer) i -> Maybe k
index)
extractIndexed :: Ord k => (s -> i -> Maybe o) -> (i -> Maybe k) -> (Map k s -> i -> Maybe (k, o))
s -> i -> Maybe o
extract i -> Maybe k
index Map k s
m i
i = do
k
k <- i -> Maybe k
index i
i
s
s <- forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k Map k s
m
o
o <- s -> i -> Maybe o
extract s
s i
i
forall (m :: * -> *) a. Monad m => a -> m a
return (k
k, o
o)
indexM :: Ord k
=> (i -> Maybe k)
-> Machine s i
-> Machine (Map k s) i
indexM :: forall k i s.
Ord k =>
(i -> Maybe k) -> Machine s i -> Machine (Map k s) i
indexM i -> Maybe k
index Machine s i
machine = Machine
{ initial :: Map k s
initial = forall k a. Map k a
M.empty
, final :: Map k s -> Bool
final = forall {b}. b -> Bool
indexMFinal
, alpha :: i -> Bool
alpha = i -> Bool
indexMAlpha
, delta :: Map k s -> i -> Maybe (Map k s)
delta = Map k s -> i -> Maybe (Map k s)
indexMDelta
}
where
indexMFinal :: b -> Bool
indexMFinal = forall a b. a -> b -> a
const Bool
False
indexMAlpha :: i -> Bool
indexMAlpha = forall s i. Machine s i -> i -> Bool
alpha Machine s i
machine
indexMDelta :: Map k s -> i -> Maybe (Map k s)
indexMDelta Map k s
m i
i = do
k
k <- i -> Maybe k
index i
i
let state :: s
state = forall a. a -> Maybe a -> a
fromMaybe (forall s i. Machine s i -> s
initial Machine s i
machine) (forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k Map k s
m)
s
state' <- forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s i
machine s
state i
i
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
k s
state' Map k s
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 :: forall k s r i.
(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 s i
machine Machine r i
router r -> i -> Maybe k
index i -> Timestamp
timer =
forall s i o.
Machine s i -> (s -> i -> Maybe o) -> [i] -> Process (s, i) o
analyse (forall k r i s.
Ord k =>
Machine r i
-> (r -> i -> Maybe k) -> Machine s i -> Machine (Map k s, r) i
routeM Machine r i
router r -> i -> Maybe k
index (forall s i.
Ord s =>
(i -> Timestamp) -> Machine s i -> Machine (Profile s) i
profileM i -> Timestamp
timer Machine s i
machine))
(forall k s i o r.
Ord k =>
(s -> i -> Maybe o)
-> (r -> i -> Maybe k) -> (Map k s, r) -> i -> Maybe (k, o)
extractRouted (forall i s.
(i -> Timestamp)
-> Profile s -> i -> Maybe (s, Timestamp, Timestamp)
extractProfile i -> Timestamp
timer) r -> i -> Maybe k
index)
extractRouted :: Ord k => (s -> i -> Maybe o) -> (r -> i -> Maybe k) -> ((Map k s, r) -> i -> Maybe (k, o))
s -> i -> Maybe o
extract r -> i -> Maybe k
index (Map k s
m, r
r) i
i = do
k
k <- r -> i -> Maybe k
index r
r i
i
s
s <- forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k Map k s
m
o
o <- s -> i -> Maybe o
extract s
s i
i
forall (m :: * -> *) a. Monad m => a -> m a
return (k
k, o
o)
routeM :: (Ord k)
=> Machine r i
-> (r -> i -> Maybe k)
-> Machine s i
-> Machine (Map k s, r) i
routeM :: forall k r i s.
Ord k =>
Machine r i
-> (r -> i -> Maybe k) -> Machine s i -> Machine (Map k s, r) i
routeM Machine r i
router r -> i -> Maybe k
index Machine s i
machine = Machine
{ initial :: (Map k s, r)
initial = (forall k a. Map k a
M.empty, forall s i. Machine s i -> s
initial Machine r i
router)
, final :: (Map k s, r) -> Bool
final = forall {b}. b -> Bool
routeMFinal
, alpha :: i -> Bool
alpha = i -> Bool
routeMAlpha
, delta :: (Map k s, r) -> i -> Maybe (Map k s, r)
delta = (Map k s, r) -> i -> Maybe (Map k s, r)
routeMDelta
}
where
routeMFinal :: b -> Bool
routeMFinal = forall a b. a -> b -> a
const Bool
False
routeMAlpha :: i -> Bool
routeMAlpha i
i = forall s i. Machine s i -> i -> Bool
alpha Machine r i
router i
i Bool -> Bool -> Bool
|| forall s i. Machine s i -> i -> Bool
alpha Machine s i
machine i
i
routeMDelta :: (Map k s, r) -> i -> Maybe (Map k s, r)
routeMDelta (Map k s
m, r
r) i
i = do
r
r' <- if forall s i. Machine s i -> i -> Bool
alpha Machine r i
router i
i
then forall s i. Machine s i -> s -> i -> Maybe s
delta Machine r i
router r
r i
i
else forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Map k s
m' <- if forall s i. Machine s i -> i -> Bool
alpha Machine s i
machine i
i
then case r -> i -> Maybe k
index r
r' i
i of
Just k
k -> do
s
s' <- forall s i. Machine s i -> s -> i -> Maybe s
delta Machine s i
machine (forall a. a -> Maybe a -> a
fromMaybe (forall s i. Machine s i -> s
initial Machine s i
machine) (forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k Map k s
m)) i
i
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
k s
s' Map k s
m
Maybe k
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return Map k s
m
else forall (m :: * -> *) a. Monad m => a -> m a
return Map k s
m
forall (m :: * -> *) a. Monad m => a -> m a
return (Map k s
m', r
r')