#if __GLASGOW_HASKELL__ >= 701
#endif
module Compiler.Hoopl.Pointed
( Pointed(..), addPoints, addPoints', addTop, addTop'
, liftJoinTop, extendJoinDomain
, WithTop, WithBot, WithTopAndBot
)
where
import Compiler.Hoopl.Graph
import Compiler.Hoopl.Label
import Compiler.Hoopl.Dataflow
data Pointed t b a where
Bot :: Pointed t C a
PElem :: a -> Pointed t b a
Top :: Pointed C b a
type WithBot a = Pointed O C a
type WithTop a = Pointed C O a
type WithTopAndBot a = Pointed C C a
addPoints :: String -> JoinFun a -> DataflowLattice (Pointed t C a)
addPoints' :: forall a t .
String
-> (Label -> OldFact a -> NewFact a -> (ChangeFlag, Pointed t C a))
-> DataflowLattice (Pointed t C a)
addPoints name join = addPoints' name join'
where join' l o n = (change, PElem f)
where (change, f) = join l o n
addPoints' name joinx = DataflowLattice name Bot join
where
join :: JoinFun (Pointed t C a)
join _ (OldFact f) (NewFact Bot) = (NoChange, f)
join _ (OldFact Top) (NewFact _) = (NoChange, Top)
join _ (OldFact Bot) (NewFact f) = (SomeChange, f)
join _ (OldFact _) (NewFact Top) = (SomeChange, Top)
join l (OldFact (PElem old)) (NewFact (PElem new))
= joinx l (OldFact old) (NewFact new)
liftJoinTop :: JoinFun a -> JoinFun (WithTop a)
extendJoinDomain :: forall a
. (Label -> OldFact a -> NewFact a -> (ChangeFlag, WithTop a))
-> JoinFun (WithTop a)
extendJoinDomain joinx = join
where join :: JoinFun (WithTop a)
join _ (OldFact Top) (NewFact _) = (NoChange, Top)
join _ (OldFact _) (NewFact Top) = (SomeChange, Top)
join l (OldFact (PElem old)) (NewFact (PElem new))
= joinx l (OldFact old) (NewFact new)
liftJoinTop joinx = extendJoinDomain (\l old new -> liftPair $ joinx l old new)
where liftPair (c, a) = (c, PElem a)
addTop :: DataflowLattice a -> DataflowLattice (WithTop a)
addTop' :: forall a .
String
-> a
-> (Label -> OldFact a -> NewFact a -> (ChangeFlag, WithTop a))
-> DataflowLattice (WithTop a)
addTop lattice = addTop' name' (fact_bot lattice) join'
where name' = fact_name lattice ++ " + T"
join' l o n = (change, PElem f)
where (change, f) = fact_join lattice l o n
addTop' name bot joinx = DataflowLattice name (PElem bot) join
where
join :: JoinFun (WithTop a)
join _ (OldFact Top) (NewFact _) = (NoChange, Top)
join _ (OldFact _) (NewFact Top) = (SomeChange, Top)
join l (OldFact (PElem old)) (NewFact (PElem new))
= joinx l (OldFact old) (NewFact new)
instance Show a => Show (Pointed t b a) where
show Bot = "_|_"
show Top = "T"
show (PElem a) = show a
instance Functor (Pointed t b) where
fmap _ Bot = Bot
fmap _ Top = Top
fmap f (PElem a) = PElem (f a)
instance Eq a => Eq (Pointed t b a) where
Bot == Bot = True
Top == Top = True
(PElem a) == (PElem a') = a == a'
_ == _ = False
instance Ord a => Ord (Pointed t b a) where
Bot `compare` Bot = EQ
Bot `compare` _ = LT
_ `compare` Bot = GT
PElem a `compare` PElem a' = a `compare` a'
Top `compare` Top = EQ
Top `compare` _ = GT
_ `compare` Top = LT