{-# LANGUAGE Safe #-}
module Algebra.PartialOrd (
PartialOrd(..),
partialOrdEq,
lfpFrom, unsafeLfpFrom,
gfpFrom, unsafeGfpFrom
) where
import Data.Foldable (Foldable (..))
import Data.Hashable (Hashable (..))
import qualified Data.HashMap.Lazy as HM
import qualified Data.HashSet as HS
import qualified Data.IntMap as IM
import qualified Data.IntSet as IS
import qualified Data.List.Compat as L
import qualified Data.Map as Map
import Data.Monoid (All (..), Any (..))
import qualified Data.Set as Set
import Data.Void (Void)
class Eq a => PartialOrd a where
leq :: a -> a -> Bool
comparable :: a -> a -> Bool
comparable a
x a
y = forall a. PartialOrd a => a -> a -> Bool
leq a
x a
y Bool -> Bool -> Bool
|| forall a. PartialOrd a => a -> a -> Bool
leq a
y a
x
partialOrdEq :: PartialOrd a => a -> a -> Bool
partialOrdEq :: forall a. PartialOrd a => a -> a -> Bool
partialOrdEq a
x a
y = forall a. PartialOrd a => a -> a -> Bool
leq a
x a
y Bool -> Bool -> Bool
&& forall a. PartialOrd a => a -> a -> Bool
leq a
y a
x
instance PartialOrd () where
leq :: () -> () -> Bool
leq ()
_ ()
_ = Bool
True
instance PartialOrd Bool where
leq :: Bool -> Bool -> Bool
leq = forall a. Ord a => a -> a -> Bool
(<=)
instance PartialOrd Any where
leq :: Any -> Any -> Bool
leq = forall a. Ord a => a -> a -> Bool
(<=)
instance PartialOrd All where
leq :: All -> All -> Bool
leq = forall a. Ord a => a -> a -> Bool
(<=)
instance PartialOrd Void where
leq :: Void -> Void -> Bool
leq Void
_ Void
_ = Bool
True
instance Eq a => PartialOrd [a] where
leq :: [a] -> [a] -> Bool
leq = forall a. Eq a => [a] -> [a] -> Bool
L.isSubsequenceOf
instance Ord a => PartialOrd (Set.Set a) where
leq :: Set a -> Set a -> Bool
leq = forall a. Ord a => Set a -> Set a -> Bool
Set.isSubsetOf
instance PartialOrd IS.IntSet where
leq :: IntSet -> IntSet -> Bool
leq = IntSet -> IntSet -> Bool
IS.isSubsetOf
instance (Eq k, Hashable k) => PartialOrd (HS.HashSet k) where
leq :: HashSet k -> HashSet k -> Bool
leq HashSet k
a HashSet k
b = forall a. HashSet a -> Bool
HS.null (forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
HS.difference HashSet k
a HashSet k
b)
instance (Ord k, PartialOrd v) => PartialOrd (Map.Map k v) where
leq :: Map k v -> Map k v -> Bool
leq = forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Map.isSubmapOfBy forall a. PartialOrd a => a -> a -> Bool
leq
instance PartialOrd v => PartialOrd (IM.IntMap v) where
leq :: IntMap v -> IntMap v -> Bool
leq = forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
IM.isSubmapOfBy forall a. PartialOrd a => a -> a -> Bool
leq
instance (Eq k, Hashable k, PartialOrd v) => PartialOrd (HM.HashMap k v) where
HashMap k v
x leq :: HashMap k v -> HashMap k v -> Bool
`leq` HashMap k v
y =
forall k v. HashMap k v -> Bool
HM.null (forall k v w.
(Eq k, Hashable k) =>
HashMap k v -> HashMap k w -> HashMap k v
HM.difference HashMap k v
x HashMap k v
y) Bool -> Bool -> Bool
&& All -> Bool
getAll (forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold forall a b. (a -> b) -> a -> b
$ forall k v1 v2 v3.
(Eq k, Hashable k) =>
(v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
HM.intersectionWith (\v
vx v
vy -> Bool -> All
All (v
vx forall a. PartialOrd a => a -> a -> Bool
`leq` v
vy)) HashMap k v
x HashMap k v
y)
instance (PartialOrd a, PartialOrd b) => PartialOrd (a, b) where
(a
x1, b
y1) leq :: (a, b) -> (a, b) -> Bool
`leq` (a
x2, b
y2) = a
x1 forall a. PartialOrd a => a -> a -> Bool
`leq` a
x2 Bool -> Bool -> Bool
&& b
y1 forall a. PartialOrd a => a -> a -> Bool
`leq` b
y2
instance (PartialOrd a, PartialOrd b) => PartialOrd (Either a b) where
leq :: Either a b -> Either a b -> Bool
leq (Right b
x) (Right b
y) = forall a. PartialOrd a => a -> a -> Bool
leq b
x b
y
leq (Right b
_) Either a b
_ = Bool
False
leq Either a b
_ (Right b
_) = Bool
True
leq (Left a
x) (Left a
y) = forall a. PartialOrd a => a -> a -> Bool
leq a
x a
y
comparable :: Either a b -> Either a b -> Bool
comparable (Right b
x) (Right b
y) = forall a. PartialOrd a => a -> a -> Bool
comparable b
x b
y
comparable (Right b
_) Either a b
_ = Bool
True
comparable Either a b
_ (Right b
_) = Bool
True
comparable (Left a
x) (Left a
y) = forall a. PartialOrd a => a -> a -> Bool
comparable a
x a
y
lfpFrom :: PartialOrd a => a -> (a -> a) -> a
lfpFrom :: forall a. PartialOrd a => a -> (a -> a) -> a
lfpFrom = forall a. Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
lfpFrom' forall a. PartialOrd a => a -> a -> Bool
leq
unsafeLfpFrom :: Eq a => a -> (a -> a) -> a
unsafeLfpFrom :: forall a. Eq a => a -> (a -> a) -> a
unsafeLfpFrom = forall a. Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
lfpFrom' (\a
_ a
_ -> Bool
True)
{-# INLINE lfpFrom' #-}
lfpFrom' :: Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
lfpFrom' :: forall a. Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
lfpFrom' a -> a -> Bool
check a
init_x a -> a
f = a -> a
go a
init_x
where go :: a -> a
go a
x | a
x' forall a. Eq a => a -> a -> Bool
== a
x = a
x
| a
x a -> a -> Bool
`check` a
x' = a -> a
go a
x'
| Bool
otherwise = forall a. HasCallStack => [Char] -> a
error [Char]
"lfpFrom: non-monotone function"
where x' :: a
x' = a -> a
f a
x
{-# INLINE gfpFrom #-}
gfpFrom :: PartialOrd a => a -> (a -> a) -> a
gfpFrom :: forall a. PartialOrd a => a -> (a -> a) -> a
gfpFrom = forall a. Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
gfpFrom' forall a. PartialOrd a => a -> a -> Bool
leq
{-# INLINE unsafeGfpFrom #-}
unsafeGfpFrom :: Eq a => a -> (a -> a) -> a
unsafeGfpFrom :: forall a. Eq a => a -> (a -> a) -> a
unsafeGfpFrom = forall a. Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
gfpFrom' (\a
_ a
_ -> Bool
True)
{-# INLINE gfpFrom' #-}
gfpFrom' :: Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
gfpFrom' :: forall a. Eq a => (a -> a -> Bool) -> a -> (a -> a) -> a
gfpFrom' a -> a -> Bool
check a
init_x a -> a
f = a -> a
go a
init_x
where go :: a -> a
go a
x | a
x' forall a. Eq a => a -> a -> Bool
== a
x = a
x
| a
x' a -> a -> Bool
`check` a
x = a -> a
go a
x'
| Bool
otherwise = forall a. HasCallStack => [Char] -> a
error [Char]
"gfpFrom: non-antinone function"
where x' :: a
x' = a -> a
f a
x