{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
module Data.Prd (
module Data.Prd
, Down(..)
) where
import Control.Applicative
import Control.Monad
import Data.Data (Data, Typeable)
import Data.Function
import Data.Int as Int (Int, Int8, Int16, Int32, Int64)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe
import Data.Monoid hiding (First, Last)
import Data.Ord (Down(..))
import Data.Ratio
import Data.Word (Word, Word8, Word16, Word32, Word64)
import GHC.Generics (Generic, Generic1)
import GHC.Real
import Numeric.Natural
import qualified Data.Semigroup as S
import qualified Data.Set as Set
import qualified Data.Map as Map
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.Sequence as Seq
infix 4 <~, >~, /~, ~~, =~, ?~, `pgt`, `pge`, `peq`, `pne`, `ple`, `plt`
infix 4 `lt`, `gt`, `le`, `ge`, `eq`, `ne`, `pmax`, `pmin`
class Prd a where
{-# MINIMAL (<~) | (>~) #-}
(<~) :: a -> a -> Bool
(<~) = flip (>~)
(>~) :: a -> a -> Bool
(>~) = flip (<~)
(=~) :: Prd a => a -> a -> Bool
x =~ y = x <~ y && x >~ y
(?~) :: Prd a => a -> a -> Bool
x ?~ y = x <~ y || x >~ y
pcompare :: Eq a => a -> a -> Maybe Ordering
pcompare x y
| x `lt` y = Just LT
| x == y = Just EQ
| x `gt` y = Just GT
| otherwise = Nothing
(~~) :: Eq a => Prd a => a -> a -> Bool
x ~~ y = not (x `lt` y) && not (x `gt` y)
(/~) :: Eq a => Prd a => a -> a -> Bool
x /~ y = not $ x ~~ y
pcomparePrd :: Prd a => a -> a -> Maybe Ordering
pcomparePrd x y
| x <~ y = Just $ if y <~ x then EQ else LT
| y <~ x = Just GT
| otherwise = Nothing
pcompareOrd :: Ord a => a -> a -> Maybe Ordering
pcompareOrd x y = Just $ x `compare` y
eq :: Prd a => a -> a -> Bool
x `eq` y = x <~ y && x >~ y
ne :: Prd a => a -> a -> Bool
x `ne` y = not $ x `eq` y
le :: Prd a => a -> a -> Bool
x `le` y = x <~ y
ge :: Prd a => a -> a -> Bool
x `ge` y = x >~ y
lt :: Eq a => Prd a => a -> a -> Bool
x `lt` y | x /= x || y /= y = False
| otherwise = x <~ y && x /= y
gt :: Eq a => Prd a => a -> a -> Bool
x `gt` y | x /= x || y /= y = False
| otherwise = x >~ y && x /= y
peq :: Eq a => Prd a => a -> a -> Maybe Bool
peq x y = case x `pcompare` y of
Just EQ -> Just True
Just _ -> Just False
Nothing -> Nothing
pne :: Eq a => Prd a => a -> a -> Maybe Bool
pne x y = case x `pcompare` y of
Just EQ -> Just False
Just _ -> Just True
Nothing -> Nothing
ple :: Eq a => Prd a => a -> a -> Maybe Bool
ple x y = case x `pcompare` y of
Just GT -> Just False
Just _ -> Just True
Nothing -> Nothing
pge :: Eq a => Prd a => a -> a -> Maybe Bool
pge x y = case x `pcompare` y of
Just LT -> Just False
Just _ -> Just True
Nothing -> Nothing
plt :: Eq a => Prd a => a -> a -> Maybe Bool
plt x y = case x `pcompare` y of
Just LT -> Just True
Just _ -> Just False
Nothing -> Nothing
pgt :: Eq a => Prd a => a -> a -> Maybe Bool
pgt x y = case x `pcompare` y of
Just GT -> Just True
Just _ -> Just False
Nothing -> Nothing
pmax :: Eq a => Prd a => a -> a -> Maybe a
pmax x y = do
o <- pcompare x y
case o of
GT -> Just x
EQ -> Just y
LT -> Just y
pjoin :: Eq a => Minimal a => Foldable f => f a -> Maybe a
pjoin = foldM pmax minimal
pmin :: Eq a => Prd a => a -> a -> Maybe a
pmin x y = do
o <- pcompare x y
case o of
GT -> Just y
EQ -> Just x
LT -> Just x
pmeet :: Eq a => Maximal a => Foldable f => f a -> Maybe a
pmeet = foldM pmin maximal
sign :: Eq a => Num a => Prd a => a -> Maybe Ordering
sign x = pcompare x 0
zero :: Eq a => Num a => Prd a => a -> Bool
zero x = sign x == Just EQ
positive :: Eq a => Num a => Prd a => a -> Bool
positive x = sign x == Just GT
negative :: Eq a => Num a => Prd a => a -> Bool
negative x = sign x == Just LT
indeterminate :: Eq a => Num a => Prd a => a -> Bool
indeterminate x = sign x == Nothing
instance Prd Bool where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Char where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Integer where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Int where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Int8 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Int16 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Int32 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Int64 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Natural where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Word where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Word8 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Word16 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Word32 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Word64 where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd Ordering where
(<~) = (<=)
pcompare = pcompareOrd
instance Prd a => Prd [a] where
{-# SPECIALISE instance Prd [Char] #-}
[] <~ _ = True
(_:_) <~ [] = False
(x:xs) <~ (y:ys) = x <~ y && xs <~ ys
instance Prd a => Prd (NonEmpty a) where
(x :| xs) <~ (y :| ys) = x <~ y && xs <~ ys
instance Prd a => Prd (Down a) where
x <~ y = y <~ x
instance Prd a => Prd (Dual a) where
x <~ y = y <~ x
instance Prd Any where
Any x <~ Any y = x <~ y
instance Prd All where
All x <~ All y = y <~ x
instance Prd Float where
x <~ y | x /= x && y /= y = True
| x /= x || y /= y = False
| otherwise = x <= y
instance Prd Double where
x <~ y | x /= x && y /= y = True
| x /= x || y /= y = False
| otherwise = x <= y
instance (Prd a, Integral a) => Prd (Ratio a) where
{-# SPECIALIZE instance Prd Rational #-}
(x:%y) <~ (x':%y') | (x `eq` 0 && y `eq` 0) || (x' `eq` 0 && y' `eq` 0) = False
| otherwise = x * y' <~ x' * y
instance Prd a => Prd (Maybe a) where
Just a <~ Just b = a <~ b
x@Just{} <~ Nothing = False
Nothing <~ _ = True
instance (Prd a, Prd b) => Prd (Either a b) where
Right a <~ Right b = a <~ b
Right _ <~ _ = False
Left e <~ Left f = e <~ f
Left _ <~ _ = True
instance Prd () where
pcompare _ _ = Just EQ
_ <~ _ = True
instance (Prd a, Prd b) => Prd (a, b) where
(a,b) <~ (i,j) = a <~ i && b <~ j
instance (Prd a, Prd b, Prd c) => Prd (a, b, c) where
(a,b,c) <~ (i,j,k) = a <~ i && b <~ j && c <~ k
instance (Prd a, Prd b, Prd c, Prd d) => Prd (a, b, c, d) where
(a,b,c,d) <~ (i,j,k,l) = a <~ i && b <~ j && c <~ k && d <~ l
instance (Prd a, Prd b, Prd c, Prd d, Prd e) => Prd (a, b, c, d, e) where
(a,b,c,d,e) <~ (i,j,k,l,m) = a <~ i && b <~ j && c <~ k && d <~ l && e <~ m
instance Ord a => Prd (Set.Set a) where
(<~) = Set.isSubsetOf
instance (Ord k, Prd a) => Prd (Map.Map k a) where
(<~) = Map.isSubmapOfBy (<~)
instance Prd a => Prd (IntMap.IntMap a) where
(<~) = IntMap.isSubmapOfBy (<~)
instance Prd IntSet.IntSet where
(<~) = IntSet.isSubsetOf
newtype Ordered a = Ordered { getOrdered :: a }
deriving ( Eq, Ord, Show, Data, Typeable, Generic, Generic1, Functor, Foldable, Traversable)
instance Ord a => Prd (Ordered a) where
(<~) = (<=)
type Bound a = (Minimal a, Maximal a)
class Prd a => Minimal a where
minimal :: a
instance Minimal () where minimal = ()
instance Minimal Natural where minimal = 0
instance Minimal Bool where minimal = minBound
instance Minimal Ordering where minimal = minBound
instance Minimal Int where minimal = minBound
instance Minimal Int8 where minimal = minBound
instance Minimal Int16 where minimal = minBound
instance Minimal Int32 where minimal = minBound
instance Minimal Int64 where minimal = minBound
instance Minimal Word where minimal = minBound
instance Minimal Word8 where minimal = minBound
instance Minimal Word16 where minimal = minBound
instance Minimal Word32 where minimal = minBound
instance Minimal Word64 where minimal = minBound
instance Prd a => Minimal (IntMap.IntMap a) where
minimal = IntMap.empty
instance Ord a => Minimal (Set.Set a) where
minimal = Set.empty
instance (Ord k, Prd a) => Minimal (Map.Map k a) where
minimal = Map.empty
instance (Minimal a, Minimal b) => Minimal (a, b) where
minimal = (minimal, minimal)
instance (Minimal a, Prd b) => Minimal (Either a b) where
minimal = Left minimal
instance Prd a => Minimal (Maybe a) where
minimal = Nothing
instance Maximal a => Minimal (Down a) where
minimal = Down maximal
class Prd a => Maximal a where
maximal :: a
instance Maximal () where maximal = ()
instance Maximal Bool where maximal = maxBound
instance Maximal Ordering where maximal = maxBound
instance Maximal Int where maximal = maxBound
instance Maximal Int8 where maximal = maxBound
instance Maximal Int16 where maximal = maxBound
instance Maximal Int32 where maximal = maxBound
instance Maximal Int64 where maximal = maxBound
instance Maximal Word where maximal = maxBound
instance Maximal Word8 where maximal = maxBound
instance Maximal Word16 where maximal = maxBound
instance Maximal Word32 where maximal = maxBound
instance Maximal Word64 where maximal = maxBound
instance (Maximal a, Maximal b) => Maximal (a, b) where
maximal = (maximal, maximal)
instance (Prd a, Maximal b) => Maximal (Either a b) where
maximal = Right maximal
instance Maximal a => Maximal (Maybe a) where
maximal = Just maximal
instance Minimal a => Maximal (Down a) where
maximal = Down minimal
{-# INLINE until #-}
until :: (a -> Bool) -> (a -> a -> Bool) -> (a -> a) -> a -> a
until pred rel f seed = go seed
where go x | x' `rel` x = x
| pred x = x
| otherwise = go x'
where x' = f x
{-# INLINE while #-}
while :: (a -> Bool) -> (a -> a -> Bool) -> (a -> a) -> a -> a
while pred rel f seed = go seed
where go x | x' `rel` x = x
| not (pred x') = x
| otherwise = go x'
where x' = f x
{-# INLINE fixed #-}
fixed :: (a -> a -> Bool) -> (a -> a) -> a -> a
fixed = while (\_ -> True)