lub-0.1.8: information operators: least upper bound (lub) and greatest lower bound (glb)
Copyright(c) Conal Elliott 2008
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Lub

Description

Compute least upper bound (lub) of two values, with respect to information content. I.e., merge the information available in each. For flat types (in which all values are either bottom or fully defined), lub is equivalent to unamb.

Synopsis

Least upper bounds

class HasLub a where Source #

Types that support information merging (lub)

Minimal complete definition

Nothing

Methods

lub :: a -> a -> a Source #

Least upper information bound. Combines information available from each argument. The arguments must be consistent, i.e., must have a common upper bound.

default lub :: (Generic a, GHasLub (Rep a)) => a -> a -> a Source #

lubs :: [a] -> a Source #

n-ary lub. Defaults to foldr lub undefined

Instances

Instances details
HasLub Bool Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Bool -> Bool -> Bool Source #

lubs :: [Bool] -> Bool Source #

HasLub Char Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Char -> Char -> Char Source #

lubs :: [Char] -> Char Source #

HasLub Double Source # 
Instance details

Defined in Data.Lub

HasLub Float Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Float -> Float -> Float Source #

lubs :: [Float] -> Float Source #

HasLub Int Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Int -> Int -> Int Source #

lubs :: [Int] -> Int Source #

HasLub Integer Source # 
Instance details

Defined in Data.Lub

HasLub Ordering Source # 
Instance details

Defined in Data.Lub

HasLub () Source # 
Instance details

Defined in Data.Lub

Methods

lub :: () -> () -> () Source #

lubs :: [()] -> () Source #

HasLub Void Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Void -> Void -> Void Source #

lubs :: [Void] -> Void Source #

HasLub TypeRep Source # 
Instance details

Defined in Data.Lub

HasLub a => HasLub [a] Source # 
Instance details

Defined in Data.Lub

Methods

lub :: [a] -> [a] -> [a] Source #

lubs :: [[a]] -> [a] Source #

HasLub a => HasLub (Maybe a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Maybe a -> Maybe a -> Maybe a Source #

lubs :: [Maybe a] -> Maybe a Source #

HasLub a => HasLub (ZipList a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: ZipList a -> ZipList a -> ZipList a Source #

lubs :: [ZipList a] -> ZipList a Source #

HasLub a => HasLub (Identity a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Identity a -> Identity a -> Identity a Source #

lubs :: [Identity a] -> Identity a Source #

HasLub a => HasLub (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Lub a -> Lub a -> Lub a Source #

lubs :: [Lub a] -> Lub a Source #

HasLub b => HasLub (a -> b) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a -> b) -> (a -> b) -> a -> b Source #

lubs :: [a -> b] -> a -> b Source #

(HasLub a, HasLub b) => HasLub (Either a b) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Either a b -> Either a b -> Either a b Source #

lubs :: [Either a b] -> Either a b Source #

HasLub (TypeRep a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: TypeRep a -> TypeRep a -> TypeRep a Source #

lubs :: [TypeRep a] -> TypeRep a Source #

(HasLub a, HasLub b) => HasLub (a, b) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a, b) -> (a, b) -> (a, b) Source #

lubs :: [(a, b)] -> (a, b) Source #

HasLub (Proxy t) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Proxy t -> Proxy t -> Proxy t Source #

lubs :: [Proxy t] -> Proxy t Source #

(HasLub a, HasLub b, HasLub c) => HasLub (a, b, c) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

lubs :: [(a, b, c)] -> (a, b, c) Source #

HasLub a => HasLub (Const a b) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Const a b -> Const a b -> Const a b Source #

lubs :: [Const a b] -> Const a b Source #

HasLub (a :~: b) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a :~: b) -> (a :~: b) -> a :~: b Source #

lubs :: [a :~: b] -> a :~: b Source #

(HasLub (f a), HasLub (g a)) => HasLub ((f :+: g) a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (f :+: g) a -> (f :+: g) a -> (f :+: g) a Source #

lubs :: [(f :+: g) a] -> (f :+: g) a Source #

(HasLub (f a), HasLub (g a)) => HasLub ((f :*: g) a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

lubs :: [(f :*: g) a] -> (f :*: g) a Source #

(HasLub a, HasLub b, HasLub c, HasLub d) => HasLub (a, b, c, d) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

lubs :: [(a, b, c, d)] -> (a, b, c, d) Source #

(HasLub (f a), HasLub (g a)) => HasLub (Product f g a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Product f g a -> Product f g a -> Product f g a Source #

lubs :: [Product f g a] -> Product f g a Source #

(HasLub (f a), HasLub (g a)) => HasLub (Sum f g a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Sum f g a -> Sum f g a -> Sum f g a Source #

lubs :: [Sum f g a] -> Sum f g a Source #

HasLub (a :~~: b) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a :~~: b) -> (a :~~: b) -> a :~~: b Source #

lubs :: [a :~~: b] -> a :~~: b Source #

(HasLub a, HasLub b, HasLub c, HasLub d, HasLub e) => HasLub (a, b, c, d, e) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

lubs :: [(a, b, c, d, e)] -> (a, b, c, d, e) Source #

HasLub (f (g a)) => HasLub (Compose f g a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Compose f g a -> Compose f g a -> Compose f g a Source #

lubs :: [Compose f g a] -> Compose f g a Source #

newtype Lub a Source #

The Semigroup operation takes the least upper bound.

Constructors

Lub 

Fields

Instances

Instances details
Monad Lub Source # 
Instance details

Defined in Data.Lub

Methods

(>>=) :: Lub a -> (a -> Lub b) -> Lub b #

(>>) :: Lub a -> Lub b -> Lub b #

return :: a -> Lub a #

Functor Lub Source # 
Instance details

Defined in Data.Lub

Methods

fmap :: (a -> b) -> Lub a -> Lub b #

(<$) :: a -> Lub b -> Lub a #

Applicative Lub Source # 
Instance details

Defined in Data.Lub

Methods

pure :: a -> Lub a #

(<*>) :: Lub (a -> b) -> Lub a -> Lub b #

liftA2 :: (a -> b -> c) -> Lub a -> Lub b -> Lub c #

(*>) :: Lub a -> Lub b -> Lub b #

(<*) :: Lub a -> Lub b -> Lub a #

Eq a => Eq (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

(==) :: Lub a -> Lub a -> Bool #

(/=) :: Lub a -> Lub a -> Bool #

Ord a => Ord (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

compare :: Lub a -> Lub a -> Ordering #

(<) :: Lub a -> Lub a -> Bool #

(<=) :: Lub a -> Lub a -> Bool #

(>) :: Lub a -> Lub a -> Bool #

(>=) :: Lub a -> Lub a -> Bool #

max :: Lub a -> Lub a -> Lub a #

min :: Lub a -> Lub a -> Lub a #

Read a => Read (Lub a) Source # 
Instance details

Defined in Data.Lub

Show a => Show (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

showsPrec :: Int -> Lub a -> ShowS #

show :: Lub a -> String #

showList :: [Lub a] -> ShowS #

Generic (Lub a) Source # 
Instance details

Defined in Data.Lub

Associated Types

type Rep (Lub a) :: Type -> Type #

Methods

from :: Lub a -> Rep (Lub a) x #

to :: Rep (Lub a) x -> Lub a #

HasLub a => Semigroup (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

(<>) :: Lub a -> Lub a -> Lub a #

sconcat :: NonEmpty (Lub a) -> Lub a #

stimes :: Integral b => b -> Lub a -> Lub a #

HasLub a => Monoid (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

mempty :: Lub a #

mappend :: Lub a -> Lub a -> Lub a #

mconcat :: [Lub a] -> Lub a #

HasLub a => HasLub (Lub a) Source # 
Instance details

Defined in Data.Lub

Methods

lub :: Lub a -> Lub a -> Lub a Source #

lubs :: [Lub a] -> Lub a Source #

type Rep (Lub a) Source # 
Instance details

Defined in Data.Lub

type Rep (Lub a) = D1 ('MetaData "Lub" "Data.Lub" "lub-0.1.8-EVcRzQDgXRgLOxIQy65ZCB" 'True) (C1 ('MetaCons "Lub" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLub") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

flatLub :: a -> a -> a Source #

A lub for flat domains. Equivalent to unamb. Handy for defining HasLub instances, e.g.,

  instance HasLub Integer where lub = flatLub

Some useful special applications of lub

parCommute :: HasLub b => (a -> a -> b) -> a -> a -> b Source #

Turn a binary commutative operation into that tries both orders in parallel, lub-merging the results. Useful when there are special cases that don't require evaluating both arguments.

Similar to parCommute from Unamb, but uses lub instead of unamb.

ptimes :: (HasLub a, Eq a, Num a) => a -> a -> a Source #

Multiplication optimized for either argument being zero or one, where the other might be expensive/delayed.

Generic deriving

class GHasLub f Source #

Used for generic deriving of HasLub

Minimal complete definition

glub

Instances

Instances details
GHasLub' f => GHasLub (D1 ('MetaData _q _r _s 'False) f) Source # 
Instance details

Defined in Data.Lub

Methods

glub :: (Generic a, Rep a ~ D1 ('MetaData _q _r _s 'False) f) => a -> a -> a

HasLub x => GHasLub (D1 ('MetaData _q _r _s 'True) (C1 _t (S1 _u (K1 _v x :: Type -> Type)))) Source # 
Instance details

Defined in Data.Lub

Methods

glub :: (Generic a, Rep a ~ D1 ('MetaData _q _r _s 'True) (C1 _t (S1 _u (K1 _v x)))) => a -> a -> a

genericLub :: (Generic a, GHasLub (Rep a)) => a -> a -> a Source #

A suitable definition of lub for instances of Generic.