Script 'mail_helper' called by obssrc Hello community, here is the log from the commit of package ghc-syb for openSUSE:Factory checked in at 2023-08-07 15:29:08 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-syb (Old) and /work/SRC/openSUSE:Factory/.ghc-syb.new.22712 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-syb" Mon Aug 7 15:29:08 2023 rev:26 rq:1102606 version:0.7.2.4 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-syb/ghc-syb.changes 2023-04-04 21:23:56.066390935 +0200 +++ /work/SRC/openSUSE:Factory/.ghc-syb.new.22712/ghc-syb.changes 2023-08-07 15:29:19.052397473 +0200 @@ -1,0 +2,8 @@ +Sun Jul 30 17:25:29 UTC 2023 - Peter Simons <psim...@suse.com> + +- Update syb to version 0.7.2.4. + # 0.7.2.4 + - Improved documentation (thanks to @BinderDavid) + - Export `ext2` function which was already defined but not exported + +------------------------------------------------------------------- Old: ---- syb-0.7.2.3.tar.gz New: ---- syb-0.7.2.4.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-syb.spec ++++++ --- /var/tmp/diff_new_pack.vyLhox/_old 2023-08-07 15:29:19.784401966 +0200 +++ /var/tmp/diff_new_pack.vyLhox/_new 2023-08-07 15:29:19.788401990 +0200 @@ -20,7 +20,7 @@ %global pkgver %{pkg_name}-%{version} %bcond_with tests Name: ghc-%{pkg_name} -Version: 0.7.2.3 +Version: 0.7.2.4 Release: 0 Summary: Scrap Your Boilerplate License: BSD-3-Clause ++++++ syb-0.7.2.3.tar.gz -> syb-0.7.2.4.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/Changelog.md new/syb-0.7.2.4/Changelog.md --- old/syb-0.7.2.3/Changelog.md 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/Changelog.md 2001-09-09 03:46:40.000000000 +0200 @@ -1,3 +1,7 @@ +# 0.7.2.4 +- Improved documentation (thanks to @BinderDavid) +- Export `ext2` function which was already defined but not exported + # 0.7.2.3 - Compatibility with `mtl` 2.3 and GHC 9.6 diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/src/Data/Generics/Aliases.hs new/syb-0.7.2.4/src/Data/Generics/Aliases.hs --- old/syb-0.7.2.3/src/Data/Generics/Aliases.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/src/Data/Generics/Aliases.hs 2001-09-09 03:46:40.000000000 +0200 @@ -4,35 +4,58 @@ -- Module : Data.Generics.Aliases -- Copyright : (c) The University of Glasgow, CWI 2001--2004 -- License : BSD-style (see the LICENSE file) --- +-- -- Maintainer : gener...@haskell.org -- Stability : experimental -- Portability : non-portable (local universal quantification) -- --- \"Scrap your boilerplate\" --- Generic programming in Haskell --- See <http://www.cs.uu.nl/wiki/GenericProgramming/SYB>. --- The present module provides a number of declarations for typical generic +-- This module provides a number of declarations for typical generic -- function types, corresponding type case, and others. -- ----------------------------------------------------------------------------- module Data.Generics.Aliases ( - -- * Combinators to \"make\" generic functions via cast - mkT, mkQ, mkM, mkMp, mkR, - ext0, extT, extQ, extM, extMp, extB, extR, - - -- * Type synonyms for generic function types + -- * Combinators which create generic functions via cast + -- + -- $castcombinators + + -- ** Transformations + mkT, + extT, + -- ** Queries + mkQ, + extQ, + -- ** Monadic transformations + mkM, + extM, + -- ** MonadPlus transformations + mkMp, + extMp, + -- ** Readers + mkR, + extR, + -- ** Builders + extB, + -- ** Other + ext0, + -- * Types for generic functions + -- ** Transformations GenericT, + GenericT'(..), + -- ** Queries GenericQ, + GenericQ'(..), + -- ** Monadic transformations GenericM, - GenericB, + GenericM'(..), + -- ** Readers GenericR, + -- ** Builders + GenericB, + -- ** Other Generic, Generic'(..), - GenericT'(..), - GenericQ'(..), - GenericM'(..), -- * Ingredients of generic functions orElse, @@ -52,6 +75,7 @@ ext1B, -- * Type extension for binary type constructors + ext2, ext2T, ext2M, ext2Q, @@ -73,149 +97,346 @@ -- ------------------------------------------------------------------------------ --- | Make a generic transformation; --- start from a type-specific case; --- preserve the term otherwise +-- $castcombinators +-- +-- Other programming languages sometimes provide an operator @instanceof@ which +-- can check whether an expression is an instance of a given type. This operator +-- allows programmers to implement a function @f :: forall a. a -> a@ which exhibits +-- a different behaviour depending on whether a `Bool` or a `Char` is passed. +-- In Haskell this is not the case: A function with type @forall a. a -> a@ +-- can only be the identity function or a function which loops indefinitely +-- or throws an exception. That is, it must implement exactly the same behaviour +-- for any type at which it is used. But sometimes it is very useful to have +-- a function which can accept (almost) any type and exhibit a different behaviour +-- for different types. Haskell provides this functionality with the 'Typeable' +-- typeclass, whose instances can be automatically derived by GHC for almost all +-- types. This typeclass allows the definition of a functon 'cast' which has type +-- @forall a b. (Typeable a, Typeable b) => a -> Maybe b@. The 'cast' function allows +-- to implement a polymorphic function with different behaviour at different types: +-- +-- >>> cast True :: Maybe Bool +-- Just True +-- +-- >>> cast True :: Maybe Int +-- Nothing +-- +-- This section provides combinators which make use of 'cast' internally to +-- provide various polymorphic functions with type-specific behaviour. + + +-- | Extend the identity function with a type-specific transformation. +-- The function created by @mkT ext@ behaves like the identity function on all +-- arguments which cannot be cast to type @b@, and like the function @ext@ otherwise. +-- The name 'mkT' is short for "make transformation". +-- +-- === __Examples__ +-- +-- >>> mkT not True +-- False +-- +-- >>> mkT not 'a' +-- 'a' -- +-- @since 0.1.0.0 mkT :: ( Typeable a , Typeable b ) => (b -> b) + -- ^ The type-specific transformation -> a + -- ^ The argument we try to cast to type @b@ -> a mkT = extT id --- | Make a generic query; --- start from a type-specific case; --- return a constant otherwise +-- | The function created by @mkQ def f@ returns the default result +-- @def@ if its argument cannot be cast to type @b@, otherwise it returns +-- the result of applying @f@ to its argument. +-- The name 'mkQ' is short for "make query". -- +-- === __Examples__ +-- +-- >>> mkQ "default" (show :: Bool -> String) True +-- "True" +-- +-- >>> mkQ "default" (show :: Bool -> String) () +-- "default" +-- +-- @since 0.1.0.0 mkQ :: ( Typeable a , Typeable b ) => r + -- ^ The default result -> (b -> r) + -- ^ The transformation to apply if the cast is successful -> a + -- ^ The argument we try to cast to type @b@ -> r (r `mkQ` br) a = case cast a of Just b -> br b Nothing -> r --- | Make a generic monadic transformation; --- start from a type-specific case; --- resort to return otherwise +-- | Extend the default monadic action @pure :: Monad m => a -> m a@ by a type-specific +-- monadic action. The function created by @mkM act@ behaves like 'pure' if its +-- argument cannot be cast to type @b@, and like the monadic action @act@ otherwise. +-- The name 'mkM' is short for "make monadic transformation". +-- +-- === __Examples__ -- +-- >>> mkM (\x -> [x, not x]) True +-- [True,False] +-- +-- >>> mkM (\x -> [x, not x]) (5 :: Int) +-- [5] +-- +-- @since 0.1.0.0 mkM :: ( Monad m , Typeable a , Typeable b ) => (b -> m b) + -- ^ The type-specific monadic transformation -> a + -- ^ The argument we try to cast to type @b@ -> m a mkM = extM return - -{- - -For the remaining definitions, we stick to a more concise style, i.e., -we fold maybes with "maybe" instead of case ... of ..., and we also -use a point-free style whenever possible. - --} - - --- | Make a generic monadic transformation for MonadPlus; --- use \"const mzero\" (i.e., failure) instead of return as default. +-- | Extend the default 'MonadPlus' action @const mzero@ by a type-specific 'MonadPlus' +-- action. The function created by @mkMp act@ behaves like @const mzero@ if its argument +-- cannot be cast to type @b@, and like the monadic action @act@ otherwise. +-- The name 'mkMp' is short for "make MonadPlus transformation". -- +-- === __Examples__ +-- +-- >>> mkMp (\x -> Just (not x)) True +-- Just False +-- +-- >>> mkMp (\x -> Just (not x)) 'a' +-- Nothing +-- +-- @since 0.1.0.0 mkMp :: ( MonadPlus m , Typeable a , Typeable b ) => (b -> m b) + -- ^ The type-specific MonadPlus action -> a + -- ^ The argument we try to cast to type @b@ -> m a mkMp = extM (const mzero) --- | Make a generic builder; --- start from a type-specific ase; --- resort to no build (i.e., mzero) otherwise +-- | Make a generic reader from a type-specific case. +-- The function created by @mkR f@ behaves like the reader @f@ if an expression +-- of type @a@ can be cast to type @b@, and like the expression @mzero@ otherwise. +-- The name 'mkR' is short for "make reader". +-- +-- === __Examples__ -- +-- >>> mkR (Just True) :: Maybe Bool +-- Just True +-- +-- >>> mkR (Just True) :: Maybe Int +-- Nothing +-- +-- @since 0.1.0.0 mkR :: ( MonadPlus m , Typeable a , Typeable b ) - => m b -> m a + => m b + -- ^ The type-specific reader + -> m a mkR f = mzero `extR` f -- | Flexible type extension +-- +-- === __Examples__ +-- +-- >>> ext0 [1 :: Int, 2, 3] [True, False] :: [Int] +-- [1,2,3] +-- +-- >>> ext0 [1 :: Int, 2, 3] [4 :: Int, 5, 6] :: [Int] +-- [4,5,6] +-- +-- @since 0.1.0.0 ext0 :: (Typeable a, Typeable b) => c a -> c b -> c a ext0 def ext = maybe def id (gcast ext) --- | Extend a generic transformation by a type-specific case +-- | Extend a generic transformation by a type-specific transformation. +-- The function created by @extT def ext@ behaves like the generic transformation +-- @def@ if its argument cannot be cast to the type @b@, and like the type-specific +-- transformation @ext@ otherwise. +-- The name 'extT' is short for "extend transformation". +-- +-- === __Examples__ +-- +-- >>> extT id not True +-- False +-- +-- >>> extT id not 'a' +-- 'a' +-- +-- @since 0.1.0.0 extT :: ( Typeable a , Typeable b ) => (a -> a) + -- ^ The transformation we want to extend -> (b -> b) + -- ^ The type-specific transformation -> a + -- ^ The argument we try to cast to type @b@ -> a extT def ext = unT ((T def) `ext0` (T ext)) --- | Extend a generic query by a type-specific case +-- | Extend a generic query by a type-specific query. The function created by @extQ def ext@ behaves +-- like the generic query @def@ if its argument cannot be cast to the type @b@, and like the type-specific +-- query @ext@ otherwise. +-- The name 'extQ' is short for "extend query". +-- +-- === __Examples__ +-- +-- >>> extQ (const True) not True +-- False +-- +-- >>> extQ (const True) not 'a' +-- True +-- +-- @since 0.1.0.0 extQ :: ( Typeable a , Typeable b ) - => (a -> q) - -> (b -> q) + => (a -> r) + -- ^ The query we want to extend + -> (b -> r) + -- ^ The type-specific query -> a - -> q + -- ^ The argument we try to cast to type @b@ + -> r extQ f g a = maybe (f a) g (cast a) --- | Extend a generic monadic transformation by a type-specific case +-- | Extend a generic monadic transformation by a type-specific case. +-- The function created by @extM def ext@ behaves like the monadic transformation +-- @def@ if its argument cannot be cast to type @b@, and like the monadic transformation +-- @ext@ otherwise. +-- The name 'extM' is short for "extend monadic transformation". +-- +-- === __Examples__ +-- +-- >>> extM (\x -> [x,x])(\x -> [not x, x]) True +-- [False,True] +-- +-- >>> extM (\x -> [x,x])(\x -> [not x, x]) (5 :: Int) +-- [5,5] +-- +-- @since 0.1.0.0 extM :: ( Monad m , Typeable a , Typeable b ) - => (a -> m a) -> (b -> m b) -> a -> m a + => (a -> m a) + -- ^ The monadic transformation we want to extend + -> (b -> m b) + -- ^ The type-specific monadic transformation + -> a + -- ^ The argument we try to cast to type @b@ + -> m a extM def ext = unM ((M def) `ext0` (M ext)) --- | Extend a generic MonadPlus transformation by a type-specific case +-- | Extend a generic MonadPlus transformation by a type-specific case. +-- The function created by @extMp def ext@ behaves like 'MonadPlus' transformation @def@ +-- if its argument cannot be cast to type @b@, and like the transformation @ext@ otherwise. +-- Note that 'extMp' behaves exactly like 'extM'. +-- The name 'extMp' is short for "extend MonadPlus transformation". +-- +-- === __Examples__ +-- +-- >>> extMp (\x -> [x,x])(\x -> [not x, x]) True +-- [False,True] +-- +-- >>> extMp (\x -> [x,x])(\x -> [not x, x]) (5 :: Int) +-- [5,5] +-- +-- @since 0.1.0.0 extMp :: ( MonadPlus m , Typeable a , Typeable b ) - => (a -> m a) -> (b -> m b) -> a -> m a + => (a -> m a) + -- ^ The 'MonadPlus' transformation we want to extend + -> (b -> m b) + -- ^ The type-specific 'MonadPlus' transformation + -> a + -- ^ The argument we try to cast to type @b@ + -> m a extMp = extM --- | Extend a generic builder +-- | Extend a generic builder by a type-specific case. +-- The builder created by @extB def ext@ returns @def@ if @ext@ cannot be cast +-- to type @a@, and like @ext@ otherwise. +-- The name 'extB' is short for "extend builder". +-- +-- === __Examples__ +-- +-- >>> extB True 'a' +-- True +-- +-- >>> extB True False +-- False +-- +-- @since 0.1.0.0 extB :: ( Typeable a , Typeable b ) - => a -> b -> a + => a + -- ^ The default result + -> b + -- ^ The argument we try to cast to type @a@ + -> a extB a = maybe a id . cast --- | Extend a generic reader +-- | Extend a generic reader by a type-specific case. +-- The reader created by @extR def ext@ behaves like the reader @def@ +-- if expressions of type @b@ cannot be cast to type @a@, and like the +-- reader @ext@ otherwise. +-- The name 'extR' is short for "extend reader". +-- +-- === __Examples__ +-- +-- >>> extR (Just True) (Just 'a') +-- Just True +-- +-- >>> extR (Just True) (Just False) +-- Just False +-- +-- @since 0.1.0.0 extR :: ( Monad m , Typeable a , Typeable b ) - => m a -> m b -> m a + => m a + -- ^ The generic reader we want to extend + -> m b + -- ^ The type-specific reader + -> m a extR def ext = unR ((R def) `ext0` (R ext)) ------------------------------------------------------------------------------ -- --- Type synonyms for generic function types +-- Types for generic functions -- ------------------------------------------------------------------------------ @@ -223,30 +444,53 @@ -- | Generic transformations, -- i.e., take an \"a\" and return an \"a\" -- +-- @since 0.1.0.0 type GenericT = forall a. Data a => a -> a +-- | The type synonym `GenericT` has a polymorphic type, and can therefore not +-- appear in places where monomorphic types are expected, for example in a list. +-- The newtype `GenericT'` wraps `GenericT` in a newtype to lift this restriction. +-- +-- @since 0.1.0.0 +newtype GenericT' = GT { unGT :: GenericT } -- | Generic queries of type \"r\", -- i.e., take any \"a\" and return an \"r\" -- +-- @since 0.1.0.0 type GenericQ r = forall a. Data a => a -> r +-- | The type synonym `GenericQ` has a polymorphic type, and can therefore not +-- appear in places where monomorphic types are expected, for example in a list. +-- The newtype `GenericQ'` wraps `GenericQ` in a newtype to lift this restriction. +-- +-- @since 0.1.0.0 +newtype GenericQ' r = GQ { unGQ :: GenericQ r } -- | Generic monadic transformations, -- i.e., take an \"a\" and compute an \"a\" -- +-- @since 0.1.0.0 type GenericM m = forall a. Data a => a -> m a +-- | The type synonym `GenericM` has a polymorphic type, and can therefore not +-- appear in places where monomorphic types are expected, for example in a list. +-- The newtype `GenericM'` wraps `GenericM` in a newtype to lift this restriction. +-- +-- @since 0.1.0.0 +newtype GenericM' m = GM { unGM :: GenericM m } -- | Generic builders -- i.e., produce an \"a\". -- +-- @since 0.1.0.0 type GenericB = forall a. Data a => a -- | Generic readers, say monadic builders, -- i.e., produce an \"a\" with the help of a monad \"m\". -- +-- @since 0.1.0.0 type GenericR m = forall a. Data a => m a @@ -254,28 +498,51 @@ -- assumed by gfoldl; there are isomorphisms such as -- GenericT = Generic T. -- +-- @since 0.1.0.0 type Generic c = forall a. Data a => a -> c a --- | Wrapped generic functions; --- recall: [Generic c] would be legal but [Generic' c] not. +-- | The type synonym `Generic` has a polymorphic type, and can therefore not +-- appear in places where monomorphic types are expected, for example in a list. +-- The data type `Generic'` wraps `Generic` in a data type to lift this restriction. -- +-- @since 0.1.0.0 data Generic' c = Generic' { unGeneric' :: Generic c } - --- | Other first-class polymorphic wrappers -newtype GenericT' = GT { unGT :: forall a. Data a => a -> a } -newtype GenericQ' r = GQ { unGQ :: GenericQ r } -newtype GenericM' m = GM { unGM :: forall a. Data a => a -> m a } - +------------------------------------------------------------------------------ +-- +-- Ingredients of generic functions +-- +------------------------------------------------------------------------------ -- | Left-biased choice on maybes +-- +-- === __Examples__ +-- +-- >>> orElse Nothing Nothing +-- Nothing +-- +-- >>> orElse Nothing (Just 'a') +-- Just 'a' +-- +-- >>> orElse (Just 'a') Nothing +-- Just 'a' +-- +-- >>> orElse (Just 'a') (Just 'b') +-- Just 'a' +-- +-- @since 0.1.0.0 orElse :: Maybe a -> Maybe a -> Maybe a x `orElse` y = case x of Just _ -> x Nothing -> y +------------------------------------------------------------------------------ +-- +-- Function combinators on generic functions +-- +------------------------------------------------------------------------------ {- The following variations take "orElse" to the function @@ -289,21 +556,29 @@ -} -- | Choice for monadic transformations +-- +-- @since 0.1.0.0 choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m choiceMp f g x = f x `mplus` g x -- | Choice for monadic queries +-- +-- @since 0.1.0.0 choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r) choiceQ f g x = f x `mplus` g x -- | Recover from the failure of monadic transformation by identity +-- +-- @since 0.1.0.0 recoverMp :: MonadPlus m => GenericM m -> GenericM m recoverMp f = f `choiceMp` return -- | Recover from the failure of monadic query by a constant +-- +-- @since 0.1.0.0 recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r) recoverQ r f = f `choiceQ` const (return r) @@ -319,6 +594,8 @@ #endif -- | Flexible type extension +-- +-- @since 0.3 ext1 :: (Data a, Typeable1 t) => c a -> (forall d. Data d => c (t d)) @@ -327,6 +604,8 @@ -- | Type extension of transformations for unary type constructors +-- +-- @since 0.1.0.0 ext1T :: (Data d, Typeable1 t) => (forall e. Data e => e -> e) -> (forall f. Data f => t f -> t f) @@ -335,6 +614,8 @@ -- | Type extension of monadic transformations for type constructors +-- +-- @since 0.1.0.0 ext1M :: (Monad m, Data d, Typeable1 t) => (forall e. Data e => e -> m e) -> (forall f. Data f => t f -> m (t f)) @@ -343,6 +624,8 @@ -- | Type extension of queries for type constructors +-- +-- @since 0.1.0.0 ext1Q :: (Data d, Typeable1 t) => (d -> q) -> (forall e. Data e => t e -> q) @@ -351,6 +634,8 @@ -- | Type extension of readers for type constructors +-- +-- @since 0.1.0.0 ext1R :: (Monad m, Data d, Typeable1 t) => m d -> (forall e. Data e => m (t e)) @@ -359,6 +644,8 @@ -- | Type extension of builders for type constructors +-- +-- @since 0.2 ext1B :: (Data a, Typeable1 t) => a -> (forall b. Data b => (t b)) @@ -378,6 +665,8 @@ -- | Type extension of transformations for unary type constructors +-- +-- @since 0.3 ext2T :: (Data d, Typeable2 t) => (forall e. Data e => e -> e) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> t d1 d2) @@ -386,6 +675,8 @@ -- | Type extension of monadic transformations for type constructors +-- +-- @since 0.3 ext2M :: (Monad m, Data d, Typeable2 t) => (forall e. Data e => e -> m e) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> m (t d1 d2)) @@ -394,6 +685,8 @@ -- | Type extension of queries for type constructors +-- +-- @since 0.3 ext2Q :: (Data d, Typeable2 t) => (d -> q) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> q) @@ -402,6 +695,8 @@ -- | Type extension of readers for type constructors +-- +-- @since 0.3 ext2R :: (Monad m, Data d, Typeable2 t) => m d -> (forall d1 d2. (Data d1, Data d2) => m (t d1 d2)) @@ -410,6 +705,8 @@ -- | Type extension of builders for type constructors +-- +-- @since 0.3 ext2B :: (Data a, Typeable2 t) => a -> (forall d1 d2. (Data d1, Data d2) => (t d1 d2)) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/src/Data/Generics/Builders.hs new/syb-0.7.2.4/src/Data/Generics/Builders.hs --- old/syb-0.7.2.3/src/Data/Generics/Builders.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/src/Data/Generics/Builders.hs 2001-09-09 03:46:40.000000000 +0200 @@ -6,7 +6,7 @@ -- Module : Data.Generics.Builders -- Copyright : (c) 2008 Universiteit Utrecht -- License : BSD-style --- +-- -- Maintainer : gener...@haskell.org -- Stability : experimental -- Portability : non-portable @@ -22,6 +22,8 @@ -- | Construct the empty value for a datatype. For algebraic datatypes, the -- leftmost constructor is chosen. +-- +-- @since 0.2 empty :: forall a. Data a => a empty = general `extB` char @@ -43,6 +45,8 @@ -- | Return a list of values of a datatype. Each value is one of the possible -- constructors of the datatype, populated with 'empty' values. +-- +-- @since 0.2 constrs :: forall a. Data a => [a] constrs = general `extB` char diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/src/Data/Generics/Schemes.hs new/syb-0.7.2.4/src/Data/Generics/Schemes.hs --- old/syb-0.7.2.3/src/Data/Generics/Schemes.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/src/Data/Generics/Schemes.hs 2001-09-09 03:46:40.000000000 +0200 @@ -48,7 +48,8 @@ import Control.Monad -- | Apply a transformation everywhere in bottom-up manner - +-- +-- @since 0.1.0.0 everywhere :: (forall a. Data a => a -> a) -> (forall a. Data a => a -> a) @@ -62,6 +63,8 @@ go = f . gmapT go -- | Apply a transformation everywhere in top-down manner +-- +-- @since 0.1.0.0 everywhere' :: (forall a. Data a => a -> a) -> (forall a. Data a => a -> a) @@ -73,6 +76,8 @@ -- | Variation on everywhere with an extra stop condition +-- +-- @since 0.1.0.0 everywhereBut :: GenericQ Bool -> GenericT -> GenericT -- Guarded to let traversal cease if predicate q holds for x @@ -85,6 +90,8 @@ -- | Monadic variation on everywhere +-- +-- @since 0.1.0.0 everywhereM :: forall m. Monad m => GenericM m -> GenericM m -- Bottom-up order is also reflected in order of do-actions @@ -97,6 +104,8 @@ -- | Apply a monadic transformation at least somewhere +-- +-- @since 0.1.0.0 somewhere :: forall m. MonadPlus m => GenericM m -> GenericM m -- We try "f" in top-down manner, but descent into "x" when we fail @@ -110,6 +119,8 @@ -- | Summarise all nodes in top-down, left-to-right order +-- +-- @since 0.1.0.0 everything :: forall r. (r -> r -> r) -> GenericQ r -> GenericQ r -- Apply f to x to summarise top-level node; @@ -122,6 +133,8 @@ go x = foldl k (f x) (gmapQ go x) -- | Variation of "everything" with an added stop condition +-- +-- @since 0.3 everythingBut :: forall r. (r -> r -> r) -> GenericQ (r, Bool) -> GenericQ r everythingBut k f = go where @@ -133,6 +146,8 @@ -- | Summarise all nodes in top-down, left-to-right order, carrying some state -- down the tree during the computation, but not left-to-right to siblings. +-- +-- @since 0.3.7 everythingWithContext :: forall s r. s -> (r -> r -> r) -> GenericQ (s -> (r, s)) -> GenericQ r everythingWithContext s0 f q = go s0 where @@ -141,11 +156,15 @@ where (r, s') = q x s -- | Get a list of all entities that meet a predicate +-- +-- @since 0.1.0.0 listify :: Typeable r => (r -> Bool) -> GenericQ [r] listify p = everything (++) ([] `mkQ` (\x -> if p x then [x] else [])) -- | Look up a subterm by means of a maybe-typed filter +-- +-- @since 0.1.0.0 something :: GenericQ (Maybe u) -> GenericQ (Maybe u) -- "something" can be defined in terms of "everything" @@ -159,6 +178,7 @@ -- 2nd argument o is for reduction of results from subterms; -- 3rd argument f updates the synthesised data according to the given term -- +-- @since 0.1.0.0 synthesize :: forall s t. s -> (t -> s -> s) -> GenericQ (s -> t) -> GenericQ t synthesize z o f = go where @@ -167,36 +187,50 @@ -- | Compute size of an arbitrary data structure +-- +-- @since 0.1.0.0 gsize :: Data a => a -> Int gsize t = 1 + sum (gmapQ gsize t) -- | Count the number of immediate subterms of the given term +-- +-- @since 0.1.0.0 glength :: GenericQ Int glength = length . gmapQ (const ()) -- | Determine depth of the given term +-- +-- @since 0.1.0.0 gdepth :: GenericQ Int gdepth = (+) 1 . foldr max 0 . gmapQ gdepth -- | Determine the number of all suitable nodes in a given term +-- +-- @since 0.1.0.0 gcount :: GenericQ Bool -> GenericQ Int gcount p = everything (+) (\x -> if p x then 1 else 0) -- | Determine the number of all nodes in a given term +-- +-- @since 0.1.0.0 gnodecount :: GenericQ Int gnodecount = gcount (const True) -- | Determine the number of nodes of a given type in a given term +-- +-- @since 0.1.0.0 gtypecount :: Typeable a => a -> GenericQ Int gtypecount (_::a) = gcount (False `mkQ` (\(_::a) -> True)) -- | Find (unambiguously) an immediate subterm of a given type +-- +-- @since 0.1.0.0 gfindtype :: (Data x, Typeable y) => x -> Maybe y gfindtype = singleton . foldl unJust [] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/src/Data/Generics/Text.hs new/syb-0.7.2.4/src/Data/Generics/Text.hs --- old/syb-0.7.2.3/src/Data/Generics/Text.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/src/Data/Generics/Text.hs 2001-09-09 03:46:40.000000000 +0200 @@ -40,10 +40,14 @@ -- | Generic show: an alternative to \"deriving Show\" +-- +-- @since 0.1.0.0 gshow :: Data a => a -> String gshow x = gshows x "" -- | Generic shows +-- +-- @since 0.2 gshows :: Data a => a -> ShowS -- This is a prefix-show using surrounding "(" and ")", @@ -57,6 +61,8 @@ -- | Generic read: an alternative to \"deriving Read\" +-- +-- @since 0.1.0.0 gread :: Data a => ReadS a {- diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/src/Data/Generics/Twins.hs new/syb-0.7.2.4/src/Data/Generics/Twins.hs --- old/syb-0.7.2.3/src/Data/Generics/Twins.hs 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/src/Data/Generics/Twins.hs 2001-09-09 03:46:40.000000000 +0200 @@ -82,7 +82,8 @@ --------------------------------------------------------------} -- | gfoldl with accumulation - +-- +-- @since 0.1.0.0 gfoldlAccum :: Data d => (forall e r. Data e => a -> c (e -> r) -> e -> (a, c r)) -> (forall g. a -> g -> (a, c g)) @@ -99,6 +100,8 @@ -- | gmapT with accumulation +-- +-- @since 0.1.0.0 gmapAccumT :: Data d => (forall e. Data e => a -> e -> (a,e)) -> a -> d -> (a, d) @@ -111,6 +114,8 @@ -- | Applicative version +-- +-- @since 0.2 gmapAccumA :: forall b d a. (Data d, Applicative a) => (forall e. Data e => b -> e -> (b, a e)) -> b -> d -> (b, a d) @@ -127,6 +132,8 @@ -- | gmapM with accumulation +-- +-- @since 0.1.0.0 gmapAccumM :: (Data d, Monad m) => (forall e. Data e => a -> e -> (a, m e)) -> a -> d -> (a, m d) @@ -138,6 +145,8 @@ -- | gmapQl with accumulation +-- +-- @since 0.1.0.0 gmapAccumQl :: Data d => (r -> r' -> r) -> r @@ -152,6 +161,8 @@ -- | gmapQr with accumulation +-- +-- @since 0.1.0.0 gmapAccumQr :: Data d => (r' -> r -> r) -> r @@ -166,6 +177,8 @@ -- | gmapQ with accumulation +-- +-- @since 0.1.0.0 gmapAccumQ :: Data d => (forall e. Data e => a -> e -> (a,q)) -> a -> d -> (a, [q]) @@ -201,6 +214,8 @@ -- | Twin map for transformation +-- +-- @since 0.1.0.0 gzipWithT :: GenericQ (GenericT) -> GenericQ (GenericT) gzipWithT f x y = case gmapAccumT perkid funs y of ([], c) -> c @@ -212,6 +227,8 @@ -- | Twin map for monadic transformation +-- +-- @since 0.1.0.0 gzipWithM :: Monad m => GenericQ (GenericM m) -> GenericQ (GenericM m) gzipWithM f x y = case gmapAccumM perkid funs y of ([], c) -> c @@ -222,6 +239,8 @@ -- | Twin map for queries +-- +-- @since 0.1.0.0 gzipWithQ :: GenericQ (GenericQ r) -> GenericQ (GenericQ [r]) gzipWithQ f x y = case gmapAccumQ perkid funs y of ([], r) -> r @@ -239,6 +258,8 @@ ------------------------------------------------------------------------------ -- | Generic equality: an alternative to \"deriving Eq\" +-- +-- @since 0.1.0.0 geq :: Data a => a -> a -> Bool {- @@ -264,6 +285,8 @@ -- | Generic zip controlled by a function with type-specific branches +-- +-- @since 0.1.0.0 gzip :: GenericQ (GenericM Maybe) -> GenericQ (GenericM Maybe) -- See testsuite/.../Generics/gzip.hs for an illustration gzip f = go @@ -277,6 +300,8 @@ else Nothing -- | Generic comparison: an alternative to \"deriving Ord\" +-- +-- @since 0.5 gcompare :: Data a => a -> a -> Ordering gcompare = gcompare' where diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/syb-0.7.2.3/syb.cabal new/syb-0.7.2.4/syb.cabal --- old/syb-0.7.2.3/syb.cabal 2001-09-09 03:46:40.000000000 +0200 +++ new/syb-0.7.2.4/syb.cabal 2001-09-09 03:46:40.000000000 +0200 @@ -1,10 +1,10 @@ name: syb -version: 0.7.2.3 +version: 0.7.2.4 license: BSD3 license-file: LICENSE author: Ralf Lammel, Simon Peyton Jones, Jose Pedro Magalhaes maintainer: Sergey Vinokurov <serg....@gmail.com> -homepage: http://www.cs.uu.nl/wiki/GenericProgramming/SYB +homepage: https://github.com/dreixel/syb bug-reports: https://github.com/dreixel/syb/issues synopsis: Scrap Your Boilerplate description: