commit ghc-logict for openSUSE:Factory
Hello community, here is the log from the commit of package ghc-logict for openSUSE:Factory checked in at 2019-07-29 17:26:14 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-logict (Old) and /work/SRC/openSUSE:Factory/.ghc-logict.new.4126 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Package is "ghc-logict" Mon Jul 29 17:26:14 2019 rev:7 rq:715413 version:0.7.0.1 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-logict/ghc-logict.changes 2019-05-09 10:10:13.293167452 +0200 +++ /work/SRC/openSUSE:Factory/.ghc-logict.new.4126/ghc-logict.changes 2019-07-29 17:26:16.850304666 +0200 @@ -1,0 +2,18 @@ +Mon Jul 8 02:01:00 UTC 2019 - psimons@suse.com + +- Update logict to version 0.7.0.1. + # 0.7.0.1 + + * Fix `MonadReader r (LogicT m)` instance again. + +------------------------------------------------------------------- +Sun Jun 30 02:01:08 UTC 2019 - psimons@suse.com + +- Update logict to version 0.7.0.0. + # 0.7.0.0 + + * Remove unlawful `MonadLogic (Writer T w m)` instances. + * Fix `MonadReader r (LogicT m)` instance. + * Move `lnot` into `MonadLogic` class. + +------------------------------------------------------------------- Old: ---- logict-0.6.0.3.tar.gz New: ---- logict-0.7.0.1.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-logict.spec ++++++ --- /var/tmp/diff_new_pack.1xCjkX/_old 2019-07-29 17:26:17.510304422 +0200 +++ /var/tmp/diff_new_pack.1xCjkX/_new 2019-07-29 17:26:17.514304420 +0200 @@ -17,8 +17,9 @@ %global pkg_name logict +%bcond_with tests Name: ghc-%{pkg_name} -Version: 0.6.0.3 +Version: 0.7.0.1 Release: 0 Summary: A backtracking logic-programming monad License: BSD-3-Clause @@ -28,6 +29,10 @@ BuildRequires: ghc-Cabal-devel BuildRequires: ghc-mtl-devel BuildRequires: ghc-rpm-macros +%if %{with tests} +BuildRequires: ghc-tasty-devel +BuildRequires: ghc-tasty-hunit-devel +%endif %description A continuation-based, backtracking, logic programming monad. An adaptation of @@ -55,6 +60,9 @@ %install %ghc_lib_install +%check +%cabal_test + %post devel %ghc_pkg_recache ++++++ logict-0.6.0.3.tar.gz -> logict-0.7.0.1.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/logict-0.6.0.3/Control/Monad/Logic/Class.hs new/logict-0.7.0.1/Control/Monad/Logic/Class.hs --- old/logict-0.6.0.3/Control/Monad/Logic/Class.hs 2014-02-09 23:59:08.000000000 +0100 +++ new/logict-0.7.0.1/Control/Monad/Logic/Class.hs 2019-06-29 22:03:05.000000000 +0200 @@ -14,20 +14,15 @@ -- /Backtracking, Interleaving, and Terminating -- Monad Transformers/, by -- Oleg Kiselyov, Chung-chieh Shan, Daniel P. Friedman, Amr Sabry --- (<http://www.cs.rutgers.edu/~ccshan/logicprog/LogicT-icfp2005.pdf>) +-- (<http://okmij.org/ftp/papers/LogicT.pdf>) ------------------------------------------------------------------------- -module Control.Monad.Logic.Class (MonadLogic(..), reflect, lnot) where +module Control.Monad.Logic.Class (MonadLogic(..), reflect) where +import Control.Monad.Reader import qualified Control.Monad.State.Lazy as LazyST import qualified Control.Monad.State.Strict as StrictST -import Control.Monad.Reader - -import Data.Monoid -import qualified Control.Monad.Writer.Lazy as LazyWT -import qualified Control.Monad.Writer.Strict as StrictWT - ------------------------------------------------------------------------------- -- | Minimal implementation: msplit class (MonadPlus m) => MonadLogic m where @@ -79,6 +74,10 @@ -- such. once :: m a -> m a + -- | Inverts a logic computation. If @m@ succeeds with at least one value, + -- @lnot m@ fails. If @m@ fails, then @lnot m@ succeeds the value @()@. + lnot :: m a -> m () + -- All the class functions besides msplit can be derived from msplit, if -- desired interleave m1 m2 = msplit m1 >>= @@ -92,6 +91,8 @@ once m = do (a, _) <- maybe mzero return =<< msplit m return a + lnot m = ifte (once m) (const mzero) (return ()) + ------------------------------------------------------------------------------- -- | The inverse of msplit. Satisfies the following law: @@ -101,33 +102,27 @@ reflect Nothing = mzero reflect (Just (a, m)) = return a `mplus` m --- | Inverts a logic computation. If @m@ succeeds with at least one value, --- @lnot m@ fails. If @m@ fails, then @lnot m@ succeeds the value @()@. -lnot :: MonadLogic m => m a -> m () -lnot m = ifte (once m) (const mzero) (return ()) - -- An instance of MonadLogic for lists instance MonadLogic [] where msplit [] = return Nothing msplit (x:xs) = return $ Just (x, xs) --- Some of these may be questionable instances. Splitting a transformer does --- not allow you to provide different input to the monadic object returned. --- So, for instance, in: +-- | Note that splitting a transformer does +-- not allow you to provide different input +-- to the monadic object returned. +-- For instance, in: -- --- let Just (_, rm') = runReaderT (msplit rm) r --- in runReaderT rm' r' +-- > let Just (_, rm') = runReaderT (msplit rm) r in runReaderT rm' r' -- --- The "r'" parameter will be ignored, as "r" was already threaded through the --- computation. The results are similar for StateT. However, this is likely not --- an issue as most uses of msplit (all the ones in this library, at least) would --- not allow for that anyway. +-- @r'@ will be ignored, because @r@ was already threaded through the +-- computation. instance MonadLogic m => MonadLogic (ReaderT e m) where msplit rm = ReaderT $ \e -> do r <- msplit $ runReaderT rm e case r of Nothing -> return Nothing Just (a, m) -> return (Just (a, lift m)) +-- | See note on splitting above. instance MonadLogic m => MonadLogic (StrictST.StateT s m) where msplit sm = StrictST.StateT $ \s -> do r <- msplit (StrictST.runStateT sm s) @@ -148,6 +143,7 @@ once ma = StrictST.StateT $ \s -> once (StrictST.runStateT ma s) +-- | See note on splitting above. instance MonadLogic m => MonadLogic (LazyST.StateT s m) where msplit sm = LazyST.StateT $ \s -> do r <- msplit (LazyST.runStateT sm s) @@ -167,47 +163,3 @@ (LazyST.runStateT el s) once ma = LazyST.StateT $ \s -> once (LazyST.runStateT ma s) - -instance (MonadLogic m, Monoid w) => MonadLogic (StrictWT.WriterT w m) where - msplit wm = StrictWT.WriterT $ - do r <- msplit (StrictWT.runWriterT wm) - case r of - Nothing -> return (Nothing, mempty) - Just ((a,w), m) -> - return (Just (a, StrictWT.WriterT m), w) - - interleave ma mb = StrictWT.WriterT $ - StrictWT.runWriterT ma `interleave` StrictWT.runWriterT mb - - ma >>- f = StrictWT.WriterT $ - StrictWT.runWriterT ma >>- \(a,w) -> - StrictWT.runWriterT (StrictWT.tell w >> f a) - - ifte t th el = StrictWT.WriterT $ - ifte (StrictWT.runWriterT t) - (\(a,w) -> StrictWT.runWriterT (StrictWT.tell w >> th a)) - (StrictWT.runWriterT el) - - once ma = StrictWT.WriterT $ once (StrictWT.runWriterT ma) - -instance (MonadLogic m, Monoid w) => MonadLogic (LazyWT.WriterT w m) where - msplit wm = LazyWT.WriterT $ - do r <- msplit (LazyWT.runWriterT wm) - case r of - Nothing -> return (Nothing, mempty) - Just ((a,w), m) -> - return (Just (a, LazyWT.WriterT m), w) - - interleave ma mb = LazyWT.WriterT $ - LazyWT.runWriterT ma `interleave` LazyWT.runWriterT mb - - ma >>- f = LazyWT.WriterT $ - LazyWT.runWriterT ma >>- \(a,w) -> - LazyWT.runWriterT (LazyWT.tell w >> f a) - - ifte t th el = LazyWT.WriterT $ - ifte (LazyWT.runWriterT t) - (\(a,w) -> LazyWT.runWriterT (LazyWT.tell w >> th a)) - (LazyWT.runWriterT el) - - once ma = LazyWT.WriterT $ once (LazyWT.runWriterT ma) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/logict-0.6.0.3/Control/Monad/Logic.hs new/logict-0.7.0.1/Control/Monad/Logic.hs --- old/logict-0.6.0.3/Control/Monad/Logic.hs 2019-04-30 23:09:32.000000000 +0200 +++ new/logict-0.7.0.1/Control/Monad/Logic.hs 2019-07-08 00:07:43.000000000 +0200 @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP, UndecidableInstances, Rank2Types, FlexibleInstances, MultiParamTypeClasses #-} - ------------------------------------------------------------------------- -- | -- Module : Control.Monad.Logic @@ -16,9 +14,11 @@ -- /Backtracking, Interleaving, and Terminating -- Monad Transformers/, by -- Oleg Kiselyov, Chung-chieh Shan, Daniel P. Friedman, Amr Sabry --- (<http://www.cs.rutgers.edu/~ccshan/logicprog/LogicT-icfp2005.pdf>). +-- (<http://okmij.org/ftp/papers/LogicT.pdf>). ------------------------------------------------------------------------- +{-# LANGUAGE CPP, UndecidableInstances, Rank2Types, FlexibleInstances, MultiParamTypeClasses #-} + module Control.Monad.Logic ( module Control.Monad.Logic.Class, -- * The Logic monad @@ -49,7 +49,9 @@ import Control.Monad.State.Class import Control.Monad.Error.Class +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(mappend, mempty)) +#endif import qualified Data.Foldable as F import qualified Data.Traversable as T @@ -57,7 +59,7 @@ ------------------------------------------------------------------------- -- | A monad transformer for performing backtracking computations --- layered over another monad 'm' +-- layered over another monad @m@. newtype LogicT m a = LogicT { unLogicT :: forall r. (a -> m r -> m r) -> m r -> m r } @@ -95,7 +97,7 @@ ------------------------------------------------------------------------- -- | The basic Logic monad, for performing backtracking computations --- returning values of type 'a' +-- returning values of type @a@. type Logic = LogicT Identity ------------------------------------------------------------------------- @@ -118,7 +120,9 @@ ------------------------------------------------------------------------- -- | Extracts up to a given number of results from a Logic computation. observeMany :: Int -> Logic a -> [a] -observeMany i = runIdentity . observeManyT i +observeMany i = take i . observeAll +-- Implementing 'observeMany' using 'observeManyT' is quite costly, +-- because it calls 'msplit' multiple times. ------------------------------------------------------------------------- -- | Runs a Logic computation with the specified initial success and @@ -161,13 +165,29 @@ liftIO = lift . liftIO instance (Monad m) => MonadLogic (LogicT m) where + -- 'msplit' is quite costly even if the base 'Monad' is 'Identity'. + -- Try to avoid it. msplit m = lift $ unLogicT m ssk (return Nothing) where ssk a fk = return $ Just (a, (lift fk >>= reflect)) + once m = LogicT $ \sk fk -> unLogicT m (\a _ -> sk a fk) fk + lnot m = LogicT $ \sk fk -> unLogicT m (\_ _ -> fk) (sk () fk) + +#if MIN_VERSION_base(4,8,0) -instance (Monad m, F.Foldable m) => F.Foldable (LogicT m) where +instance {-# OVERLAPPABLE #-} (Monad m, F.Foldable m) => F.Foldable (LogicT m) where foldMap f m = F.fold $ unLogicT m (liftM . mappend . f) (return mempty) +instance {-# OVERLAPPING #-} F.Foldable (LogicT Identity) where + foldr f z m = runLogic m f z + +#else + +instance {-# OVERLAPPABLE #-} (Monad m, F.Foldable m) => F.Foldable (LogicT m) where + foldMap f m = F.fold $ unLogicT m (liftM . mappend . f) (return mempty) + +#endif + instance T.Traversable (LogicT Identity) where traverse g l = runLogic l (\a ft -> cons <$> g a <*> ft) (pure mzero) where cons a l' = return a `mplus` l' @@ -175,7 +195,9 @@ -- Needs undecidable instances 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) + local f (LogicT m) = LogicT $ \sk fk -> do + env <- ask + local f $ m ((local (const env) .) . sk) (local (const env) fk) -- Needs undecidable instances instance MonadState s m => MonadState s (LogicT m) where diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/logict-0.6.0.3/changelog.md new/logict-0.7.0.1/changelog.md --- old/logict-0.6.0.3/changelog.md 2019-04-30 23:09:32.000000000 +0200 +++ new/logict-0.7.0.1/changelog.md 2019-07-08 00:07:43.000000000 +0200 @@ -1,3 +1,13 @@ +# 0.7.0.1 + +* Fix `MonadReader r (LogicT m)` instance again. + +# 0.7.0.0 + +* Remove unlawful `MonadLogic (Writer T w m)` instances. +* Fix `MonadReader r (LogicT m)` instance. +* Move `lnot` into `MonadLogic` class. + # 0.6.0.3 * Comply with MonadFail proposal. diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/logict-0.6.0.3/logict.cabal new/logict-0.7.0.1/logict.cabal --- old/logict-0.6.0.3/logict.cabal 2019-04-30 23:10:34.000000000 +0200 +++ new/logict-0.7.0.1/logict.cabal 2019-07-08 00:07:43.000000000 +0200 @@ -1,38 +1,53 @@ -name: logict -version: 0.6.0.3 -description: A continuation-based, backtracking, logic programming monad. - An adaptation of the two-continuation implementation found - in the paper "Backtracking, Interleaving, and Terminating - Monad Transformers" available here: - <http://okmij.org/ftp/papers/LogicT.pdf> -synopsis: A backtracking logic-programming monad. -category: Control -license: BSD3 -license-file: LICENSE -copyright: Copyright (c) 2007-2014, Dan Doel, - Copyright (c) 2011-2013, Edward Kmett, - Copyright (c) 2014, Roman Cheplyaka -author: Dan Doel -maintainer: Andrew Lelechenko <andrew.lelechenko@gmail.com> -homepage: https://github.com/Bodigrim/logict#readme -cabal-version: >= 1.9.2 -tested-with: GHC -build-type: Simple -extra-source-files: changelog.md +name: logict +version: 0.7.0.1 +license: BSD3 +license-file: LICENSE +copyright: + Copyright (c) 2007-2014, Dan Doel, + Copyright (c) 2011-2013, Edward Kmett, + Copyright (c) 2014, Roman Cheplyaka +maintainer: Andrew Lelechenko <andrew.lelechenko@gmail.com> +author: Dan Doel +tested-with: ghc -any +homepage: https://github.com/Bodigrim/logict#readme +synopsis: A backtracking logic-programming monad. +description: + A continuation-based, backtracking, logic programming monad. + An adaptation of the two-continuation implementation found + in the paper "Backtracking, Interleaving, and Terminating + Monad Transformers" available here: + <http://okmij.org/ftp/papers/LogicT.pdf> +category: Control +build-type: Simple +extra-source-files: + changelog.md +cabal-version: >=1.9.2 source-repository head type: git location: https://github.com/Bodigrim/logict library - build-depends: base >=2 && < 5, mtl>=2 && <2.3 - if impl(ghc < 8.0) - build-depends: fail + exposed-modules: + Control.Monad.Logic + Control.Monad.Logic.Class + ghc-options: -O2 -Wall + build-depends: + base >=2 && <5, + mtl >=2 && <2.3 - exposed-modules: Control.Monad.Logic, - Control.Monad.Logic.Class - extensions: MultiParamTypeClasses, - UndecidableInstances, - Rank2Types, - FlexibleInstances - ghc-options: -O2 -Wall + if impl(ghc <8.0) + build-depends: + fail -any + +test-suite logict-tests + type: exitcode-stdio-1.0 + main-is: Test.hs + ghc-options: -Wall + build-depends: + base >=2 && <5, + logict -any, + mtl >=2 && <2.3, + tasty, + tasty-hunit + hs-source-dirs: test diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/logict-0.6.0.3/test/Test.hs new/logict-0.7.0.1/test/Test.hs --- old/logict-0.6.0.3/test/Test.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/logict-0.7.0.1/test/Test.hs 2019-07-07 23:58:05.000000000 +0200 @@ -0,0 +1,29 @@ +{-# LANGUAGE FlexibleContexts #-} + +module Main where + +import Test.Tasty +import Test.Tasty.HUnit + +import Control.Monad.Logic +import Control.Monad.Reader + +monadReader1 :: Assertion +monadReader1 = assertEqual "should be equal" [5 :: Int] $ + runReader (observeAllT (local (+ 5) ask)) 0 + +monadReader2 :: Assertion +monadReader2 = assertEqual "should be equal" [(5, 0)] $ + runReader (observeAllT foo) 0 + where + foo :: MonadReader Int m => m (Int,Int) + foo = do + x <- local (5+) ask + y <- ask + return (x,y) + +main :: IO () +main = defaultMain $ testGroup "All" + [ testCase "Monad Reader 1" monadReader1 + , testCase "Monad Reader 2" monadReader2 + ]
participants (1)
-
root