{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Ord (
Ord(..),
Ordering(..),
Down(..),
comparing,
) where
import Data.Bits (Bits, FiniteBits)
import Foreign.Storable (Storable)
import GHC.Ix (Ix)
import GHC.Base
import GHC.Enum (Bounded, Enum)
import GHC.Float (Floating, RealFloat)
import GHC.Num
import GHC.Read
import GHC.Real (Fractional, Integral, Real, RealFrac)
import GHC.Show
comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering
comparing :: (b -> a) -> b -> b -> Ordering
comparing b -> a
p b
x b
y = a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord a
compare (b -> a
p b
x) (b -> a
p b
y)
newtype Down a = Down
{ Down a -> a
getDown :: a
}
deriving
( Eq
, Num
, Semigroup
, Monoid
, Bits
, Bounded
, Enum
, FiniteBits
, Floating
, Fractional
, Integral
, Ix
, Real
, RealFrac
, RealFloat
, Storable
)
instance (Read a) => Read (Down a) where
readsPrec :: Int -> ReadS (Down a)
readsPrec Int
d = Bool -> ReadS (Down a) -> ReadS (Down a)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10) (ReadS (Down a) -> ReadS (Down a))
-> ReadS (Down a) -> ReadS (Down a)
forall a b. (a -> b) -> a -> b
$ \ String
r ->
[(a -> Down a
forall a. a -> Down a
Down a
x,String
t) | (String
"Down",String
s) <- ReadS String
lex String
r, (a
x,String
t) <- Int -> ReadS a
forall a. Read a => Int -> ReadS a
Evidence bound by a type signature of the constraint type Read a
readsPrec Int
11 String
s]
instance (Show a) => Show (Down a) where
showsPrec :: Int -> Down a -> ShowS
showsPrec Int
d (Down a
x) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"Down " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
Evidence bound by a type signature of the constraint type Show a
showsPrec Int
11 a
x
instance Ord a => Ord (Down a) where
compare :: Down a -> Down a -> Ordering
compare (Down a
x) (Down a
y) = a
y a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord a
`compare` a
x
instance Functor Down where
fmap :: (a -> b) -> Down a -> Down b
fmap = (a -> b) -> Down a -> Down b
coerce
instance Applicative Down where
pure :: a -> Down a
pure = a -> Down a
forall a. a -> Down a
Down
<*> :: Down (a -> b) -> Down a -> Down b
(<*>) = Down (a -> b) -> Down a -> Down b
coerce
instance Monad Down where
Down a
a >>= :: Down a -> (a -> Down b) -> Down b
>>= a -> Down b
k = a -> Down b
k a
a