{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Control.Monad.Watson
( Watson
, MonadCell (..)
, unsafeRead
, backward
, forward
, runAll
, runOne
, satisfying
, whenever
) where
import Control.Monad.ST (ST, runST)
import Control.Monad.Cell.Class (MonadCell (..))
import qualified Control.Monad.Cell.Class as Cell
import Control.Monad.MoriarT (MoriarT (..))
import qualified Control.Monad.MoriarT as MoriarT
import Data.Coerce (coerce)
import Data.Input.Config (Config (..))
import Data.JoinSemilattice.Class.Eq (EqR)
import Data.JoinSemilattice.Class.Merge (Merge)
import Data.Kind (Type)
import Data.Propagator (Prop)
import qualified Data.Propagator as Prop
import Type.Reflection (Typeable)
newtype Watson (h :: Type) (x :: Type)
= Watson { runWatson :: MoriarT (ST h) x }
deriving (Functor, Applicative, Monad)
instance MonadCell (Watson h) where
newtype Cell (Watson h) x = Cell { unwrap :: Cell (MoriarT (ST h)) x }
discard = coerce (discard @(MoriarT (ST h)))
fill = fmap Cell . coerce (fill @(MoriarT (ST h)))
watch (Cell cell) = coerce (watch @(MoriarT (ST h)) cell)
with (Cell cell) = coerce (with @(MoriarT (ST h)) cell)
write (Cell cell) = coerce (write @(MoriarT (ST h)) cell)
unsafeRead :: Cell (Watson h) x -> Watson h x
unsafeRead = coerce . MoriarT.unsafeRead . unwrap
backward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> y -> Maybe x
backward f y = runST $ MoriarT.runOne $ runWatson do
input <- Cell.make
output <- Prop.down (f (Prop.up input))
Cell.write output y
unsafeRead input
forward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> x -> Maybe y
forward f x = runST $ MoriarT.runOne $ runWatson do
input <- Cell.make
output <- Prop.down (f (Prop.up input))
Cell.write input x
unsafeRead output
runAll :: (forall h. Watson h x) -> [ x ]
runAll xs = runST (MoriarT.runAll (runWatson xs))
runOne :: (forall h. Watson h x) -> Maybe x
runOne xs = runST (MoriarT.runOne (runWatson xs))
satisfying :: (EqR x b, Typeable x) => (forall h. Config (Watson h) x) -> (forall m. MonadCell m => [ Prop m x ] -> Prop m b) -> Maybe [ x ]
satisfying config f = runST (MoriarT.runOne (MoriarT.solve (coerce config) f))
whenever :: (EqR x b, Typeable x) => (forall h. Config (Watson h) x) -> (forall m. MonadCell m => [ Prop m x ] -> Prop m b) -> [[ x ]]
whenever config f = runST (MoriarT.runAll (MoriarT.solve (coerce config) f))