{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Control.Provenance
( ProvM (..),
PObject,
Provenance,
Prov,
BlackBox,
lift,
putM,
getM,
modifyM,
modifyWithBlackBox,
runProv,
runWithProv,
runOtherProv,
liftProv,
dump,
store,
push,
pull,
update,
updateWithBlackBox,
pushOtherProv,
runWithProvM,
runProvM,
find,
observe,
preservesNothing,
preservesJust,
)
where
import Control.Monad.State.Strict (MonadState (..), MonadTrans (..), StateT (..))
import Data.Aeson (ToJSON (..))
import Data.Map.Strict (Map, empty, insert)
import qualified Data.Map.Strict as Map
import Data.Maybe.Strict
import Data.Text (Text, unpack)
import Data.Type.Equality (TestEquality (testEquality))
import NoThunks.Class (NoThunks (..), allNoThunks)
import Type.Reflection (TypeRep, Typeable, typeOf, typeRep, (:~:) (Refl))
newtype ProvM t m a = ProvM (StateT (StrictMaybe t) m a)
deriving (a -> ProvM t m b -> ProvM t m a
(a -> b) -> ProvM t m a -> ProvM t m b
(forall a b. (a -> b) -> ProvM t m a -> ProvM t m b)
-> (forall a b. a -> ProvM t m b -> ProvM t m a)
-> Functor (ProvM t m)
forall a b. a -> ProvM t m b -> ProvM t m a
forall a b. (a -> b) -> ProvM t m a -> ProvM t m b
forall t (m :: * -> *) a b.
Functor m =>
a -> ProvM t m b -> ProvM t m a
forall t (m :: * -> *) a b.
Functor m =>
(a -> b) -> ProvM t m a -> ProvM t m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ProvM t m b -> ProvM t m a
$c<$ :: forall t (m :: * -> *) a b.
Functor m =>
a -> ProvM t m b -> ProvM t m a
fmap :: (a -> b) -> ProvM t m a -> ProvM t m b
$cfmap :: forall t (m :: * -> *) a b.
Functor m =>
(a -> b) -> ProvM t m a -> ProvM t m b
Functor, Functor (ProvM t m)
a -> ProvM t m a
Functor (ProvM t m)
-> (forall a. a -> ProvM t m a)
-> (forall a b. ProvM t m (a -> b) -> ProvM t m a -> ProvM t m b)
-> (forall a b c.
(a -> b -> c) -> ProvM t m a -> ProvM t m b -> ProvM t m c)
-> (forall a b. ProvM t m a -> ProvM t m b -> ProvM t m b)
-> (forall a b. ProvM t m a -> ProvM t m b -> ProvM t m a)
-> Applicative (ProvM t m)
ProvM t m a -> ProvM t m b -> ProvM t m b
ProvM t m a -> ProvM t m b -> ProvM t m a
ProvM t m (a -> b) -> ProvM t m a -> ProvM t m b
(a -> b -> c) -> ProvM t m a -> ProvM t m b -> ProvM t m c
forall a. a -> ProvM t m a
forall a b. ProvM t m a -> ProvM t m b -> ProvM t m a
forall a b. ProvM t m a -> ProvM t m b -> ProvM t m b
forall a b. ProvM t m (a -> b) -> ProvM t m a -> ProvM t m b
forall a b c.
(a -> b -> c) -> ProvM t m a -> ProvM t m b -> ProvM t m c
forall t (m :: * -> *). Monad m => Functor (ProvM t m)
forall t (m :: * -> *) a. Monad m => a -> ProvM t m a
forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> ProvM t m b -> ProvM t m a
forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> ProvM t m b -> ProvM t m b
forall t (m :: * -> *) a b.
Monad m =>
ProvM t m (a -> b) -> ProvM t m a -> ProvM t m b
forall t (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> ProvM t m a -> ProvM t m b -> ProvM t m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: ProvM t m a -> ProvM t m b -> ProvM t m a
$c<* :: forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> ProvM t m b -> ProvM t m a
*> :: ProvM t m a -> ProvM t m b -> ProvM t m b
$c*> :: forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> ProvM t m b -> ProvM t m b
liftA2 :: (a -> b -> c) -> ProvM t m a -> ProvM t m b -> ProvM t m c
$cliftA2 :: forall t (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> ProvM t m a -> ProvM t m b -> ProvM t m c
<*> :: ProvM t m (a -> b) -> ProvM t m a -> ProvM t m b
$c<*> :: forall t (m :: * -> *) a b.
Monad m =>
ProvM t m (a -> b) -> ProvM t m a -> ProvM t m b
pure :: a -> ProvM t m a
$cpure :: forall t (m :: * -> *) a. Monad m => a -> ProvM t m a
$cp1Applicative :: forall t (m :: * -> *). Monad m => Functor (ProvM t m)
Applicative, Applicative (ProvM t m)
a -> ProvM t m a
Applicative (ProvM t m)
-> (forall a b. ProvM t m a -> (a -> ProvM t m b) -> ProvM t m b)
-> (forall a b. ProvM t m a -> ProvM t m b -> ProvM t m b)
-> (forall a. a -> ProvM t m a)
-> Monad (ProvM t m)
ProvM t m a -> (a -> ProvM t m b) -> ProvM t m b
ProvM t m a -> ProvM t m b -> ProvM t m b
forall a. a -> ProvM t m a
forall a b. ProvM t m a -> ProvM t m b -> ProvM t m b
forall a b. ProvM t m a -> (a -> ProvM t m b) -> ProvM t m b
forall t (m :: * -> *). Monad m => Applicative (ProvM t m)
forall t (m :: * -> *) a. Monad m => a -> ProvM t m a
forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> ProvM t m b -> ProvM t m b
forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> (a -> ProvM t m b) -> ProvM t m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> ProvM t m a
$creturn :: forall t (m :: * -> *) a. Monad m => a -> ProvM t m a
>> :: ProvM t m a -> ProvM t m b -> ProvM t m b
$c>> :: forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> ProvM t m b -> ProvM t m b
>>= :: ProvM t m a -> (a -> ProvM t m b) -> ProvM t m b
$c>>= :: forall t (m :: * -> *) a b.
Monad m =>
ProvM t m a -> (a -> ProvM t m b) -> ProvM t m b
$cp1Monad :: forall t (m :: * -> *). Monad m => Applicative (ProvM t m)
Monad)
instance MonadTrans (ProvM t) where
lift :: m a -> ProvM t m a
lift m a
x = StateT (StrictMaybe t) m a -> ProvM t m a
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (m a -> StateT (StrictMaybe t) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m a
x)
runWithProvM :: Monad m => s -> ProvM s m a -> m (a, s)
runWithProvM :: s -> ProvM s m a -> m (a, s)
runWithProvM s
s (ProvM StateT (StrictMaybe s) m a
m) = do
(a
a, StrictMaybe s
x) <- StateT (StrictMaybe s) m a -> StrictMaybe s -> m (a, StrictMaybe s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT StateT (StrictMaybe s) m a
m (s -> StrictMaybe s
forall a. a -> StrictMaybe a
SJust s
s)
case StrictMaybe s
x of
StrictMaybe s
SNothing -> [Char] -> m (a, s)
forall a. HasCallStack => [Char] -> a
error ([Char]
"(SJust state) returns SNothing in runWithProvM")
SJust s
st -> (a, s) -> m (a, s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
a, s
st)
{-# INLINE runWithProvM #-}
runProvM :: (Monad m) => ProvM s m b -> m b
runProvM :: ProvM s m b -> m b
runProvM (ProvM StateT (StrictMaybe s) m b
m) = do
(b, StrictMaybe s)
pair <- StateT (StrictMaybe s) m b -> StrictMaybe s -> m (b, StrictMaybe s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT StateT (StrictMaybe s) m b
m StrictMaybe s
forall a. StrictMaybe a
SNothing
case (b, StrictMaybe s)
pair of
(b
a, StrictMaybe s
SNothing) -> b -> m b
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
a
(b
_, SJust s
_) -> [Char] -> m b
forall a. HasCallStack => [Char] -> a
error ([Char]
"SNothing returns (SJust p) in runProvM")
{-# INLINE runProvM #-}
data BlackBox t = Box !t | NoBox
deriving (Int -> BlackBox t -> ShowS
[BlackBox t] -> ShowS
BlackBox t -> [Char]
(Int -> BlackBox t -> ShowS)
-> (BlackBox t -> [Char])
-> ([BlackBox t] -> ShowS)
-> Show (BlackBox t)
forall t. Show t => Int -> BlackBox t -> ShowS
forall t. Show t => [BlackBox t] -> ShowS
forall t. Show t => BlackBox t -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [BlackBox t] -> ShowS
$cshowList :: forall t. Show t => [BlackBox t] -> ShowS
show :: BlackBox t -> [Char]
$cshow :: forall t. Show t => BlackBox t -> [Char]
showsPrec :: Int -> BlackBox t -> ShowS
$cshowsPrec :: forall t. Show t => Int -> BlackBox t -> ShowS
Show, a -> BlackBox b -> BlackBox a
(a -> b) -> BlackBox a -> BlackBox b
(forall a b. (a -> b) -> BlackBox a -> BlackBox b)
-> (forall a b. a -> BlackBox b -> BlackBox a) -> Functor BlackBox
forall a b. a -> BlackBox b -> BlackBox a
forall a b. (a -> b) -> BlackBox a -> BlackBox b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> BlackBox b -> BlackBox a
$c<$ :: forall a b. a -> BlackBox b -> BlackBox a
fmap :: (a -> b) -> BlackBox a -> BlackBox b
$cfmap :: forall a b. (a -> b) -> BlackBox a -> BlackBox b
Functor)
modifyMState :: Monad m => (t -> t) -> StateT (StrictMaybe t) m ()
modifyMState :: (t -> t) -> StateT (StrictMaybe t) m ()
modifyMState t -> t
delta = do
StrictMaybe t
mstore <- StateT (StrictMaybe t) m (StrictMaybe t)
forall s (m :: * -> *). MonadState s m => m s
get
case StrictMaybe t
mstore of
StrictMaybe t
SNothing -> () -> StateT (StrictMaybe t) m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
(SJust t
st) -> StrictMaybe t -> StateT (StrictMaybe t) m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (t -> StrictMaybe t
forall a. a -> StrictMaybe a
SJust (t -> t
delta t
st))
{-# INLINE modifyMState #-}
putM :: Monad m => s -> ProvM s m ()
putM :: s -> ProvM s m ()
putM s
s = StateT (StrictMaybe s) m () -> ProvM s m ()
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM ((s -> s) -> StateT (StrictMaybe s) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState (s -> s -> s
forall a b. a -> b -> a
const s
s))
{-# INLINE putM #-}
getM :: Monad m => ProvM s m (BlackBox s)
getM :: ProvM s m (BlackBox s)
getM = StateT (StrictMaybe s) m (BlackBox s) -> ProvM s m (BlackBox s)
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (do StrictMaybe s
m <- StateT (StrictMaybe s) m (StrictMaybe s)
forall s (m :: * -> *). MonadState s m => m s
get; case StrictMaybe s
m of { StrictMaybe s
SNothing -> BlackBox s -> StateT (StrictMaybe s) m (BlackBox s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlackBox s
forall t. BlackBox t
NoBox; SJust s
t -> BlackBox s -> StateT (StrictMaybe s) m (BlackBox s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (s -> BlackBox s
forall t. t -> BlackBox t
Box s
t) })
{-# INLINE getM #-}
modifyM :: Monad m => (t -> t) -> ProvM t m ()
modifyM :: (t -> t) -> ProvM t m ()
modifyM t -> t
delta = StateT (StrictMaybe t) m () -> ProvM t m ()
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM ((t -> t) -> StateT (StrictMaybe t) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState t -> t
delta)
{-# INLINE modifyM #-}
modifyWithBlackBox :: Monad m => BlackBox p -> (p -> t -> t) -> ProvM t m ()
modifyWithBlackBox :: BlackBox p -> (p -> t -> t) -> ProvM t m ()
modifyWithBlackBox (Box p
x) p -> t -> t
delta = StateT (StrictMaybe t) m () -> ProvM t m ()
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM ((t -> t) -> StateT (StrictMaybe t) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState (p -> t -> t
delta p
x))
modifyWithBlackBox BlackBox p
NoBox p -> t -> t
_ = StateT (StrictMaybe t) m () -> ProvM t m ()
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (() -> StateT (StrictMaybe t) m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
{-# INLINE modifyWithBlackBox #-}
active :: Monad m => ProvM s m Bool
active :: ProvM s m Bool
active = StateT (StrictMaybe s) m Bool -> ProvM s m Bool
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (do StrictMaybe s
m <- StateT (StrictMaybe s) m (StrictMaybe s)
forall s (m :: * -> *). MonadState s m => m s
get; Bool -> StateT (StrictMaybe s) m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (case StrictMaybe s
m of StrictMaybe s
SNothing -> Bool
False; SJust s
_ -> Bool
True))
{-# INLINE active #-}
runOtherProv :: Monad m => s1 -> ProvM s1 m a -> ProvM s2 m (a, BlackBox s1)
runOtherProv :: s1 -> ProvM s1 m a -> ProvM s2 m (a, BlackBox s1)
runOtherProv s1
initial ProvM s1 m a
other = do
Bool
t <- ProvM s2 m Bool
forall (m :: * -> *) s. Monad m => ProvM s m Bool
active
if Bool
t
then StateT (StrictMaybe s2) m (a, BlackBox s1)
-> ProvM s2 m (a, BlackBox s1)
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (m (a, BlackBox s1) -> StateT (StrictMaybe s2) m (a, BlackBox s1)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, BlackBox s1) -> StateT (StrictMaybe s2) m (a, BlackBox s1))
-> m (a, BlackBox s1) -> StateT (StrictMaybe s2) m (a, BlackBox s1)
forall a b. (a -> b) -> a -> b
$ do (a
a, s1
s) <- s1 -> ProvM s1 m a -> m (a, s1)
forall (m :: * -> *) s a. Monad m => s -> ProvM s m a -> m (a, s)
runWithProvM s1
initial ProvM s1 m a
other; (a, BlackBox s1) -> m (a, BlackBox s1)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
a, s1 -> BlackBox s1
forall t. t -> BlackBox t
Box s1
s))
else StateT (StrictMaybe s2) m (a, BlackBox s1)
-> ProvM s2 m (a, BlackBox s1)
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (m (a, BlackBox s1) -> StateT (StrictMaybe s2) m (a, BlackBox s1)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, BlackBox s1) -> StateT (StrictMaybe s2) m (a, BlackBox s1))
-> m (a, BlackBox s1) -> StateT (StrictMaybe s2) m (a, BlackBox s1)
forall a b. (a -> b) -> a -> b
$ do a
a <- ProvM s1 m a -> m a
forall (m :: * -> *) s b. Monad m => ProvM s m b -> m b
runProvM ProvM s1 m a
other; (a, BlackBox s1) -> m (a, BlackBox s1)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
a, BlackBox s1
forall t. BlackBox t
NoBox))
{-# INLINE runOtherProv #-}
liftProv :: Monad m => ProvM s1 m a -> s1 -> (a -> s1 -> s2 -> s2) -> ProvM s2 m a
liftProv :: ProvM s1 m a -> s1 -> (a -> s1 -> s2 -> s2) -> ProvM s2 m a
liftProv ProvM s1 m a
computation s1
inits1 a -> s1 -> s2 -> s2
combine =
do
(a
a, BlackBox s1
blackbox) <- s1 -> ProvM s1 m a -> ProvM s2 m (a, BlackBox s1)
forall (m :: * -> *) s1 a s2.
Monad m =>
s1 -> ProvM s1 m a -> ProvM s2 m (a, BlackBox s1)
runOtherProv s1
inits1 ProvM s1 m a
computation
BlackBox s1 -> (s1 -> s2 -> s2) -> ProvM s2 m ()
forall (m :: * -> *) p t.
Monad m =>
BlackBox p -> (p -> t -> t) -> ProvM t m ()
modifyWithBlackBox BlackBox s1
blackbox (a -> s1 -> s2 -> s2
combine a
a)
a -> ProvM s2 m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
{-# INLINE liftProv #-}
type Prov m a = ProvM Store m a
runProv :: Monad m => Prov m t -> m t
runProv :: Prov m t -> m t
runProv (ProvM StateT (StrictMaybe Store) m t
m) = do (t
a, StrictMaybe Store
_) <- StateT (StrictMaybe Store) m t
-> StrictMaybe Store -> m (t, StrictMaybe Store)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT StateT (StrictMaybe Store) m t
m StrictMaybe Store
forall a. StrictMaybe a
SNothing; t -> m t
forall (f :: * -> *) a. Applicative f => a -> f a
pure t
a
runWithProv :: Monad m => Prov m t -> m (t, Store)
runWithProv :: Prov m t -> m (t, Store)
runWithProv = Store -> Prov m t -> m (t, Store)
forall (m :: * -> *) s a. Monad m => s -> ProvM s m a -> m (a, s)
runWithProvM Store
forall k a. Map k a
empty
store :: forall t m. (Provenance t, Monad m) => Text -> m t -> Prov m t
store :: Text -> m t -> Prov m t
store Text
key m t
m = StateT (StrictMaybe Store) m t -> Prov m t
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (do t
a <- m t -> StateT (StrictMaybe Store) m t
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m t
m; (Store -> Store) -> StateT (StrictMaybe Store) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState (Text -> PObject -> Store -> Store
forall k a. Ord k => k -> a -> Map k a -> Map k a
insert Text
key (t -> PObject
forall t. Provenance t => t -> PObject
pobject t
a)); t -> StateT (StrictMaybe Store) m t
forall (f :: * -> *) a. Applicative f => a -> f a
pure t
a)
{-# INLINE store #-}
push :: (Provenance t, Monad m) => Text -> t -> Prov m ()
push :: Text -> t -> Prov m ()
push Text
key t
t = StateT (StrictMaybe Store) m () -> Prov m ()
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM ((Store -> Store) -> StateT (StrictMaybe Store) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState (Text -> PObject -> Store -> Store
forall k a. Ord k => k -> a -> Map k a -> Map k a
insert Text
key (t -> PObject
forall t. Provenance t => t -> PObject
pobject t
t)))
{-# INLINE push #-}
update :: forall t m. (Provenance t, Monad m) => Text -> (t -> t) -> Prov m ()
update :: Text -> (t -> t) -> Prov m ()
update Text
key t -> t
delta = StateT (StrictMaybe Store) m () -> Prov m ()
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM StateT (StrictMaybe Store) m ()
action2
where
action2 :: StateT (StrictMaybe Store) m ()
action2 = do
StrictMaybe Store
m <- StateT (StrictMaybe Store) m (StrictMaybe Store)
forall s (m :: * -> *). MonadState s m => m s
get
case Text -> StrictMaybe Store -> StrictMaybe t
forall t k.
(Ord k, Typeable t) =>
k -> StrictMaybe (Map k PObject) -> StrictMaybe t
findM @t Text
key StrictMaybe Store
m of
SJust t
t -> (Store -> Store) -> StateT (StrictMaybe Store) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState (Text -> PObject -> Store -> Store
forall k a. Ord k => k -> a -> Map k a -> Map k a
insert Text
key (t -> PObject
forall t. Provenance t => t -> PObject
pobject @t (t -> t
delta t
t)))
StrictMaybe t
SNothing -> () -> StateT (StrictMaybe Store) m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-# INLINE update #-}
updateWithBlackBox :: forall t m s. (Provenance t, Monad m) => Text -> BlackBox s -> (s -> t -> t) -> Prov m ()
updateWithBlackBox :: Text -> BlackBox s -> (s -> t -> t) -> Prov m ()
updateWithBlackBox Text
key (Box s
s) s -> t -> t
delta = Text -> (t -> t) -> Prov m ()
forall t (m :: * -> *).
(Provenance t, Monad m) =>
Text -> (t -> t) -> Prov m ()
update Text
key (s -> t -> t
delta s
s)
updateWithBlackBox Text
_ BlackBox s
NoBox s -> t -> t
_ = () -> Prov m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-# INLINE updateWithBlackBox #-}
pull :: forall t m. (Monad m, Typeable t) => Text -> Prov m (BlackBox t)
pull :: Text -> Prov m (BlackBox t)
pull Text
key = StateT (StrictMaybe Store) m (BlackBox t) -> Prov m (BlackBox t)
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (do StrictMaybe Store
m <- StateT (StrictMaybe Store) m (StrictMaybe Store)
forall s (m :: * -> *). MonadState s m => m s
get; case Text -> StrictMaybe Store -> StrictMaybe t
forall t k.
(Ord k, Typeable t) =>
k -> StrictMaybe (Map k PObject) -> StrictMaybe t
findM Text
key StrictMaybe Store
m of { StrictMaybe t
SNothing -> BlackBox t -> StateT (StrictMaybe Store) m (BlackBox t)
forall (f :: * -> *) a. Applicative f => a -> f a
pure BlackBox t
forall t. BlackBox t
NoBox; SJust t
t -> BlackBox t -> StateT (StrictMaybe Store) m (BlackBox t)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (t -> BlackBox t
forall t. t -> BlackBox t
Box t
t) })
{-# INLINE pull #-}
dump :: Monad m => Prov m String
dump :: Prov m [Char]
dump =
StateT (StrictMaybe Store) m [Char] -> Prov m [Char]
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM
( do
StrictMaybe Store
mstore <- StateT (StrictMaybe Store) m (StrictMaybe Store)
forall s (m :: * -> *). MonadState s m => m s
get
case StrictMaybe Store
mstore of
SJust Store
m -> [Char] -> StateT (StrictMaybe Store) m [Char]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Store -> [Char]
observe Store
m)
StrictMaybe Store
SNothing -> [Char] -> StateT (StrictMaybe Store) m [Char]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Char]
"SNothing Store"
)
pushOtherProv :: (Provenance s1, Monad m) => Text -> s1 -> ProvM s1 m a -> ProvM Store m a
pushOtherProv :: Text -> s1 -> ProvM s1 m a -> ProvM Store m a
pushOtherProv Text
key s1
initial ProvM s1 m a
other = do
Bool
t <- ProvM Store m Bool
forall (m :: * -> *) s. Monad m => ProvM s m Bool
active
if Bool
t
then
StateT (StrictMaybe Store) m a -> ProvM Store m a
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM
( do
(a
a, s1
v) <- m (a, s1) -> StateT (StrictMaybe Store) m (a, s1)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (s1 -> ProvM s1 m a -> m (a, s1)
forall (m :: * -> *) s a. Monad m => s -> ProvM s m a -> m (a, s)
runWithProvM s1
initial ProvM s1 m a
other)
(Store -> Store) -> StateT (StrictMaybe Store) m ()
forall (m :: * -> *) t.
Monad m =>
(t -> t) -> StateT (StrictMaybe t) m ()
modifyMState (Text -> PObject -> Store -> Store
forall k a. Ord k => k -> a -> Map k a -> Map k a
insert Text
key (s1 -> PObject
forall t. Provenance t => t -> PObject
pobject s1
v))
a -> StateT (StrictMaybe Store) m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
)
else StateT (StrictMaybe Store) m a -> ProvM Store m a
forall t (m :: * -> *) a. StateT (StrictMaybe t) m a -> ProvM t m a
ProvM (m a -> StateT (StrictMaybe Store) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> StateT (StrictMaybe Store) m a)
-> m a -> StateT (StrictMaybe Store) m a
forall a b. (a -> b) -> a -> b
$ ProvM s1 m a -> m a
forall (m :: * -> *) s b. Monad m => ProvM s m b -> m b
runProvM ProvM s1 m a
other)
type Provenance t = (Typeable t, ToJSON t, Show t, NoThunks t)
data PObject where
PObject :: Provenance t => !(TypeRep t) -> !t -> PObject
instance NoThunks PObject where
showTypeOf :: Proxy PObject -> [Char]
showTypeOf Proxy PObject
_ = [Char]
"PObject"
wNoThunks :: Context -> PObject -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt (PObject TypeRep t
_ t
t) = [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks [Context -> t -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt t
t]
instance Show PObject where
show :: PObject -> [Char]
show (PObject TypeRep t
ty t
t) = [Char]
"#" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ t -> [Char]
forall a. Show a => a -> [Char]
show t
t [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"::" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep t -> [Char]
forall a. Show a => a -> [Char]
show TypeRep t
ty
extract :: forall t. (Typeable t) => PObject -> StrictMaybe t
(PObject TypeRep t
ty t
n) = case TypeRep t -> TypeRep t -> Maybe (t :~: t)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality TypeRep t
ty (Typeable t => TypeRep t
forall k (a :: k). Typeable a => TypeRep a
typeRep @t) of Just t :~: t
Refl -> t -> StrictMaybe t
forall a. a -> StrictMaybe a
SJust t
n; Maybe (t :~: t)
Nothing -> StrictMaybe t
forall a. StrictMaybe a
SNothing
pobject :: Provenance t => t -> PObject
pobject :: t -> PObject
pobject !t
n = TypeRep t -> t -> PObject
forall t. Provenance t => TypeRep t -> t -> PObject
PObject (t -> TypeRep t
forall a. Typeable a => a -> TypeRep a
typeOf t
n) t
n
type Store = Map Text PObject
find :: forall t k. (Ord k, Typeable t) => k -> Map k PObject -> StrictMaybe t
find :: k -> Map k PObject -> StrictMaybe t
find k
key Map k PObject
m = case k -> Map k PObject -> Maybe PObject
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
key Map k PObject
m of Just PObject
obj -> PObject -> StrictMaybe t
forall t. Typeable t => PObject -> StrictMaybe t
extract PObject
obj; Maybe PObject
Nothing -> StrictMaybe t
forall a. StrictMaybe a
SNothing
findM :: forall t k. (Ord k, Typeable t) => k -> StrictMaybe (Map k PObject) -> StrictMaybe t
findM :: k -> StrictMaybe (Map k PObject) -> StrictMaybe t
findM k
_ StrictMaybe (Map k PObject)
SNothing = StrictMaybe t
forall a. StrictMaybe a
SNothing
findM k
key (SJust Map k PObject
m) = k -> Map k PObject -> StrictMaybe t
forall t k.
(Ord k, Typeable t) =>
k -> Map k PObject -> StrictMaybe t
find k
key Map k PObject
m
observe :: Store -> String
observe :: Store -> [Char]
observe Store
m = Context -> [Char]
unlines (((Text, PObject) -> [Char]) -> [(Text, PObject)] -> Context
forall a b. (a -> b) -> [a] -> [b]
map (Text, PObject) -> [Char]
f (Store -> [(Text, PObject)]
forall k a. Map k a -> [(k, a)]
Map.assocs Store
m))
where
f :: (Text, PObject) -> [Char]
f (Text
key, PObject TypeRep t
_ t
t) = Text -> [Char]
unpack Text
key [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
" =\n " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ t -> [Char]
forall a. Show a => a -> [Char]
show t
t
preservesNothing :: Monad m => ProvM t m a -> m Bool
preservesNothing :: ProvM t m a -> m Bool
preservesNothing (ProvM StateT (StrictMaybe t) m a
m) = do
(a
_, StrictMaybe t
maybet) <- StateT (StrictMaybe t) m a -> StrictMaybe t -> m (a, StrictMaybe t)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT StateT (StrictMaybe t) m a
m StrictMaybe t
forall a. StrictMaybe a
SNothing
case StrictMaybe t
maybet of StrictMaybe t
SNothing -> Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True; SJust t
_ -> Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
preservesJust :: Monad m => t -> ProvM t m a -> m Bool
preservesJust :: t -> ProvM t m a -> m Bool
preservesJust t
t (ProvM StateT (StrictMaybe t) m a
m) = do
(a
_, StrictMaybe t
maybet) <- StateT (StrictMaybe t) m a -> StrictMaybe t -> m (a, StrictMaybe t)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT StateT (StrictMaybe t) m a
m (t -> StrictMaybe t
forall a. a -> StrictMaybe a
SJust t
t)
case StrictMaybe t
maybet of StrictMaybe t
SNothing -> Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False; SJust t
_ -> Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True