{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Functor.Interval
( Interval(..)
, inf_
, sup_
, (...)
, point
, diameter
, midpoint
, uncurryI
, liftI
, enum
, liftEnum
, toUnit
, fromUnit
, transform
, lerp
, wrap
, foldMapInterval
, mapInterval
, traverseInterval
, member
, isValid
, isEmpty
, isPoint
, isSubintervalOf
, isSuperintervalOf
, isProperSubintervalOf
, isProperSuperintervalOf
, intersects
, Union(..)
, union
, Intersection(..)
, intersection
) where
import Control.Applicative (liftA2)
import Control.Monad.Trans.Class
import Data.Coerce (coerce)
import Data.Fixed (mod')
import Data.Function (on)
import Data.Semigroup
import GHC.Generics (Generic, Generic1)
data Interval f a = Interval
{ Interval f a -> f a
inf :: !(f a)
, Interval f a -> f a
sup :: !(f a)
}
deriving
( Interval f a -> Interval f a -> Bool
(Interval f a -> Interval f a -> Bool)
-> (Interval f a -> Interval f a -> Bool) -> Eq (Interval f a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (f :: * -> *) a.
Eq (f a) =>
Interval f a -> Interval f a -> Bool
/= :: Interval f a -> Interval f a -> Bool
$c/= :: forall (f :: * -> *) a.
Eq (f a) =>
Interval f a -> Interval f a -> Bool
== :: Interval f a -> Interval f a -> Bool
$c== :: forall (f :: * -> *) a.
Eq (f a) =>
Interval f a -> Interval f a -> Bool
Eq
, Foldable
, Functor
, (forall x. Interval f a -> Rep (Interval f a) x)
-> (forall x. Rep (Interval f a) x -> Interval f a)
-> Generic (Interval f a)
forall x. Rep (Interval f a) x -> Interval f a
forall x. Interval f a -> Rep (Interval f a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) a x. Rep (Interval f a) x -> Interval f a
forall (f :: * -> *) a x. Interval f a -> Rep (Interval f a) x
$cto :: forall (f :: * -> *) a x. Rep (Interval f a) x -> Interval f a
$cfrom :: forall (f :: * -> *) a x. Interval f a -> Rep (Interval f a) x
Generic
, (forall a. Interval f a -> Rep1 (Interval f) a)
-> (forall a. Rep1 (Interval f) a -> Interval f a)
-> Generic1 (Interval f)
forall a. Rep1 (Interval f) a -> Interval f a
forall a. Interval f a -> Rep1 (Interval f) a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall (f :: * -> *) a. Rep1 (Interval f) a -> Interval f a
forall (f :: * -> *) a. Interval f a -> Rep1 (Interval f) a
$cto1 :: forall (f :: * -> *) a. Rep1 (Interval f) a -> Interval f a
$cfrom1 :: forall (f :: * -> *) a. Interval f a -> Rep1 (Interval f) a
Generic1
, Ord
, Traversable
)
instance Show (f a) => Show (Interval f a) where
showsPrec :: Int -> Interval f a -> ShowS
showsPrec Int
p Interval f a
i = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
3) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> f a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
4 (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
i) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"..." ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> f a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
4 (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
i)
{-# INLINE showsPrec #-}
instance Applicative f => Applicative (Interval f) where
pure :: a -> Interval f a
pure = f a -> Interval f a
forall (f :: * -> *) a. f a -> Interval f a
point (f a -> Interval f a) -> (a -> f a) -> a -> Interval f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE pure #-}
Interval f (a -> b)
f <*> :: Interval f (a -> b) -> Interval f a -> Interval f b
<*> Interval f a
a = f b -> f b -> Interval f b
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (Interval f (a -> b) -> f (a -> b)
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f (a -> b)
f f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
a) (Interval f (a -> b) -> f (a -> b)
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f (a -> b)
f f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
a)
{-# INLINE (<*>) #-}
Interval f a
a *> :: Interval f a -> Interval f b -> Interval f b
*> Interval f b
b = f b -> f b -> Interval f b
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
a f a -> f b -> f b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f b
b) (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
a f a -> f b -> f b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f b
b)
{-# INLINE (*>) #-}
Interval f a
a <* :: Interval f a -> Interval f b -> Interval f a
<* Interval f b
b = f a -> f a -> Interval f a
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
a f a -> f b -> f a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f b
b) (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
a f a -> f b -> f a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f b
b)
{-# INLINE (<*) #-}
liftA2 :: (a -> b -> c) -> Interval f a -> Interval f b -> Interval f c
liftA2 a -> b -> c
f Interval f a
a Interval f b
b = f c -> f c -> Interval f c
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval ((a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
a) (Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f b
b)) ((a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
a) (Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f b
b))
{-# INLINE liftA2 #-}
instance Monad f => Monad (Interval f) where
Interval f a
m >>= :: Interval f a -> (a -> Interval f b) -> Interval f b
>>= a -> Interval f b
f = f b -> f b -> Interval f b
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
m f a -> (a -> f b) -> f b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
inf (Interval f b -> f b) -> (a -> Interval f b) -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Interval f b
f) (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
m f a -> (a -> f b) -> f b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Interval f b -> f b
forall (f :: * -> *) a. Interval f a -> f a
sup (Interval f b -> f b) -> (a -> Interval f b) -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Interval f b
f)
{-# INLINE (>>=) #-}
instance MonadTrans Interval where
lift :: m a -> Interval m a
lift = m a -> Interval m a
forall (f :: * -> *) a. f a -> Interval f a
point
{-# INLINE lift #-}
instance (Applicative f, Num a) => Num (Interval f a) where
+ :: Interval f a -> Interval f a -> Interval f a
(+) = (a -> a -> a) -> Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(+)
{-# INLINE (+) #-}
* :: Interval f a -> Interval f a -> Interval f a
(*) = (a -> a -> a) -> Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(*)
{-# INLINE (*) #-}
(-) = (a -> a -> a) -> Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
{-# INLINE (-) #-}
abs :: Interval f a -> Interval f a
abs = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs
{-# INLINE abs #-}
signum :: Interval f a -> Interval f a
signum = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
signum
{-# INLINE signum #-}
negate :: Interval f a -> Interval f a
negate = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
negate
{-# INLINE negate #-}
fromInteger :: Integer -> Interval f a
fromInteger = a -> Interval f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Interval f a) -> (Integer -> a) -> Integer -> Interval f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
{-# INLINE fromInteger #-}
instance (Applicative f, Fractional a) => Fractional (Interval f a) where
recip :: Interval f a -> Interval f a
recip = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Fractional a => a -> a
recip
{-# INLINE recip #-}
/ :: Interval f a -> Interval f a -> Interval f a
(/) = (a -> a -> a) -> Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Fractional a => a -> a -> a
(/)
{-# INLINE (/) #-}
fromRational :: Rational -> Interval f a
fromRational = a -> Interval f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Interval f a) -> (Rational -> a) -> Rational -> Interval f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> a
forall a. Fractional a => Rational -> a
fromRational
{-# INLINE fromRational #-}
instance (Applicative f, Floating a) => Floating (Interval f a) where
pi :: Interval f a
pi = a -> Interval f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Floating a => a
pi
{-# INLINE pi #-}
exp :: Interval f a -> Interval f a
exp = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
exp
{-# INLINE exp #-}
sqrt :: Interval f a -> Interval f a
sqrt = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sqrt
{-# INLINE sqrt #-}
log :: Interval f a -> Interval f a
log = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
log
{-# INLINE log #-}
** :: Interval f a -> Interval f a -> Interval f a
(**) = (a -> a -> a) -> Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Floating a => a -> a -> a
(**)
{-# INLINE (**) #-}
logBase :: Interval f a -> Interval f a -> Interval f a
logBase = (a -> a -> a) -> Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Floating a => a -> a -> a
logBase
{-# INLINE logBase #-}
sin :: Interval f a -> Interval f a
sin = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sin
{-# INLINE sin #-}
tan :: Interval f a -> Interval f a
tan = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tan
{-# INLINE tan #-}
cos :: Interval f a -> Interval f a
cos = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cos
{-# INLINE cos #-}
asin :: Interval f a -> Interval f a
asin = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asin
{-# INLINE asin #-}
atan :: Interval f a -> Interval f a
atan = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atan
{-# INLINE atan #-}
acos :: Interval f a -> Interval f a
acos = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acos
{-# INLINE acos #-}
sinh :: Interval f a -> Interval f a
sinh = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sinh
{-# INLINE sinh #-}
tanh :: Interval f a -> Interval f a
tanh = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tanh
{-# INLINE tanh #-}
cosh :: Interval f a -> Interval f a
cosh = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cosh
{-# INLINE cosh #-}
asinh :: Interval f a -> Interval f a
asinh = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asinh
{-# INLINE asinh #-}
atanh :: Interval f a -> Interval f a
atanh = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atanh
{-# INLINE atanh #-}
acosh :: Interval f a -> Interval f a
acosh = (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acosh
{-# INLINE acosh #-}
instance (Applicative f, Ord a) => Semigroup (Interval f a) where
<> :: Interval f a -> Interval f a -> Interval f a
(<>) = Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a.
(Applicative f, Ord a) =>
Interval f a -> Interval f a -> Interval f a
union
{-# INLINE (<>) #-}
stimes :: b -> Interval f a -> Interval f a
stimes = b -> Interval f a -> Interval f a
forall b a. Integral b => b -> a -> a
stimesIdempotent
{-# INLINE stimes #-}
inf_, sup_ :: Lens' (Interval f a) (f a)
inf_ :: (f a -> f (f a)) -> Interval f a -> f (Interval f a)
inf_ = (Interval f a -> f a)
-> (Interval f a -> f a -> Interval f a)
-> Lens' (Interval f a) (f a)
forall s a. (s -> a) -> (s -> a -> s) -> Lens' s a
lens Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf ((Interval f a -> f a -> Interval f a)
-> Lens' (Interval f a) (f a))
-> (Interval f a -> f a -> Interval f a)
-> Lens' (Interval f a) (f a)
forall a b. (a -> b) -> a -> b
$ \ Interval f a
i f a
inf -> Interval f a
i{ f a
inf :: f a
inf :: f a
inf }
{-# INLINE inf_ #-}
sup_ :: (f a -> f (f a)) -> Interval f a -> f (Interval f a)
sup_ = (Interval f a -> f a)
-> (Interval f a -> f a -> Interval f a)
-> Lens' (Interval f a) (f a)
forall s a. (s -> a) -> (s -> a -> s) -> Lens' s a
lens Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup ((Interval f a -> f a -> Interval f a)
-> Lens' (Interval f a) (f a))
-> (Interval f a -> f a -> Interval f a)
-> Lens' (Interval f a) (f a)
forall a b. (a -> b) -> a -> b
$ \ Interval f a
i f a
sup -> Interval f a
i{ f a
sup :: f a
sup :: f a
sup }
{-# INLINE sup_ #-}
(...) :: Applicative f => a -> a -> Interval f a
a
inf... :: a -> a -> Interval f a
...a
sup = f a -> f a -> Interval f a
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
inf) (a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
sup)
{-# INLINE (...) #-}
infix 3 ...
point :: f a -> Interval f a
point :: f a -> Interval f a
point f a
p = f a -> f a -> Interval f a
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval f a
p f a
p
{-# INLINE point #-}
diameter :: (Applicative f, Num a) => Interval f a -> f a
diameter :: Interval f a -> f a
diameter = (a -> a -> a) -> Interval f a -> f a
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI ((a -> a) -> (a -> a) -> a -> a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs ((a -> a) -> a -> a) -> (a -> a -> a) -> a -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> a) -> a -> a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (-))
{-# INLINE diameter #-}
midpoint :: (Applicative f, Fractional a) => Interval f a -> f a
midpoint :: Interval f a -> f a
midpoint = a -> Interval f a -> f a
forall (f :: * -> *) a.
(Applicative f, Num a) =>
a -> Interval f a -> f a
lerp a
0.5
{-# INLINE midpoint #-}
uncurryI :: (f a -> f a -> b) -> Interval f a -> b
uncurryI :: (f a -> f a -> b) -> Interval f a -> b
uncurryI f a -> f a -> b
f Interval f a
i = f a -> f a -> b
f (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
i) (Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
i)
{-# INLINE uncurryI #-}
liftI :: Applicative f => (a -> a -> b) -> Interval f a -> f b
liftI :: (a -> a -> b) -> Interval f a -> f b
liftI a -> a -> b
f = (f a -> f a -> f b) -> Interval f a -> f b
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI ((a -> a -> b) -> f a -> f a -> f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> b
f)
{-# INLINE liftI #-}
enum :: Enum (f a) => Interval f a -> [f a]
enum :: Interval f a -> [f a]
enum = (f a -> f a -> [f a]) -> Interval f a -> [f a]
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI f a -> f a -> [f a]
forall a. Enum a => a -> a -> [a]
enumFromTo
{-# INLINE enum #-}
liftEnum :: (Applicative f, Enum a) => Interval f a -> f [a]
liftEnum :: Interval f a -> f [a]
liftEnum = (a -> a -> [a]) -> Interval f a -> f [a]
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI a -> a -> [a]
forall a. Enum a => a -> a -> [a]
enumFromTo
{-# INLINE liftEnum #-}
toUnit, fromUnit :: (Applicative f, Fractional a) => Interval f a -> f a -> f a
toUnit :: Interval f a -> f a -> f a
toUnit Interval f a
i f a
x = (a -> a -> a -> a) -> Interval f a -> f (a -> a)
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI (\ a
inf a
sup a
t -> (a
t a -> a -> a
forall a. Num a => a -> a -> a
- a
inf) a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
sup a -> a -> a
forall a. Num a => a -> a -> a
- a
inf)) Interval f a
i f (a -> a) -> f a -> f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
x
{-# INLINE toUnit #-}
fromUnit :: Interval f a -> f a -> f a
fromUnit Interval f a
i f a
x = (a -> a -> a -> a) -> Interval f a -> f (a -> a)
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI (\ a
inf a
sup a
t -> (a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a
t) a -> a -> a
forall a. Num a => a -> a -> a
* a
inf a -> a -> a
forall a. Num a => a -> a -> a
+ a
t a -> a -> a
forall a. Num a => a -> a -> a
* a
sup) Interval f a
i f (a -> a) -> f a -> f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
x
{-# INLINE fromUnit #-}
transform :: (Applicative f, Fractional a) => Interval f a -> Interval f a -> f a -> f a
transform :: Interval f a -> Interval f a -> f a -> f a
transform Interval f a
i1 Interval f a
i2 f a
x = (f a -> f a -> f a) -> Interval f a -> f a
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI (\ f a
inf1 f a
sup1 -> (f a -> f a -> f a) -> Interval f a -> f a
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI (\ f a
inf2 f a
sup2 -> (a -> a -> a -> a -> a -> a) -> f a -> f a -> f (a -> a -> a -> a)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a -> a -> a -> a
forall a. Fractional a => a -> a -> a -> a -> a -> a
f f a
inf1 f a
sup1 f (a -> a -> a -> a) -> f a -> f (a -> a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
inf2 f (a -> a -> a) -> f a -> f (a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
sup2 f (a -> a) -> f a -> f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
x) Interval f a
i2) Interval f a
i1
where
f :: a -> a -> a -> a -> a -> a
f a
inf1 a
sup1 a
inf2 a
sup2 a
t = (-a
t a -> a -> a
forall a. Num a => a -> a -> a
* a
inf2 a -> a -> a
forall a. Num a => a -> a -> a
+ a
sup1 a -> a -> a
forall a. Num a => a -> a -> a
* a
inf2 a -> a -> a
forall a. Num a => a -> a -> a
+ a
t a -> a -> a
forall a. Num a => a -> a -> a
* a
sup2 a -> a -> a
forall a. Num a => a -> a -> a
- a
inf1 a -> a -> a
forall a. Num a => a -> a -> a
* a
sup2) a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
sup1 a -> a -> a
forall a. Num a => a -> a -> a
- a
inf1)
{-# INLINE transform #-}
lerp :: (Applicative f, Num a) => a -> Interval f a -> f a
lerp :: a -> Interval f a -> f a
lerp a
t = (a -> a -> a) -> Interval f a -> f a
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI (\ a
inf a
sup -> (a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a
t) a -> a -> a
forall a. Num a => a -> a -> a
* a
inf a -> a -> a
forall a. Num a => a -> a -> a
+ a
t a -> a -> a
forall a. Num a => a -> a -> a
* a
sup)
{-# INLINE lerp #-}
wrap :: (Applicative f, Real a) => Interval f a -> f a -> f a
wrap :: Interval f a -> f a -> f a
wrap Interval f a
i f a
x = (a -> a -> a -> a) -> Interval f a -> f (a -> a)
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI (\ a
inf a
sup a
x -> ((a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
sup) a -> a -> a
forall a. Real a => a -> a -> a
`mod'` (a
sup a -> a -> a
forall a. Num a => a -> a -> a
- a
inf)) a -> a -> a
forall a. Num a => a -> a -> a
+ a
inf) Interval f a
i f (a -> a) -> f a -> f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
x
{-# INLINE wrap #-}
foldMapInterval :: Semigroup s => (f a -> s) -> Interval f a -> s
foldMapInterval :: (f a -> s) -> Interval f a -> s
foldMapInterval f a -> s
f = (f a -> f a -> s) -> Interval f a -> s
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI (s -> s -> s
forall a. Semigroup a => a -> a -> a
(<>) (s -> s -> s) -> (f a -> s) -> f a -> f a -> s
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` f a -> s
f)
{-# INLINE foldMapInterval #-}
mapInterval :: (f a -> g b) -> Interval f a -> Interval g b
mapInterval :: (f a -> g b) -> Interval f a -> Interval g b
mapInterval f a -> g b
f = (f a -> f a -> Interval g b) -> Interval f a -> Interval g b
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI (g b -> g b -> Interval g b
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (g b -> g b -> Interval g b)
-> (f a -> g b) -> f a -> f a -> Interval g b
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` f a -> g b
f)
{-# INLINE mapInterval #-}
traverseInterval :: Applicative m => (f a -> m (g b)) -> Interval f a -> m (Interval g b)
traverseInterval :: (f a -> m (g b)) -> Interval f a -> m (Interval g b)
traverseInterval f a -> m (g b)
f = (f a -> f a -> m (Interval g b))
-> Interval f a -> m (Interval g b)
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI ((g b -> g b -> Interval g b)
-> m (g b) -> m (g b) -> m (Interval g b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 g b -> g b -> Interval g b
forall (f :: * -> *) a. f a -> f a -> Interval f a
Interval (m (g b) -> m (g b) -> m (Interval g b))
-> (f a -> m (g b)) -> f a -> f a -> m (Interval g b)
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` f a -> m (g b)
f)
{-# INLINE traverseInterval #-}
member :: (Applicative f, Foldable f, Ord a) => f a -> Interval f a -> Bool
member :: f a -> Interval f a -> Bool
member = Interval f a -> Interval f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
Interval f a -> Interval f a -> Bool
isSubintervalOf (Interval f a -> Interval f a -> Bool)
-> (f a -> Interval f a) -> f a -> Interval f a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> Interval f a
forall (f :: * -> *) a. f a -> Interval f a
point
{-# INLINE member #-}
isValid :: (Applicative f, Foldable f, Ord a) => Interval f a -> Bool
isValid :: Interval f a -> Bool
isValid = (f a -> f a -> Bool) -> Interval f a -> Bool
forall (f :: * -> *) a b. (f a -> f a -> b) -> Interval f a -> b
uncurryI f a -> f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
f a -> f a -> Bool
lte
{-# INLINE isValid #-}
isEmpty :: (Applicative f, Foldable f, Ord a) => Interval f a -> Bool
isEmpty :: Interval f a -> Bool
isEmpty = Bool -> Bool
not (Bool -> Bool) -> (Interval f a -> Bool) -> Interval f a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Interval f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
Interval f a -> Bool
isValid
{-# INLINE isEmpty #-}
isPoint :: (Applicative f, Foldable f, Eq a) => Interval f a -> Bool
isPoint :: Interval f a -> Bool
isPoint = f Bool -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and (f Bool -> Bool)
-> (Interval f a -> f Bool) -> Interval f a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> Bool) -> Interval f a -> f Bool
forall (f :: * -> *) a b.
Applicative f =>
(a -> a -> b) -> Interval f a -> f b
liftI a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE isPoint #-}
isSubintervalOf :: (Applicative f, Foldable f, Ord a) => Interval f a -> Interval f a -> Bool
isSubintervalOf :: Interval f a -> Interval f a -> Bool
isSubintervalOf Interval f a
a Interval f a
b = Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
a f a -> f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
f a -> f a -> Bool
`gte` Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
inf Interval f a
b Bool -> Bool -> Bool
&& Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
a f a -> f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
f a -> f a -> Bool
`lte` Interval f a -> f a
forall (f :: * -> *) a. Interval f a -> f a
sup Interval f a
b
{-# INLINE isSubintervalOf #-}
isSuperintervalOf :: (Applicative f, Foldable f, Ord a) => Interval f a -> Interval f a -> Bool
isSuperintervalOf :: Interval f a -> Interval f a -> Bool
isSuperintervalOf = (Interval f a -> Interval f a -> Bool)
-> Interval f a -> Interval f a -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Interval f a -> Interval f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
Interval f a -> Interval f a -> Bool
isSubintervalOf
{-# INLINE isSuperintervalOf #-}
isProperSubintervalOf :: (Applicative f, Foldable f, Ord a) => Interval f a -> Interval f a -> Bool
isProperSubintervalOf :: Interval f a -> Interval f a -> Bool
isProperSubintervalOf Interval f a
a Interval f a
b = Interval f a -> Interval f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
Interval f a -> Interval f a -> Bool
isSubintervalOf Interval f a
a Interval f a
b Bool -> Bool -> Bool
&& Interval f Bool -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ((a -> a -> Bool) -> Interval f a -> Interval f a -> Interval f Bool
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(/=) Interval f a
a Interval f a
b)
{-# INLINE isProperSubintervalOf #-}
isProperSuperintervalOf :: (Applicative f, Foldable f, Ord a) => Interval f a -> Interval f a -> Bool
isProperSuperintervalOf :: Interval f a -> Interval f a -> Bool
isProperSuperintervalOf = (Interval f a -> Interval f a -> Bool)
-> Interval f a -> Interval f a -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Interval f a -> Interval f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
Interval f a -> Interval f a -> Bool
isProperSubintervalOf
{-# INLINE isProperSuperintervalOf #-}
intersects :: (Applicative f, Foldable f, Ord a) => Interval f a -> Interval f a -> Bool
intersects :: Interval f a -> Interval f a -> Bool
intersects Interval f a
a Interval f a
b = Interval f a -> Bool
forall (f :: * -> *) a.
(Applicative f, Foldable f, Ord a) =>
Interval f a -> Bool
isValid (Interval f a -> Interval f a -> Interval f a
forall (f :: * -> *) a.
(Applicative f, Ord a) =>
Interval f a -> Interval f a -> Interval f a
intersection Interval f a
a Interval f a
b)
{-# INLINE intersects #-}
newtype Union f a = Union { Union f a -> Interval f a
getUnion :: Interval f a }
deriving (Functor (Union f)
a -> Union f a
Functor (Union f)
-> (forall a. a -> Union f a)
-> (forall a b. Union f (a -> b) -> Union f a -> Union f b)
-> (forall a b c.
(a -> b -> c) -> Union f a -> Union f b -> Union f c)
-> (forall a b. Union f a -> Union f b -> Union f b)
-> (forall a b. Union f a -> Union f b -> Union f a)
-> Applicative (Union f)
Union f a -> Union f b -> Union f b
Union f a -> Union f b -> Union f a
Union f (a -> b) -> Union f a -> Union f b
(a -> b -> c) -> Union f a -> Union f b -> Union f c
forall a. a -> Union f a
forall a b. Union f a -> Union f b -> Union f a
forall a b. Union f a -> Union f b -> Union f b
forall a b. Union f (a -> b) -> Union f a -> Union f b
forall a b c. (a -> b -> c) -> Union f a -> Union f b -> Union f c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (f :: * -> *). Applicative f => Functor (Union f)
forall (f :: * -> *) a. Applicative f => a -> Union f a
forall (f :: * -> *) a b.
Applicative f =>
Union f a -> Union f b -> Union f a
forall (f :: * -> *) a b.
Applicative f =>
Union f a -> Union f b -> Union f b
forall (f :: * -> *) a b.
Applicative f =>
Union f (a -> b) -> Union f a -> Union f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Union f a -> Union f b -> Union f c
<* :: Union f a -> Union f b -> Union f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
Union f a -> Union f b -> Union f a
*> :: Union f a -> Union f b -> Union f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Union f a -> Union f b -> Union f b
liftA2 :: (a -> b -> c) -> Union f a -> Union f b -> Union f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Union f a -> Union f b -> Union f c
<*> :: Union f (a -> b) -> Union f a -> Union f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Union f (a -> b) -> Union f a -> Union f b
pure :: a -> Union f a
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Union f a
$cp1Applicative :: forall (f :: * -> *). Applicative f => Functor (Union f)
Applicative, Union f a -> Union f a -> Bool
(Union f a -> Union f a -> Bool)
-> (Union f a -> Union f a -> Bool) -> Eq (Union f a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (f :: * -> *) a. Eq (f a) => Union f a -> Union f a -> Bool
/= :: Union f a -> Union f a -> Bool
$c/= :: forall (f :: * -> *) a. Eq (f a) => Union f a -> Union f a -> Bool
== :: Union f a -> Union f a -> Bool
$c== :: forall (f :: * -> *) a. Eq (f a) => Union f a -> Union f a -> Bool
Eq, a -> Union f a -> Bool
Union f m -> m
Union f a -> [a]
Union f a -> Bool
Union f a -> Int
Union f a -> a
Union f a -> a
Union f a -> a
Union f a -> a
(a -> m) -> Union f a -> m
(a -> m) -> Union f a -> m
(a -> b -> b) -> b -> Union f a -> b
(a -> b -> b) -> b -> Union f a -> b
(b -> a -> b) -> b -> Union f a -> b
(b -> a -> b) -> b -> Union f a -> b
(a -> a -> a) -> Union f a -> a
(a -> a -> a) -> Union f a -> a
(forall m. Monoid m => Union f m -> m)
-> (forall m a. Monoid m => (a -> m) -> Union f a -> m)
-> (forall m a. Monoid m => (a -> m) -> Union f a -> m)
-> (forall a b. (a -> b -> b) -> b -> Union f a -> b)
-> (forall a b. (a -> b -> b) -> b -> Union f a -> b)
-> (forall b a. (b -> a -> b) -> b -> Union f a -> b)
-> (forall b a. (b -> a -> b) -> b -> Union f a -> b)
-> (forall a. (a -> a -> a) -> Union f a -> a)
-> (forall a. (a -> a -> a) -> Union f a -> a)
-> (forall a. Union f a -> [a])
-> (forall a. Union f a -> Bool)
-> (forall a. Union f a -> Int)
-> (forall a. Eq a => a -> Union f a -> Bool)
-> (forall a. Ord a => Union f a -> a)
-> (forall a. Ord a => Union f a -> a)
-> (forall a. Num a => Union f a -> a)
-> (forall a. Num a => Union f a -> a)
-> Foldable (Union f)
forall a. Eq a => a -> Union f a -> Bool
forall a. Num a => Union f a -> a
forall a. Ord a => Union f a -> a
forall m. Monoid m => Union f m -> m
forall a. Union f a -> Bool
forall a. Union f a -> Int
forall a. Union f a -> [a]
forall a. (a -> a -> a) -> Union f a -> a
forall m a. Monoid m => (a -> m) -> Union f a -> m
forall b a. (b -> a -> b) -> b -> Union f a -> b
forall a b. (a -> b -> b) -> b -> Union f a -> b
forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> Union f a -> Bool
forall (f :: * -> *) a. (Foldable f, Num a) => Union f a -> a
forall (f :: * -> *) a. (Foldable f, Ord a) => Union f a -> a
forall (f :: * -> *) m. (Foldable f, Monoid m) => Union f m -> m
forall (f :: * -> *) a. Foldable f => Union f a -> Bool
forall (f :: * -> *) a. Foldable f => Union f a -> Int
forall (f :: * -> *) a. Foldable f => Union f a -> [a]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> Union f a -> a
forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Union f a -> m
forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> Union f a -> b
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> Union f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Union f a -> a
$cproduct :: forall (f :: * -> *) a. (Foldable f, Num a) => Union f a -> a
sum :: Union f a -> a
$csum :: forall (f :: * -> *) a. (Foldable f, Num a) => Union f a -> a
minimum :: Union f a -> a
$cminimum :: forall (f :: * -> *) a. (Foldable f, Ord a) => Union f a -> a
maximum :: Union f a -> a
$cmaximum :: forall (f :: * -> *) a. (Foldable f, Ord a) => Union f a -> a
elem :: a -> Union f a -> Bool
$celem :: forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> Union f a -> Bool
length :: Union f a -> Int
$clength :: forall (f :: * -> *) a. Foldable f => Union f a -> Int
null :: Union f a -> Bool
$cnull :: forall (f :: * -> *) a. Foldable f => Union f a -> Bool
toList :: Union f a -> [a]
$ctoList :: forall (f :: * -> *) a. Foldable f => Union f a -> [a]
foldl1 :: (a -> a -> a) -> Union f a -> a
$cfoldl1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> Union f a -> a
foldr1 :: (a -> a -> a) -> Union f a -> a
$cfoldr1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> Union f a -> a
foldl' :: (b -> a -> b) -> b -> Union f a -> b
$cfoldl' :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> Union f a -> b
foldl :: (b -> a -> b) -> b -> Union f a -> b
$cfoldl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> Union f a -> b
foldr' :: (a -> b -> b) -> b -> Union f a -> b
$cfoldr' :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> Union f a -> b
foldr :: (a -> b -> b) -> b -> Union f a -> b
$cfoldr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> Union f a -> b
foldMap' :: (a -> m) -> Union f a -> m
$cfoldMap' :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Union f a -> m
foldMap :: (a -> m) -> Union f a -> m
$cfoldMap :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Union f a -> m
fold :: Union f m -> m
$cfold :: forall (f :: * -> *) m. (Foldable f, Monoid m) => Union f m -> m
Foldable, a -> Union f b -> Union f a
(a -> b) -> Union f a -> Union f b
(forall a b. (a -> b) -> Union f a -> Union f b)
-> (forall a b. a -> Union f b -> Union f a) -> Functor (Union f)
forall a b. a -> Union f b -> Union f a
forall a b. (a -> b) -> Union f a -> Union f b
forall (f :: * -> *) a b. Functor f => a -> Union f b -> Union f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Union f a -> Union f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Union f b -> Union f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Union f b -> Union f a
fmap :: (a -> b) -> Union f a -> Union f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Union f a -> Union f b
Functor, Applicative (Union f)
a -> Union f a
Applicative (Union f)
-> (forall a b. Union f a -> (a -> Union f b) -> Union f b)
-> (forall a b. Union f a -> Union f b -> Union f b)
-> (forall a. a -> Union f a)
-> Monad (Union f)
Union f a -> (a -> Union f b) -> Union f b
Union f a -> Union f b -> Union f b
forall a. a -> Union f a
forall a b. Union f a -> Union f b -> Union f b
forall a b. Union f a -> (a -> Union f b) -> Union f b
forall (f :: * -> *). Monad f => Applicative (Union f)
forall (f :: * -> *) a. Monad f => a -> Union f a
forall (f :: * -> *) a b.
Monad f =>
Union f a -> Union f b -> Union f b
forall (f :: * -> *) a b.
Monad f =>
Union f a -> (a -> Union f b) -> Union f b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Union f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> Union f a
>> :: Union f a -> Union f b -> Union f b
$c>> :: forall (f :: * -> *) a b.
Monad f =>
Union f a -> Union f b -> Union f b
>>= :: Union f a -> (a -> Union f b) -> Union f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
Union f a -> (a -> Union f b) -> Union f b
$cp1Monad :: forall (f :: * -> *). Monad f => Applicative (Union f)
Monad, Eq (Union f a)
Eq (Union f a)
-> (Union f a -> Union f a -> Ordering)
-> (Union f a -> Union f a -> Bool)
-> (Union f a -> Union f a -> Bool)
-> (Union f a -> Union f a -> Bool)
-> (Union f a -> Union f a -> Bool)
-> (Union f a -> Union f a -> Union f a)
-> (Union f a -> Union f a -> Union f a)
-> Ord (Union f a)
Union f a -> Union f a -> Bool
Union f a -> Union f a -> Ordering
Union f a -> Union f a -> Union f a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (f :: * -> *) a. Ord (f a) => Eq (Union f a)
forall (f :: * -> *) a. Ord (f a) => Union f a -> Union f a -> Bool
forall (f :: * -> *) a.
Ord (f a) =>
Union f a -> Union f a -> Ordering
forall (f :: * -> *) a.
Ord (f a) =>
Union f a -> Union f a -> Union f a
min :: Union f a -> Union f a -> Union f a
$cmin :: forall (f :: * -> *) a.
Ord (f a) =>
Union f a -> Union f a -> Union f a
max :: Union f a -> Union f a -> Union f a
$cmax :: forall (f :: * -> *) a.
Ord (f a) =>
Union f a -> Union f a -> Union f a
>= :: Union f a -> Union f a -> Bool
$c>= :: forall (f :: * -> *) a. Ord (f a) => Union f a -> Union f a -> Bool
> :: Union f a -> Union f a -> Bool
$c> :: forall (f :: * -> *) a. Ord (f a) => Union f a -> Union f a -> Bool
<= :: Union f a -> Union f a -> Bool
$c<= :: forall (f :: * -> *) a. Ord (f a) => Union f a -> Union f a -> Bool
< :: Union f a -> Union f a -> Bool
$c< :: forall (f :: * -> *) a. Ord (f a) => Union f a -> Union f a -> Bool
compare :: Union f a -> Union f a -> Ordering
$ccompare :: forall (f :: * -> *) a.
Ord (f a) =>
Union f a -> Union f a -> Ordering
$cp1Ord :: forall (f :: * -> *) a. Ord (f a) => Eq (Union f a)
Ord, Int -> Union f a -> ShowS
[Union f a] -> ShowS
Union f a -> String
(Int -> Union f a -> ShowS)
-> (Union f a -> String)
-> ([Union f a] -> ShowS)
-> Show (Union f a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (f :: * -> *) a. Show (f a) => Int -> Union f a -> ShowS
forall (f :: * -> *) a. Show (f a) => [Union f a] -> ShowS
forall (f :: * -> *) a. Show (f a) => Union f a -> String
showList :: [Union f a] -> ShowS
$cshowList :: forall (f :: * -> *) a. Show (f a) => [Union f a] -> ShowS
show :: Union f a -> String
$cshow :: forall (f :: * -> *) a. Show (f a) => Union f a -> String
showsPrec :: Int -> Union f a -> ShowS
$cshowsPrec :: forall (f :: * -> *) a. Show (f a) => Int -> Union f a -> ShowS
Show, Functor (Union f)
Foldable (Union f)
Functor (Union f)
-> Foldable (Union f)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Union f a -> f (Union f b))
-> (forall (f :: * -> *) a.
Applicative f =>
Union f (f a) -> f (Union f a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Union f a -> m (Union f b))
-> (forall (m :: * -> *) a.
Monad m =>
Union f (m a) -> m (Union f a))
-> Traversable (Union f)
(a -> f b) -> Union f a -> f (Union f b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (f :: * -> *). Traversable f => Functor (Union f)
forall (f :: * -> *). Traversable f => Foldable (Union f)
forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
Union f (m a) -> m (Union f a)
forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
Union f (f a) -> f (Union f a)
forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Union f a -> m (Union f b)
forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Union f a -> f (Union f b)
forall (m :: * -> *) a. Monad m => Union f (m a) -> m (Union f a)
forall (f :: * -> *) a.
Applicative f =>
Union f (f a) -> f (Union f a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Union f a -> m (Union f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Union f a -> f (Union f b)
sequence :: Union f (m a) -> m (Union f a)
$csequence :: forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
Union f (m a) -> m (Union f a)
mapM :: (a -> m b) -> Union f a -> m (Union f b)
$cmapM :: forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Union f a -> m (Union f b)
sequenceA :: Union f (f a) -> f (Union f a)
$csequenceA :: forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
Union f (f a) -> f (Union f a)
traverse :: (a -> f b) -> Union f a -> f (Union f b)
$ctraverse :: forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Union f a -> f (Union f b)
$cp2Traversable :: forall (f :: * -> *). Traversable f => Foldable (Union f)
$cp1Traversable :: forall (f :: * -> *). Traversable f => Functor (Union f)
Traversable)
instance (Applicative f, Ord a) => Semigroup (Union f a) where
Union Interval f a
i1 <> :: Union f a -> Union f a -> Union f a
<> Union Interval f a
i2 = Interval f a -> Union f a
forall (f :: * -> *) a. Interval f a -> Union f a
Union ((a -> a -> a
forall a. Ord a => a -> a -> a
min(a -> a -> a) -> (a -> a -> a) -> Interval f (a -> a -> a)
forall (f :: * -> *) a. Applicative f => a -> a -> Interval f a
...a -> a -> a
forall a. Ord a => a -> a -> a
max) Interval f (a -> a -> a) -> Interval f a -> Interval f (a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Interval f a
i1 Interval f (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Interval f a
i2)
{-# INLINE (<>) #-}
stimes :: b -> Union f a -> Union f a
stimes = b -> Union f a -> Union f a
forall b a. Integral b => b -> a -> a
stimesIdempotent
{-# INLINE stimes #-}
union :: forall f a . (Applicative f, Ord a) => Interval f a -> Interval f a -> Interval f a
union :: Interval f a -> Interval f a -> Interval f a
union = (Union f a -> Union f a -> Union f a)
-> Interval f a -> Interval f a -> Interval f a
coerce (Union f a -> Union f a -> Union f a
forall a. Semigroup a => a -> a -> a
(<>) :: Union f a -> Union f a -> Union f a)
{-# INLINE union #-}
newtype Intersection f a = Intersection { Intersection f a -> Interval f a
getIntersection :: Interval f a }
deriving (Functor (Intersection f)
a -> Intersection f a
Functor (Intersection f)
-> (forall a. a -> Intersection f a)
-> (forall a b.
Intersection f (a -> b) -> Intersection f a -> Intersection f b)
-> (forall a b c.
(a -> b -> c)
-> Intersection f a -> Intersection f b -> Intersection f c)
-> (forall a b.
Intersection f a -> Intersection f b -> Intersection f b)
-> (forall a b.
Intersection f a -> Intersection f b -> Intersection f a)
-> Applicative (Intersection f)
Intersection f a -> Intersection f b -> Intersection f b
Intersection f a -> Intersection f b -> Intersection f a
Intersection f (a -> b) -> Intersection f a -> Intersection f b
(a -> b -> c)
-> Intersection f a -> Intersection f b -> Intersection f c
forall a. a -> Intersection f a
forall a b.
Intersection f a -> Intersection f b -> Intersection f a
forall a b.
Intersection f a -> Intersection f b -> Intersection f b
forall a b.
Intersection f (a -> b) -> Intersection f a -> Intersection f b
forall a b c.
(a -> b -> c)
-> Intersection f a -> Intersection f b -> Intersection f c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (f :: * -> *). Applicative f => Functor (Intersection f)
forall (f :: * -> *) a. Applicative f => a -> Intersection f a
forall (f :: * -> *) a b.
Applicative f =>
Intersection f a -> Intersection f b -> Intersection f a
forall (f :: * -> *) a b.
Applicative f =>
Intersection f a -> Intersection f b -> Intersection f b
forall (f :: * -> *) a b.
Applicative f =>
Intersection f (a -> b) -> Intersection f a -> Intersection f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> Intersection f a -> Intersection f b -> Intersection f c
<* :: Intersection f a -> Intersection f b -> Intersection f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
Intersection f a -> Intersection f b -> Intersection f a
*> :: Intersection f a -> Intersection f b -> Intersection f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Intersection f a -> Intersection f b -> Intersection f b
liftA2 :: (a -> b -> c)
-> Intersection f a -> Intersection f b -> Intersection f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> Intersection f a -> Intersection f b -> Intersection f c
<*> :: Intersection f (a -> b) -> Intersection f a -> Intersection f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Intersection f (a -> b) -> Intersection f a -> Intersection f b
pure :: a -> Intersection f a
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Intersection f a
$cp1Applicative :: forall (f :: * -> *). Applicative f => Functor (Intersection f)
Applicative, Intersection f a -> Intersection f a -> Bool
(Intersection f a -> Intersection f a -> Bool)
-> (Intersection f a -> Intersection f a -> Bool)
-> Eq (Intersection f a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (f :: * -> *) a.
Eq (f a) =>
Intersection f a -> Intersection f a -> Bool
/= :: Intersection f a -> Intersection f a -> Bool
$c/= :: forall (f :: * -> *) a.
Eq (f a) =>
Intersection f a -> Intersection f a -> Bool
== :: Intersection f a -> Intersection f a -> Bool
$c== :: forall (f :: * -> *) a.
Eq (f a) =>
Intersection f a -> Intersection f a -> Bool
Eq, a -> Intersection f a -> Bool
Intersection f m -> m
Intersection f a -> [a]
Intersection f a -> Bool
Intersection f a -> Int
Intersection f a -> a
Intersection f a -> a
Intersection f a -> a
Intersection f a -> a
(a -> m) -> Intersection f a -> m
(a -> m) -> Intersection f a -> m
(a -> b -> b) -> b -> Intersection f a -> b
(a -> b -> b) -> b -> Intersection f a -> b
(b -> a -> b) -> b -> Intersection f a -> b
(b -> a -> b) -> b -> Intersection f a -> b
(a -> a -> a) -> Intersection f a -> a
(a -> a -> a) -> Intersection f a -> a
(forall m. Monoid m => Intersection f m -> m)
-> (forall m a. Monoid m => (a -> m) -> Intersection f a -> m)
-> (forall m a. Monoid m => (a -> m) -> Intersection f a -> m)
-> (forall a b. (a -> b -> b) -> b -> Intersection f a -> b)
-> (forall a b. (a -> b -> b) -> b -> Intersection f a -> b)
-> (forall b a. (b -> a -> b) -> b -> Intersection f a -> b)
-> (forall b a. (b -> a -> b) -> b -> Intersection f a -> b)
-> (forall a. (a -> a -> a) -> Intersection f a -> a)
-> (forall a. (a -> a -> a) -> Intersection f a -> a)
-> (forall a. Intersection f a -> [a])
-> (forall a. Intersection f a -> Bool)
-> (forall a. Intersection f a -> Int)
-> (forall a. Eq a => a -> Intersection f a -> Bool)
-> (forall a. Ord a => Intersection f a -> a)
-> (forall a. Ord a => Intersection f a -> a)
-> (forall a. Num a => Intersection f a -> a)
-> (forall a. Num a => Intersection f a -> a)
-> Foldable (Intersection f)
forall a. Eq a => a -> Intersection f a -> Bool
forall a. Num a => Intersection f a -> a
forall a. Ord a => Intersection f a -> a
forall m. Monoid m => Intersection f m -> m
forall a. Intersection f a -> Bool
forall a. Intersection f a -> Int
forall a. Intersection f a -> [a]
forall a. (a -> a -> a) -> Intersection f a -> a
forall m a. Monoid m => (a -> m) -> Intersection f a -> m
forall b a. (b -> a -> b) -> b -> Intersection f a -> b
forall a b. (a -> b -> b) -> b -> Intersection f a -> b
forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> Intersection f a -> Bool
forall (f :: * -> *) a.
(Foldable f, Num a) =>
Intersection f a -> a
forall (f :: * -> *) a.
(Foldable f, Ord a) =>
Intersection f a -> a
forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
Intersection f m -> m
forall (f :: * -> *) a. Foldable f => Intersection f a -> Bool
forall (f :: * -> *) a. Foldable f => Intersection f a -> Int
forall (f :: * -> *) a. Foldable f => Intersection f a -> [a]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> Intersection f a -> a
forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Intersection f a -> m
forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> Intersection f a -> b
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> Intersection f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Intersection f a -> a
$cproduct :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
Intersection f a -> a
sum :: Intersection f a -> a
$csum :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
Intersection f a -> a
minimum :: Intersection f a -> a
$cminimum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
Intersection f a -> a
maximum :: Intersection f a -> a
$cmaximum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
Intersection f a -> a
elem :: a -> Intersection f a -> Bool
$celem :: forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> Intersection f a -> Bool
length :: Intersection f a -> Int
$clength :: forall (f :: * -> *) a. Foldable f => Intersection f a -> Int
null :: Intersection f a -> Bool
$cnull :: forall (f :: * -> *) a. Foldable f => Intersection f a -> Bool
toList :: Intersection f a -> [a]
$ctoList :: forall (f :: * -> *) a. Foldable f => Intersection f a -> [a]
foldl1 :: (a -> a -> a) -> Intersection f a -> a
$cfoldl1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> Intersection f a -> a
foldr1 :: (a -> a -> a) -> Intersection f a -> a
$cfoldr1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> Intersection f a -> a
foldl' :: (b -> a -> b) -> b -> Intersection f a -> b
$cfoldl' :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> Intersection f a -> b
foldl :: (b -> a -> b) -> b -> Intersection f a -> b
$cfoldl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> Intersection f a -> b
foldr' :: (a -> b -> b) -> b -> Intersection f a -> b
$cfoldr' :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> Intersection f a -> b
foldr :: (a -> b -> b) -> b -> Intersection f a -> b
$cfoldr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> Intersection f a -> b
foldMap' :: (a -> m) -> Intersection f a -> m
$cfoldMap' :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Intersection f a -> m
foldMap :: (a -> m) -> Intersection f a -> m
$cfoldMap :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> Intersection f a -> m
fold :: Intersection f m -> m
$cfold :: forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
Intersection f m -> m
Foldable, a -> Intersection f b -> Intersection f a
(a -> b) -> Intersection f a -> Intersection f b
(forall a b. (a -> b) -> Intersection f a -> Intersection f b)
-> (forall a b. a -> Intersection f b -> Intersection f a)
-> Functor (Intersection f)
forall a b. a -> Intersection f b -> Intersection f a
forall a b. (a -> b) -> Intersection f a -> Intersection f b
forall (f :: * -> *) a b.
Functor f =>
a -> Intersection f b -> Intersection f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Intersection f a -> Intersection f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Intersection f b -> Intersection f a
$c<$ :: forall (f :: * -> *) a b.
Functor f =>
a -> Intersection f b -> Intersection f a
fmap :: (a -> b) -> Intersection f a -> Intersection f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Intersection f a -> Intersection f b
Functor, Applicative (Intersection f)
a -> Intersection f a
Applicative (Intersection f)
-> (forall a b.
Intersection f a -> (a -> Intersection f b) -> Intersection f b)
-> (forall a b.
Intersection f a -> Intersection f b -> Intersection f b)
-> (forall a. a -> Intersection f a)
-> Monad (Intersection f)
Intersection f a -> (a -> Intersection f b) -> Intersection f b
Intersection f a -> Intersection f b -> Intersection f b
forall a. a -> Intersection f a
forall a b.
Intersection f a -> Intersection f b -> Intersection f b
forall a b.
Intersection f a -> (a -> Intersection f b) -> Intersection f b
forall (f :: * -> *). Monad f => Applicative (Intersection f)
forall (f :: * -> *) a. Monad f => a -> Intersection f a
forall (f :: * -> *) a b.
Monad f =>
Intersection f a -> Intersection f b -> Intersection f b
forall (f :: * -> *) a b.
Monad f =>
Intersection f a -> (a -> Intersection f b) -> Intersection f b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Intersection f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> Intersection f a
>> :: Intersection f a -> Intersection f b -> Intersection f b
$c>> :: forall (f :: * -> *) a b.
Monad f =>
Intersection f a -> Intersection f b -> Intersection f b
>>= :: Intersection f a -> (a -> Intersection f b) -> Intersection f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
Intersection f a -> (a -> Intersection f b) -> Intersection f b
$cp1Monad :: forall (f :: * -> *). Monad f => Applicative (Intersection f)
Monad, Eq (Intersection f a)
Eq (Intersection f a)
-> (Intersection f a -> Intersection f a -> Ordering)
-> (Intersection f a -> Intersection f a -> Bool)
-> (Intersection f a -> Intersection f a -> Bool)
-> (Intersection f a -> Intersection f a -> Bool)
-> (Intersection f a -> Intersection f a -> Bool)
-> (Intersection f a -> Intersection f a -> Intersection f a)
-> (Intersection f a -> Intersection f a -> Intersection f a)
-> Ord (Intersection f a)
Intersection f a -> Intersection f a -> Bool
Intersection f a -> Intersection f a -> Ordering
Intersection f a -> Intersection f a -> Intersection f a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (f :: * -> *) a. Ord (f a) => Eq (Intersection f a)
forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Bool
forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Ordering
forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Intersection f a
min :: Intersection f a -> Intersection f a -> Intersection f a
$cmin :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Intersection f a
max :: Intersection f a -> Intersection f a -> Intersection f a
$cmax :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Intersection f a
>= :: Intersection f a -> Intersection f a -> Bool
$c>= :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Bool
> :: Intersection f a -> Intersection f a -> Bool
$c> :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Bool
<= :: Intersection f a -> Intersection f a -> Bool
$c<= :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Bool
< :: Intersection f a -> Intersection f a -> Bool
$c< :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Bool
compare :: Intersection f a -> Intersection f a -> Ordering
$ccompare :: forall (f :: * -> *) a.
Ord (f a) =>
Intersection f a -> Intersection f a -> Ordering
$cp1Ord :: forall (f :: * -> *) a. Ord (f a) => Eq (Intersection f a)
Ord, Int -> Intersection f a -> ShowS
[Intersection f a] -> ShowS
Intersection f a -> String
(Int -> Intersection f a -> ShowS)
-> (Intersection f a -> String)
-> ([Intersection f a] -> ShowS)
-> Show (Intersection f a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (f :: * -> *) a.
Show (f a) =>
Int -> Intersection f a -> ShowS
forall (f :: * -> *) a. Show (f a) => [Intersection f a] -> ShowS
forall (f :: * -> *) a. Show (f a) => Intersection f a -> String
showList :: [Intersection f a] -> ShowS
$cshowList :: forall (f :: * -> *) a. Show (f a) => [Intersection f a] -> ShowS
show :: Intersection f a -> String
$cshow :: forall (f :: * -> *) a. Show (f a) => Intersection f a -> String
showsPrec :: Int -> Intersection f a -> ShowS
$cshowsPrec :: forall (f :: * -> *) a.
Show (f a) =>
Int -> Intersection f a -> ShowS
Show, Functor (Intersection f)
Foldable (Intersection f)
Functor (Intersection f)
-> Foldable (Intersection f)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Intersection f a -> f (Intersection f b))
-> (forall (f :: * -> *) a.
Applicative f =>
Intersection f (f a) -> f (Intersection f a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Intersection f a -> m (Intersection f b))
-> (forall (m :: * -> *) a.
Monad m =>
Intersection f (m a) -> m (Intersection f a))
-> Traversable (Intersection f)
(a -> f b) -> Intersection f a -> f (Intersection f b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (f :: * -> *). Traversable f => Functor (Intersection f)
forall (f :: * -> *). Traversable f => Foldable (Intersection f)
forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
Intersection f (m a) -> m (Intersection f a)
forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
Intersection f (f a) -> f (Intersection f a)
forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Intersection f a -> m (Intersection f b)
forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Intersection f a -> f (Intersection f b)
forall (m :: * -> *) a.
Monad m =>
Intersection f (m a) -> m (Intersection f a)
forall (f :: * -> *) a.
Applicative f =>
Intersection f (f a) -> f (Intersection f a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Intersection f a -> m (Intersection f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Intersection f a -> f (Intersection f b)
sequence :: Intersection f (m a) -> m (Intersection f a)
$csequence :: forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
Intersection f (m a) -> m (Intersection f a)
mapM :: (a -> m b) -> Intersection f a -> m (Intersection f b)
$cmapM :: forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Intersection f a -> m (Intersection f b)
sequenceA :: Intersection f (f a) -> f (Intersection f a)
$csequenceA :: forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
Intersection f (f a) -> f (Intersection f a)
traverse :: (a -> f b) -> Intersection f a -> f (Intersection f b)
$ctraverse :: forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Intersection f a -> f (Intersection f b)
$cp2Traversable :: forall (f :: * -> *). Traversable f => Foldable (Intersection f)
$cp1Traversable :: forall (f :: * -> *). Traversable f => Functor (Intersection f)
Traversable)
instance (Applicative f, Ord a) => Semigroup (Intersection f a) where
Intersection Interval f a
i1 <> :: Intersection f a -> Intersection f a -> Intersection f a
<> Intersection Interval f a
i2 = Interval f a -> Intersection f a
forall (f :: * -> *) a. Interval f a -> Intersection f a
Intersection ((a -> a -> a
forall a. Ord a => a -> a -> a
max(a -> a -> a) -> (a -> a -> a) -> Interval f (a -> a -> a)
forall (f :: * -> *) a. Applicative f => a -> a -> Interval f a
...a -> a -> a
forall a. Ord a => a -> a -> a
min) Interval f (a -> a -> a) -> Interval f a -> Interval f (a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Interval f a
i1 Interval f (a -> a) -> Interval f a -> Interval f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Interval f a
i2)
{-# INLINE (<>) #-}
stimes :: b -> Intersection f a -> Intersection f a
stimes = b -> Intersection f a -> Intersection f a
forall b a. Integral b => b -> a -> a
stimesIdempotent
{-# INLINE stimes #-}
intersection :: forall f a . (Applicative f, Ord a) => Interval f a -> Interval f a -> Interval f a
intersection :: Interval f a -> Interval f a -> Interval f a
intersection = (Intersection f a -> Intersection f a -> Intersection f a)
-> Interval f a -> Interval f a -> Interval f a
coerce (Intersection f a -> Intersection f a -> Intersection f a
forall a. Semigroup a => a -> a -> a
(<>) :: Intersection f a -> Intersection f a -> Intersection f a)
{-# INLINE intersection #-}
liftRelation :: (Applicative f, Foldable f) => (a -> b -> Bool) -> f a -> f b -> Bool
liftRelation :: (a -> b -> Bool) -> f a -> f b -> Bool
liftRelation a -> b -> Bool
rel f a
a f b
b = f Bool -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ((a -> b -> Bool) -> f a -> f b -> f Bool
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> Bool
rel f a
a f b
b)
{-# INLINE liftRelation #-}
infix 4 `lte`, `gte`
lte, gte :: (Applicative f, Foldable f, Ord a) => f a -> f a -> Bool
lte :: f a -> f a -> Bool
lte = (a -> a -> Bool) -> f a -> f a -> Bool
forall (f :: * -> *) a b.
(Applicative f, Foldable f) =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftRelation a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
{-# INLINE lte #-}
gte :: f a -> f a -> Bool
gte = (a -> a -> Bool) -> f a -> f a -> Bool
forall (f :: * -> *) a b.
(Applicative f, Foldable f) =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftRelation a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
{-# INLINE gte #-}
type Lens' s a = forall f . Functor f => (a -> f a) -> (s -> f s)
lens :: (s -> a) -> (s -> a -> s) -> Lens' s a
lens :: (s -> a) -> (s -> a -> s) -> Lens' s a
lens s -> a
get s -> a -> s
put a -> f a
afa s
s = (a -> s) -> f a -> f s
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (s -> a -> s
put s
s) (a -> f a
afa (s -> a
get s
s))
{-# INLINE lens #-}