summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Ord.hs
blob: b21acb8e33e5ac0a40819385e149d2bc398bb373 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Ord
-- Copyright   :  (c) The University of Glasgow 2005
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  stable
-- Portability :  portable
--
-- Orderings
--
-----------------------------------------------------------------------------

module Data.Ord (
   Ord(..),
   Ordering(..),
   Down(..),
   comparing,
   clamp,
 ) where

import Data.Bits (Bits, FiniteBits)
import Foreign.Storable (Storable)
import GHC.Ix (Ix)
import GHC.Base
import GHC.Enum (Bounded(..))
import GHC.Float (Floating, RealFloat)
import GHC.Num
import GHC.Read
import GHC.Real (Fractional, Real, RealFrac)
import GHC.Show

-- $setup
-- >>> import Prelude

-- |
-- > comparing p x y = compare (p x) (p y)
--
-- Useful combinator for use in conjunction with the @xxxBy@ family
-- of functions from "Data.List", for example:
--
-- >   ... sortBy (comparing fst) ...
comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering
comparing p x y = compare (p x) (p y)

-- |
-- > clamp (low, high) a = min high (max a low)
--
-- Function for ensuring the value @a@ is within the inclusive bounds given by
-- @low@ and @high@. If it is, @a@ is returned unchanged. The result
-- is otherwise @low@ if @a <= low@, or @high@ if @high <= a@.
--
-- When clamp is used at Double and Float, it has NaN propagating semantics in
-- its second argument. That is, @clamp (l,h) NaN = NaN@, but @clamp (NaN, NaN)
-- x = x@.
--
-- >>> clamp (0, 10) 2
-- 2
--
-- >>> clamp ('a', 'm') 'x'
-- 'm'
clamp :: (Ord a) => (a, a) -> a -> a
clamp (low, high) a = min high (max a low)

-- | The 'Down' type allows you to reverse sort order conveniently.  A value of type
-- @'Down' a@ contains a value of type @a@ (represented as @'Down' a@).
--
-- If @a@ has an @'Ord'@ instance associated with it then comparing two
-- values thus wrapped will give you the opposite of their normal sort order.
-- This is particularly useful when sorting in generalised list comprehensions,
-- as in: @then sortWith by 'Down' x@.
--
-- >>> compare True False
-- GT
--
-- >>> compare (Down True) (Down False)
-- LT
--
-- If @a@ has a @'Bounded'@ instance then the wrapped instance also respects
-- the reversed ordering by exchanging the values of @'minBound'@ and
-- @'maxBound'@.
--
-- >>> minBound :: Int
-- -9223372036854775808
--
-- >>> minBound :: Down Int
-- Down 9223372036854775807
--
-- All other instances of @'Down' a@ behave as they do for @a@.
--
-- @since 4.6.0.0
newtype Down a = Down
    { getDown :: a -- ^ @since 4.14.0.0
    }
    deriving
      ( Eq        -- ^ @since 4.6.0.0
      , Num       -- ^ @since 4.11.0.0
      , Semigroup -- ^ @since 4.11.0.0
      , Monoid    -- ^ @since 4.11.0.0
      , Bits       -- ^ @since 4.14.0.0
      , FiniteBits -- ^ @since 4.14.0.0
      , Floating   -- ^ @since 4.14.0.0
      , Fractional -- ^ @since 4.14.0.0
      , Ix         -- ^ @since 4.14.0.0
      , Real       -- ^ @since 4.14.0.0
      , RealFrac   -- ^ @since 4.14.0.0
      , RealFloat  -- ^ @since 4.14.0.0
      , Storable   -- ^ @since 4.14.0.0
      )

-- | This instance would be equivalent to the derived instances of the
-- 'Down' newtype if the 'getDown' field were removed
--
-- @since 4.7.0.0
instance (Read a) => Read (Down a) where
    readsPrec d = readParen (d > 10) $ \ r ->
        [(Down x,t) | ("Down",s) <- lex r, (x,t) <- readsPrec 11 s]

-- | This instance would be equivalent to the derived instances of the
-- 'Down' newtype if the 'getDown' field were removed
--
-- @since 4.7.0.0
instance (Show a) => Show (Down a) where
    showsPrec d (Down x) = showParen (d > 10) $
        showString "Down " . showsPrec 11 x

-- | @since 4.6.0.0
instance Ord a => Ord (Down a) where
    compare (Down x) (Down y) = y `compare` x
    Down x < Down y = y < x
    Down x > Down y = y > x
    Down x <= Down y = y <= x
    Down x >= Down y = y >= x
    min (Down x) (Down y) = Down (max y x)
    max (Down x) (Down y) = Down (min y x)

-- | Swaps @'minBound'@ and @'maxBound'@ of the underlying type.
--
-- @since 4.14.0.0
instance Bounded a => Bounded (Down a) where
    minBound = Down maxBound
    maxBound = Down minBound

-- | @since 4.11.0.0
instance Functor Down where
    fmap = coerce

-- | @since 4.11.0.0
instance Applicative Down where
    pure = Down
    (<*>) = coerce

-- | @since 4.11.0.0
instance Monad Down where
    Down a >>= k = k a