module Control.Monad.Logic (
module Control.Monad.Logic.Class,
Logic(),
runLogic,
observe,
observeMany,
observeAll,
LogicT(),
runLogicT,
observeT,
observeManyT,
observeAllT,
module Control.Monad,
module Control.Monad.Trans
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Identity
import Control.Monad.Trans
import Control.Monad.Reader.Class
import Control.Monad.State.Class
import qualified Data.Foldable as F
import qualified Data.Traversable as T
import Control.Monad.Logic.Class
instance Applicative Identity where
pure = Identity
(Identity f) <*> (Identity a) = Identity (f a)
type SK r a = a -> r -> r
type FK a = a
newtype LogicT m a =
LogicT { unLogicT :: forall ans. SK (m ans) a -> FK (m ans) -> m ans }
observeT :: Monad m => LogicT m a -> m a
observeT lt = unLogicT lt (const . return) (fail "No answer.")
observeAllT :: Monad m => LogicT m a -> m [a]
observeAllT m = unLogicT m (liftM . (:)) (return [])
observeManyT :: Monad m => Int -> LogicT m a -> m [a]
observeManyT n m
| n <= 0 = return []
| n == 1 = unLogicT m (\a _ -> return [a]) (return [])
| otherwise = unLogicT (msplit m) sk (return [])
where
sk Nothing _ = return []
sk (Just (a, m')) _ = (a:) `liftM` observeManyT (n1) m'
runLogicT :: LogicT m a -> (a -> m r -> m r) -> m r -> m r
runLogicT = unLogicT
newtype Logic a = Logic { unLogic :: LogicT Identity a }
observe :: Logic a -> a
observe = runIdentity . observeT . unLogic
observeAll :: Logic a -> [a]
observeAll = runIdentity . observeAllT . unLogic
observeMany :: Int -> Logic a -> [a]
observeMany i = runIdentity . observeManyT i . unLogic
runLogic :: Logic a -> (a -> r -> r) -> r -> r
runLogic l s f = runIdentity $ unLogicT (unLogic l) si fi
where
si = fmap . s
fi = Identity f
instance (Functor f) => Functor (LogicT f) where
fmap f lt = LogicT $ \sk fk -> unLogicT lt (sk . f) fk
instance (Applicative f) => Applicative (LogicT f) where
pure a = LogicT $ \sk fk -> sk a fk
f <*> a = LogicT $ \sk fk -> unLogicT f (\g fk' -> unLogicT a (sk . g) fk') fk
instance (Applicative f) => Alternative (LogicT f) where
empty = LogicT $ \_ fk -> fk
f1 <|> f2 = LogicT $ \sk fk -> unLogicT f1 sk (unLogicT f2 sk fk)
instance (Monad m) => Monad (LogicT m) where
return a = LogicT $ \sk fk -> sk a fk
m >>= f = LogicT $ \sk fk -> unLogicT m (\a fk' -> unLogicT (f a) sk fk') fk
fail _ = LogicT $ \_ fk -> fk
instance (Monad m) => MonadPlus (LogicT m) where
mzero = LogicT $ \_ fk -> fk
m1 `mplus` m2 = LogicT $ \sk fk -> unLogicT m1 sk (unLogicT m2 sk fk)
instance MonadTrans LogicT where
lift m = LogicT $ \sk fk -> m >>= \a -> sk a fk
instance (MonadIO m) => MonadIO (LogicT m) where
liftIO = lift . liftIO
instance (Monad m) => MonadLogic (LogicT m) where
msplit m = lift $ unLogicT m ssk (return Nothing)
where
ssk a fk = return $ Just (a, (lift fk >>= reflect))
instance F.Foldable Logic where
foldr f z l = runLogic l f z
instance T.Traversable Logic where
traverse g l = runLogic l (\a ft -> cons <$> g a <*> ft) (pure mzero)
where cons a l' = return a `mplus` l'
instance Functor Logic where
fmap f = Logic . fmap f . unLogic
instance Applicative Logic where
pure = Logic . pure
f <*> a = Logic $ unLogic f <*> unLogic a
instance Alternative Logic where
empty = Logic empty
a1 <|> a2 = Logic $ unLogic a1 <|> unLogic a2
instance Monad Logic where
return = Logic . return
m >>= f = Logic $ unLogic m >>= unLogic . f
fail = Logic . fail
instance MonadPlus Logic where
mzero = Logic mzero
m1 `mplus` m2 = Logic $ unLogic m1 `mplus` unLogic m2
instance MonadLogic Logic where
msplit m = Logic . liftM (liftM (fmap Logic)) $ msplit (unLogic m)
instance (MonadReader r m) => MonadReader r (LogicT m) where
ask = lift ask
local f m = LogicT $ \sk fk -> unLogicT m ((local f .) . sk) (local f fk)
instance (MonadState s m) => MonadState s (LogicT m) where
get = lift get
put = lift . put