diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs index 4c333c32edf37c5d7cdbecc268bb8200698f3dde..bb269847b6a011e3f671969a6f300b2af680a26b 100644 --- a/libraries/base/Control/Monad/Fix.hs +++ b/libraries/base/Control/Monad/Fix.hs @@ -29,6 +29,7 @@ import Data.Function ( fix ) import Data.Maybe import Data.Monoid ( Dual(..), Sum(..), Product(..) , First(..), Last(..), Alt(..), Ap(..) ) +import Data.Ord ( Down(..) ) import GHC.Base ( Monad, NonEmpty(..), errorWithoutStackTrace, (.) ) import GHC.Generics import GHC.List ( head, tail ) @@ -149,3 +150,10 @@ instance (MonadFix f, MonadFix g) => MonadFix (f :*: g) where where fstP (a :*: _) = a sndP (_ :*: b) = b + +-- Instances for Data.Ord + +-- | @since 4.12.0.0 +instance MonadFix Down where + mfix f = Down (fix (getDown . f)) + where getDown (Down x) = x diff --git a/libraries/base/Control/Monad/Zip.hs b/libraries/base/Control/Monad/Zip.hs index d484d1fa8358cf2e01ccc23123d293311bada1e9..beef913119cb607af63a23d79c95cab1aaa2e4a3 100644 --- a/libraries/base/Control/Monad/Zip.hs +++ b/libraries/base/Control/Monad/Zip.hs @@ -21,6 +21,7 @@ module Control.Monad.Zip where import Control.Monad (liftM, liftM2) import Data.Functor.Identity import Data.Monoid +import Data.Ord ( Down(..) ) import Data.Proxy import qualified Data.List.NonEmpty as NE import GHC.Generics @@ -124,3 +125,9 @@ instance MonadZip f => MonadZip (M1 i c f) where -- | @since 4.9.0.0 instance (MonadZip f, MonadZip g) => MonadZip (f :*: g) where mzipWith f (x1 :*: y1) (x2 :*: y2) = mzipWith f x1 x2 :*: mzipWith f y1 y2 + +-- instances for Data.Ord + +-- | @since 4.12.0.0 +instance MonadZip Down where + mzipWith = liftM2 diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 194df0800391fb44a816c483e6238903846e7a02..fa199f1117ffd5a9266ed74eec9e003286699575 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1334,3 +1334,9 @@ deriving instance Data SourceStrictness -- | @since 4.9.0.0 deriving instance Data DecidedStrictness + +---------------------------------------------------------------------------- +-- Data instances for Data.Ord + +-- | @since 4.12.0.0 +deriving instance Data a => Data (Down a) diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index 47f22e343bbf10210d6e8edf29683194ce3355e3..847eb56dcfe23d77a4ceba840611f726ce94653a 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -505,6 +505,10 @@ deriving instance Foldable UInt -- | @since 4.9.0.0 deriving instance Foldable UWord +-- Instances for Data.Ord +-- | @since 4.12.0.0 +deriving instance Foldable Down + -- | Monadic fold over the elements of a structure, -- associating to the right, i.e. from right to left. foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b diff --git a/libraries/base/Data/Functor/Classes.hs b/libraries/base/Data/Functor/Classes.hs index 32d9929e32e8a420ec5becb532f7c38b617535e2..e44c817b641abf928fd8626f0a232451bcc527e5 100644 --- a/libraries/base/Data/Functor/Classes.hs +++ b/libraries/base/Data/Functor/Classes.hs @@ -70,6 +70,7 @@ import Data.Functor.Identity (Identity(Identity)) import Data.Proxy (Proxy(Proxy)) import Data.List.NonEmpty (NonEmpty(..)) import Data.Monoid (mappend) +import Data.Ord (Down(Down)) import GHC.Read (expectP, list, paren) @@ -644,6 +645,24 @@ instance Read1 Proxy where liftReadListPrec = liftReadListPrecDefault liftReadList = liftReadListDefault +-- | @since 4.12.0.0 +instance Eq1 Down where + liftEq eq (Down x) (Down y) = eq x y + +-- | @since 4.12.0.0 +instance Ord1 Down where + liftCompare comp (Down x) (Down y) = comp x y + +-- | @since 4.12.0.0 +instance Read1 Down where + liftReadsPrec rp _ = readsData $ + readsUnaryWith rp "Down" Down + +-- | @since 4.12.0.0 +instance Show1 Down where + liftShowsPrec sp _ d (Down x) = showsUnaryWith sp "Down" d x + + -- Building blocks -- | @'readsData' p d@ is a parser for datatypes where each alternative diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index bed2ef93ab30aa089a3027ee14df58d8e2c84c1c..5e88dc7dd1a9bc7be97c20a22f9e3f730182b272 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -62,6 +62,7 @@ import Data.Functor.Identity ( Identity(..) ) import Data.Functor.Utils ( StateL(..), StateR(..) ) import Data.Monoid ( Dual(..), Sum(..), Product(..), First(..), Last(..), Alt(..), Ap(..) ) +import Data.Ord ( Down(..) ) import Data.Proxy ( Proxy(..) ) import GHC.Arr @@ -360,6 +361,10 @@ deriving instance Traversable UInt -- | @since 4.9.0.0 deriving instance Traversable UWord +-- Instance for Data.Ord +-- | @since 4.12.0.0 +deriving instance Traversable Down + -- general functions -- | 'for' is 'traverse' with its arguments flipped. For a version diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index 05a96b98ebfc6610d66b818334d3d37630eab61e..34425f2b5f80b61084dfbb9396e50a9d14a1c26e 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -731,6 +731,7 @@ module GHC.Generics ( -- We use some base types import Data.Either ( Either (..) ) import Data.Maybe ( Maybe(..), fromMaybe ) +import Data.Ord ( Down(..) ) import GHC.Integer ( Integer, integerToInt ) import GHC.Prim ( Addr#, Char#, Double#, Float#, Int#, Word# ) import GHC.Ptr ( Ptr ) @@ -1435,6 +1436,9 @@ deriving instance Generic ((,,,,,) a b c d e f) -- | @since 4.6.0.0 deriving instance Generic ((,,,,,,) a b c d e f g) +-- | @since 4.12.0.0 +deriving instance Generic (Down a) + -- | @since 4.6.0.0 deriving instance Generic1 [] @@ -1469,6 +1473,9 @@ deriving instance Generic1 ((,,,,,) a b c d e) -- | @since 4.6.0.0 deriving instance Generic1 ((,,,,,,) a b c d e f) +-- | @since 4.12.0.0 +deriving instance Generic1 Down + -------------------------------------------------------------------------------- -- Copied from the singletons package -------------------------------------------------------------------------------- diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 9e896d367177a637d0d23fd4771976518b638ee6..43bdf0256c68818231d303ddeb10476e1a2b6c83 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -37,6 +37,11 @@ * `Control.Exception.throw` is now levity polymorphic. (#15180) + * `Data.Ord.Down` now has a number of new instances. These include: + `MonadFix`, `MonadZip`, `Data`, `Foldable`, `Traversable`, `Eq1`, `Ord1`, + `Read1`, `Show1`, `Generic`, `Generic1`. (#15098) + + ## 4.11.1.0 *TBA* * Bundled with GHC 8.4.2 diff --git a/testsuite/tests/annotations/should_fail/annfail10.stderr b/testsuite/tests/annotations/should_fail/annfail10.stderr index 9aa4c4047f14f350c117e63e4d5e9523145a3d30..d29a861566cd4456d672298ae8fafc667a80af93 100644 --- a/testsuite/tests/annotations/should_fail/annfail10.stderr +++ b/testsuite/tests/annotations/should_fail/annfail10.stderr @@ -10,7 +10,7 @@ annfail10.hs:9:1: error: instance Data.Data.Data Ordering -- Defined in ‘Data.Data’ instance Data.Data.Data Integer -- Defined in ‘Data.Data’ ...plus 15 others - ...plus 46 instances involving out-of-scope types + ...plus 47 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the annotation: {-# ANN f 1 #-} @@ -23,6 +23,6 @@ annfail10.hs:9:11: error: instance Num Double -- Defined in ‘GHC.Float’ instance Num Float -- Defined in ‘GHC.Float’ ...plus two others - ...plus 18 instances involving out-of-scope types + ...plus 19 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the annotation: {-# ANN f 1 #-} diff --git a/testsuite/tests/ghci/scripts/T10963.stderr b/testsuite/tests/ghci/scripts/T10963.stderr index de0b094ac42c997bdd76b4eaeb7fa8aa3ee45974..2efd138be8032f41342cb44102dc3fb53e9114ad 100644 --- a/testsuite/tests/ghci/scripts/T10963.stderr +++ b/testsuite/tests/ghci/scripts/T10963.stderr @@ -8,5 +8,5 @@ instance Num Double -- Defined in ‘GHC.Float’ instance Num Float -- Defined in ‘GHC.Float’ ...plus two others - ...plus 7 instances involving out-of-scope types + ...plus 8 instances involving out-of-scope types (use -fprint-potential-instances to see them all) diff --git a/testsuite/tests/polykinds/T13393.stderr b/testsuite/tests/polykinds/T13393.stderr index 1c4294e8a30e7a5a5ee8bf4f9161b8886047abd0..beea4732ebf0dc588b1c4cce85bacded3401a21f 100644 --- a/testsuite/tests/polykinds/T13393.stderr +++ b/testsuite/tests/polykinds/T13393.stderr @@ -8,7 +8,7 @@ T13393.hs:61:3: error: instance Traversable Identity -- Defined in ‘Data.Traversable’ instance Traversable Maybe -- Defined in ‘Data.Traversable’ ...plus two others - ...plus 27 instances involving out-of-scope types + ...plus 28 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In a stmt of a 'do' block: mapM putBackLeftOverInputAndReturnOutput undefined diff --git a/testsuite/tests/typecheck/should_compile/T14273.stderr b/testsuite/tests/typecheck/should_compile/T14273.stderr index ca739a3ac753fe84770ccbc03cf7be23c21a974c..cb4be120f7b7178987105a57df6041c465dbeb48 100644 --- a/testsuite/tests/typecheck/should_compile/T14273.stderr +++ b/testsuite/tests/typecheck/should_compile/T14273.stderr @@ -12,7 +12,7 @@ T14273.hs:7:27: warning: [-Wdeferred-type-errors (in -Wdefault)] instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others - ...plus 69 instances involving out-of-scope types + ...plus 70 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the first argument of ‘Just’, namely ‘(show _a)’ In the expression: Just (show _a) @@ -65,7 +65,7 @@ T14273.hs:13:10: warning: [-Wdeferred-type-errors (in -Wdefault)] instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others - ...plus 69 instances involving out-of-scope types + ...plus 70 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: show (_h ++ []) In an equation for ‘foo’: foo xs = show (_h ++ []) diff --git a/testsuite/tests/typecheck/should_compile/holes2.stderr b/testsuite/tests/typecheck/should_compile/holes2.stderr index 329e939c5d567d2b8679aeecb2dae37ef996524f..4ed5dfc552b4dc4730e7e397e7a8945376b07f9a 100644 --- a/testsuite/tests/typecheck/should_compile/holes2.stderr +++ b/testsuite/tests/typecheck/should_compile/holes2.stderr @@ -9,7 +9,7 @@ holes2.hs:3:5: warning: [-Wdeferred-type-errors (in -Wdefault)] instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others - ...plus 69 instances involving out-of-scope types + ...plus 70 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: show _ In an equation for ‘f’: f = show _ diff --git a/testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr b/testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr index 17c487ffee9b160adf387fff00df8705ee8d17e2..6dde6ea5cff1a92e295143c4efe34a367995b9f6 100644 --- a/testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr +++ b/testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr @@ -98,7 +98,7 @@ valid_hole_fits.hs:30:5: warning: [-Wdeferred-type-errors (in -Wdefault)] instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others - ...plus 69 instances involving out-of-scope types + ...plus 70 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: show _ In an equation for ‘f’: f = show _ @@ -148,7 +148,7 @@ valid_hole_fits.hs:34:5: warning: [-Wdeferred-type-errors (in -Wdefault)] instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others - ...plus 69 instances involving out-of-scope types + ...plus 70 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: show (_ (_ :: Bool)) In an equation for ‘h’: h = show (_ (_ :: Bool)) diff --git a/testsuite/tests/typecheck/should_fail/T10971b.stderr b/testsuite/tests/typecheck/should_fail/T10971b.stderr index 42e8fab656879f42f098aae77462ae51f73d9d5f..3ac8c4400b2df8000d88afd1c1a7b9104b3ec317 100644 --- a/testsuite/tests/typecheck/should_fail/T10971b.stderr +++ b/testsuite/tests/typecheck/should_fail/T10971b.stderr @@ -11,7 +11,7 @@ T10971b.hs:4:11: error: instance Foldable Maybe -- Defined in ‘Data.Foldable’ instance Foldable ((,) a) -- Defined in ‘Data.Foldable’ ...plus one other - ...plus 28 instances involving out-of-scope types + ...plus 29 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: length x In the expression: \ x -> length x @@ -29,7 +29,7 @@ T10971b.hs:5:13: error: instance Traversable Maybe -- Defined in ‘Data.Traversable’ instance Traversable ((,) a) -- Defined in ‘Data.Traversable’ ...plus one other - ...plus 28 instances involving out-of-scope types + ...plus 29 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: fmapDefault f x In the expression: \ f x -> fmapDefault f x @@ -47,7 +47,7 @@ T10971b.hs:6:14: error: instance Traversable Maybe -- Defined in ‘Data.Traversable’ instance Traversable ((,) a) -- Defined in ‘Data.Traversable’ ...plus one other - ...plus 28 instances involving out-of-scope types + ...plus 29 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: fmapDefault f x In the expression: (fmapDefault f x, length x) @@ -65,7 +65,7 @@ T10971b.hs:6:31: error: instance Foldable Maybe -- Defined in ‘Data.Foldable’ instance Foldable ((,) a) -- Defined in ‘Data.Foldable’ ...plus one other - ...plus 28 instances involving out-of-scope types + ...plus 29 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: length x In the expression: (fmapDefault f x, length x) diff --git a/testsuite/tests/typecheck/should_fail/T12921.stderr b/testsuite/tests/typecheck/should_fail/T12921.stderr index b6c14061cecb9a7ee9fd2c5f801fb908ed739f2f..d38ccf22b9e6a1984435ed42974252cfc9cfe5d6 100644 --- a/testsuite/tests/typecheck/should_fail/T12921.stderr +++ b/testsuite/tests/typecheck/should_fail/T12921.stderr @@ -10,7 +10,7 @@ T12921.hs:4:1: error: instance Data.Data.Data Ordering -- Defined in ‘Data.Data’ instance Data.Data.Data Integer -- Defined in ‘Data.Data’ ...plus 15 others - ...plus 46 instances involving out-of-scope types + ...plus 47 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the annotation: {-# ANN module "HLint: ignore Reduce duplication" #-} diff --git a/testsuite/tests/typecheck/should_fail/T14884.stderr b/testsuite/tests/typecheck/should_fail/T14884.stderr index 89ddef9947c5f1e2b5332d0bb5f9e1cf3d1fd903..cb85da14a5870aadeef39aa162a94c6c9697df1f 100644 --- a/testsuite/tests/typecheck/should_fail/T14884.stderr +++ b/testsuite/tests/typecheck/should_fail/T14884.stderr @@ -42,7 +42,7 @@ T14884.hs:4:7: error: instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others - ...plus 66 instances involving out-of-scope types + ...plus 67 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the first argument of ‘_’, namely ‘print’ In the expression: _ print "abc"