Skip to content
Snippets Groups Projects
Commit 9ff54ea8 authored by Vaibhav Sagar's avatar Vaibhav Sagar Committed by Marge Bot
Browse files

Data.Functor.Classes: fix Ord1 instance for Down

parent c43ee6b8
No related branches found
No related tags found
No related merge requests found
......@@ -834,7 +834,10 @@ instance Eq1 Down where
-- | @since 4.12.0.0
instance Ord1 Down where
liftCompare comp (Down x) (Down y) = comp x y
liftCompare comp (Down x) (Down y) = case comp x y of
LT -> GT
EQ -> EQ
GT -> LT
-- | @since 4.12.0.0
instance Read1 Down where
......
......@@ -33,6 +33,8 @@
have an HasCallStack constraint. Hopefully providing better error messages in case
they are used in unexpected ways.
* Fix the `Ord1` instance for `Data.Ord.Down` to reverse sort order.
## 4.16.0.0 *Nov 2021*
* The unary tuple type, `Solo`, is now exported by `Data.Tuple`.
......
module Main where
import Data.Ord
import Data.Functor.Classes
-- Should print GT
main :: IO ()
main = print $ compare1 (Down 1) (Down 2)
GT
......@@ -5,3 +5,4 @@ test('T16916', when(opsys('mingw32'), skip), compile_and_run, ['-O2 -threaded -w
test('T17310', normal, compile, [''])
test('T19691', normal, compile, [''])
test('executablePath', extra_run_opts(config.os), compile_and_run, [''])
test('T17472', normal, compile_and_run, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment