Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-rio-prettyprint for 
openSUSE:Factory checked in at 2023-01-18 13:10:25
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-rio-prettyprint (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-rio-prettyprint.new.32243 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-rio-prettyprint"

Wed Jan 18 13:10:25 2023 rev:7 rq:1059101 version:0.1.4.0

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-rio-prettyprint/ghc-rio-prettyprint.changes  
2020-12-22 11:45:38.769823272 +0100
+++ 
/work/SRC/openSUSE:Factory/.ghc-rio-prettyprint.new.32243/ghc-rio-prettyprint.changes
       2023-01-18 13:10:48.860822227 +0100
@@ -1,0 +2,6 @@
+Tue Nov 29 05:38:24 UTC 2022 - Peter Simons <[email protected]>
+
+- Update rio-prettyprint to version 0.1.4.0.
+  Upstream does not provide a change log file.
+
+-------------------------------------------------------------------

Old:
----
  rio-prettyprint-0.1.1.0.tar.gz

New:
----
  rio-prettyprint-0.1.4.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-rio-prettyprint.spec ++++++
--- /var/tmp/diff_new_pack.QsGRIq/_old  2023-01-18 13:10:49.500826021 +0100
+++ /var/tmp/diff_new_pack.QsGRIq/_new  2023-01-18 13:10:49.504826045 +0100
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-rio-prettyprint
 #
-# Copyright (c) 2020 SUSE LLC
+# Copyright (c) 2022 SUSE LLC
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -18,7 +18,7 @@
 
 %global pkg_name rio-prettyprint
 Name:           ghc-%{pkg_name}
-Version:        0.1.1.0
+Version:        0.1.4.0
 Release:        0
 Summary:        Pretty-printing for RIO
 License:        BSD-3-Clause

++++++ rio-prettyprint-0.1.1.0.tar.gz -> rio-prettyprint-0.1.4.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/rio-prettyprint-0.1.1.0/rio-prettyprint.cabal 
new/rio-prettyprint-0.1.4.0/rio-prettyprint.cabal
--- old/rio-prettyprint-0.1.1.0/rio-prettyprint.cabal   2020-08-05 
05:36:38.000000000 +0200
+++ new/rio-prettyprint-0.1.4.0/rio-prettyprint.cabal   2022-11-29 
06:36:13.000000000 +0100
@@ -1,13 +1,11 @@
 cabal-version: 1.12
 
--- This file has been generated from package.yaml by hpack version 0.33.0.
+-- This file has been generated from package.yaml by hpack version 0.35.0.
 --
 -- see: https://github.com/sol/hpack
---
--- hash: bf50273f06f81eee478b5dd1dc56a8006c9fd634dc6eb2a70fd70821b5a1cade
 
 name:           rio-prettyprint
-version:        0.1.1.0
+version:        0.1.4.0
 synopsis:       Pretty-printing for RIO
 description:    Combine RIO's log capabilities with pretty printing
 category:       Development
@@ -28,6 +26,8 @@
   exposed-modules:
       RIO.PrettyPrint
       RIO.PrettyPrint.DefaultStyles
+      RIO.PrettyPrint.PrettyException
+      RIO.PrettyPrint.Simple
       RIO.PrettyPrint.StylesUpdate
       RIO.PrettyPrint.Types
       Text.PrettyPrint.Leijen.Extended
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/rio-prettyprint-0.1.1.0/src/RIO/PrettyPrint/PrettyException.hs 
new/rio-prettyprint-0.1.4.0/src/RIO/PrettyPrint/PrettyException.hs
--- old/rio-prettyprint-0.1.1.0/src/RIO/PrettyPrint/PrettyException.hs  
1970-01-01 01:00:00.000000000 +0100
+++ new/rio-prettyprint-0.1.4.0/src/RIO/PrettyPrint/PrettyException.hs  
2022-11-29 06:36:10.000000000 +0100
@@ -0,0 +1,77 @@
+{-# LANGUAGE NoImplicitPrelude         #-}
+{-# LANGUAGE ExistentialQuantification #-}
+{-# LANGUAGE StandaloneDeriving        #-}
+
+-- | This module provides a type representing pretty exceptions. It can be used
+-- as in the example below:
+--
+-- > {-# LANGUAGE NoImplicitPrelude #-}
+-- > {-# LANGUAGE OverloadedStrings #-}
+-- >
+-- > module Main (main) where
+-- >
+-- > import RIO
+-- >          ( Exception, Handler (..), IO, RIO, Show, SomeException (..), 
Typeable
+-- >          , ($), catches, displayException, exitFailure, fromString, 
logError
+-- >          , mempty, throwIO
+-- >          )
+-- > import RIO.PrettyPrint
+-- >          ( Pretty (..), Style (..), (<+>), prettyError, prettyInfo, style 
)
+-- > import RIO.PrettyPrint.PrettyException ( PrettyException (..) )
+-- > import RIO.PrettyPrint.Simple ( SimplePrettyApp, runSimplePrettyApp )
+-- >
+-- > main :: IO ()
+-- > main = runSimplePrettyApp 80 mempty (action `catches` handleExceptions)
+-- >  where
+-- >   action :: RIO SimplePrettyApp ()
+-- >   action = do
+-- >       prettyInfo "Running action!"
+-- >       throwIO (PrettyException MyPrettyException)
+-- >
+-- >  handleExceptions :: [Handler (RIO SimplePrettyApp) ()]
+-- >  handleExceptions =
+-- >    [ Handler handlePrettyException
+-- >    , Handler handleSomeException
+-- >    ]
+-- >
+-- >  handlePrettyException :: PrettyException -> RIO SimplePrettyApp ()
+-- >  handlePrettyException e = do
+-- >    prettyError $ pretty e
+-- >    exitFailure
+-- >
+-- >  handleSomeException :: SomeException -> RIO SimplePrettyApp ()
+-- >  handleSomeException (SomeException e) = do
+-- >    logError $ fromString $ displayException e
+-- >    exitFailure
+-- >
+-- > data MyPrettyException
+-- >   = MyPrettyException
+-- >   deriving (Show, Typeable)
+-- >
+-- > instance Pretty MyPrettyException where
+-- >   pretty MyPrettyException =
+-- >     "My" <+> style Highlight "pretty" <+> "exception!"
+-- >
+-- > instance Exception MyPrettyException
+--
+module RIO.PrettyPrint.PrettyException
+  ( PrettyException (..)
+  ) where
+
+import RIO (Exception (..), Show, Typeable)
+import Text.PrettyPrint.Leijen.Extended (Pretty (..))
+
+-- | Type representing pretty exceptions.
+--
+-- @since 0.1.4.0
+data PrettyException
+  = forall e. (Exception e, Pretty e) => PrettyException e
+  deriving Typeable
+
+deriving instance Show PrettyException
+
+instance Pretty PrettyException where
+  pretty (PrettyException e) = pretty e
+
+instance Exception PrettyException where
+  displayException (PrettyException e) = displayException e
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/rio-prettyprint-0.1.1.0/src/RIO/PrettyPrint/Simple.hs 
new/rio-prettyprint-0.1.4.0/src/RIO/PrettyPrint/Simple.hs
--- old/rio-prettyprint-0.1.1.0/src/RIO/PrettyPrint/Simple.hs   1970-01-01 
01:00:00.000000000 +0100
+++ new/rio-prettyprint-0.1.4.0/src/RIO/PrettyPrint/Simple.hs   2022-11-13 
03:18:03.000000000 +0100
@@ -0,0 +1,98 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+{-|
+This module exports a 'SimplePrettyApp' type, for providing a basic environment
+including pretty printing functionality.
+-}
+module RIO.PrettyPrint.Simple
+  ( SimplePrettyApp
+  , mkSimplePrettyApp
+  , runSimplePrettyApp
+  ) where
+
+import System.Environment (lookupEnv)
+
+import RIO
+         ( Bool (..), HasLogFunc (..), Int, LogFunc, Maybe (..), MonadIO, RIO
+         , ($), (<$>), isJust, lens, liftIO, logOptionsHandle, maybe, pure
+         , runRIO, setLogUseColor, stderr, withLogFunc
+         )
+import RIO.Process
+         ( HasProcessContext (..), ProcessContext, mkDefaultProcessContext )
+
+import RIO.PrettyPrint (HasTerm (..))
+import RIO.PrettyPrint.StylesUpdate (HasStylesUpdate (..), StylesUpdate (..))
+
+-- | A simple, non-customizable environment type, which provides
+-- pretty printing functionality.
+--
+-- @since 0.1.3.0
+data SimplePrettyApp = SimplePrettyApp
+  { spaLogFunc :: !LogFunc
+  , spaProcessContext :: !ProcessContext
+  , spaUseColor :: !Bool
+  , spaTermWidth :: !Int
+  , spaStylesUpdate :: !StylesUpdate
+  }
+
+instance HasLogFunc SimplePrettyApp where
+  logFuncL = lens spaLogFunc (\x y -> x { spaLogFunc = y })
+
+instance HasProcessContext SimplePrettyApp where
+  processContextL = lens spaProcessContext (\x y -> x { spaProcessContext = y 
})
+
+instance HasStylesUpdate SimplePrettyApp where
+  stylesUpdateL = lens spaStylesUpdate (\x y -> x { spaStylesUpdate = y })
+
+instance HasTerm SimplePrettyApp where
+  useColorL = lens spaUseColor (\x y -> x { spaUseColor = y })
+  termWidthL = lens spaTermWidth (\x y -> x { spaTermWidth = y })
+
+-- | Constructor for 'SimplePrettyApp'. If 'ProcessContext' is not supplied
+-- 'mkDefaultProcessContext' will be used to create it.
+--
+-- @since 0.1.3.0
+mkSimplePrettyApp
+  :: MonadIO m
+  => LogFunc
+  -> Maybe ProcessContext
+  -> Bool
+     -- ^ Use color?
+  -> Int
+     -- ^ Terminal width
+  -> StylesUpdate
+  -> m SimplePrettyApp
+mkSimplePrettyApp logFunc mProcessContext useColor termWidth stylesUpdate = do
+  processContext <- maybe mkDefaultProcessContext pure mProcessContext
+  pure $ SimplePrettyApp
+    { spaLogFunc = logFunc
+    , spaProcessContext = processContext
+    , spaUseColor = useColor
+    , spaTermWidth = termWidth
+    , spaStylesUpdate = stylesUpdate
+    }
+
+-- | Run with a default configured @SimplePrettyApp@, consisting of:
+--
+-- * Logging to 'stderr'
+--
+-- * If the @RIO_VERBOSE@ environment variable is set, turns on verbose logging
+--
+-- * Default process context
+--
+-- * Logging using color
+--
+-- @since 0.1.3.0
+runSimplePrettyApp
+  :: MonadIO m
+  => Int
+     -- ^ Terminal width
+  -> StylesUpdate
+  -> RIO SimplePrettyApp a
+  -> m a
+runSimplePrettyApp termWidth stylesUpdate m = liftIO $ do
+  verbose <- isJust <$> lookupEnv "RIO_VERBOSE"
+  lo <- setLogUseColor True <$> logOptionsHandle stderr verbose
+  withLogFunc lo $ \lf -> do
+    simplePrettyApp <- mkSimplePrettyApp lf Nothing True termWidth stylesUpdate
+    runRIO simplePrettyApp m
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/rio-prettyprint-0.1.1.0/src/RIO/PrettyPrint.hs 
new/rio-prettyprint-0.1.4.0/src/RIO/PrettyPrint.hs
--- old/rio-prettyprint-0.1.1.0/src/RIO/PrettyPrint.hs  2020-08-05 
05:25:34.000000000 +0200
+++ new/rio-prettyprint-0.1.4.0/src/RIO/PrettyPrint.hs  2022-11-29 
06:36:10.000000000 +0100
@@ -21,16 +21,18 @@
     , logLevelToStyle
       -- * Formatting utils
     , bulletedList
+    , mkNarrativeList
     , spacedBulletedList
     , debugBracket
       -- * Re-exports from "Text.PrettyPrint.Leijen.Extended"
-    , Pretty (..), StyleDoc, StyleAnn (..)
+    , Pretty (..), StyleDoc (..), StyleAnn (..)
     , nest, line, linebreak, group, softline, softbreak
     , align, hang, indent, encloseSep
     , (<+>)
     , hsep, vsep, fillSep, sep, hcat, vcat, fillCat, cat, punctuate
     , fill, fillBreak
     , enclose, squotes, dquotes, parens, angles, braces, brackets
+    , string
     , indentAfterLabel, wordDocs, flow
       -- * Re-exports from "RIO.PrettyPrint.Types.PrettyPrint"
     , Style (..)
@@ -47,7 +49,7 @@
                      fill, fillBreak, fillCat, fillSep, group, hang, hcat, 
hsep,
                      indent, line, linebreak,
                      nest, parens, punctuate, sep, softbreak, softline, 
squotes,
-                     styleAnn, vcat, vsep)
+                     string, styleAnn, vcat, vsep)
 
 class (HasLogFunc env, HasStylesUpdate env) => HasTerm env where
   useColorL :: Lens' env Bool
@@ -171,6 +173,31 @@
 bulletedList :: [StyleDoc] -> StyleDoc
 bulletedList = mconcat . intersperse line . map (("*" <+>) . align)
 
+-- | A helper function to yield a narrative list from a list of items, with a
+-- final fullstop. For example, helps produce the output
+-- @\"apple, ball and cat.\"@ (no serial comma) or @\"apple, ball, and cat.\"@
+-- (serial comma) from @[\"apple\", \"ball\", \"cat\"]@.
+--
+-- @since 0.1.4.0
+mkNarrativeList :: Pretty a
+                => Maybe Style
+                -- ^ Style the items in the list?
+                -> Bool
+                -- ^ Use a serial comma?
+                -> [a]
+                -> [StyleDoc]
+mkNarrativeList _ _ [] = []
+mkNarrativeList mStyle _ [x] = [maybe id style mStyle (pretty x) <> "."]
+mkNarrativeList mStyle useSerialComma [x1, x2] =
+      mStyle' (pretty x1) <> (if useSerialComma then "," else mempty)
+    : "and"
+    : mkNarrativeList mStyle useSerialComma [x2]
+  where
+    mStyle' = maybe id style mStyle
+mkNarrativeList mStyle useSerialComma (x:xs) =
+      maybe id style mStyle (pretty x) <> ","
+    : mkNarrativeList mStyle useSerialComma xs
+
 -- | Display a bulleted list of 'StyleDoc' with a blank line between
 -- each.
 spacedBulletedList :: [StyleDoc] -> StyleDoc
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/rio-prettyprint-0.1.1.0/src/Text/PrettyPrint/Leijen/Extended.hs 
new/rio-prettyprint-0.1.4.0/src/Text/PrettyPrint/Leijen/Extended.hs
--- old/rio-prettyprint-0.1.1.0/src/Text/PrettyPrint/Leijen/Extended.hs 
2020-08-05 05:25:34.000000000 +0200
+++ new/rio-prettyprint-0.1.4.0/src/Text/PrettyPrint/Leijen/Extended.hs 
2022-11-29 06:36:10.000000000 +0100
@@ -24,7 +24,7 @@
   --
   -- See "System.Console.ANSI" for 'SGR' values to use beyond the colors
   -- provided.
-  StyleDoc, StyleAnn(..),
+  StyleDoc (..), StyleAnn(..),
   -- hDisplayAnsi,
   displayAnsi, displayPlain, renderDefault,
 
@@ -86,11 +86,12 @@
   -- @
 
   -- ** Primitive type documents
-  -- Entirely omitted:
+  -- Omitted compared to the original:
   --
   -- @
-  -- string, int, integer, float, double, rational, bool,
+  -- int, integer, float, double, rational, bool,
   -- @
+  string,
 
   -- ** Semantic annotations
   annotate, noAnnotate, styleAnn
@@ -173,7 +174,7 @@
 
 -- |A document annotated by a style
 newtype StyleDoc = StyleDoc { unStyleDoc :: Doc StyleAnn }
-  deriving IsString
+  deriving (IsString, Show)
 
 -- |An ANSI code(s) annotation.
 newtype AnsiAnn = AnsiAnn [SGR]
@@ -386,6 +387,17 @@
 brackets :: StyleDoc -> StyleDoc
 brackets = StyleDoc . P.brackets . unStyleDoc
 
+-- | The document @string s@ concatenates all characters in @s@ using @line@ 
for
+-- newline characters and @char@ for all other characters. It is used whenever
+-- the text contains newline characters.
+--
+-- @since 0.1.4.0
+string :: String -> StyleDoc
+string "" = mempty
+string ('\n':s) = line <> string s
+string s        = let (xs, ys) = span (/='\n') s
+                  in  fromString xs <> string ys
+
 annotate :: StyleAnn -> StyleDoc -> StyleDoc
 annotate a = StyleDoc . P.annotate a . unStyleDoc
 

Reply via email to