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

Data.Glb

Description

Greatest lower bound

Synopsis

Documentation

class HasGlb a where Source #

Types that support information intersection (glb)

Minimal complete definition

Nothing

Methods

glb :: a -> a -> a Source #

Greatest lower information bound. Intersects information available from each argument.

default glb :: (Generic a, GHasGlb (Rep a)) => a -> a -> a Source #

glbs1 :: [a] -> a Source #

n-ary glb for n > 0. Defaults to foldr1 glb. Unlike lub, we have no unit for glb.

Instances

Instances details
HasGlb Bool Source # 
Instance details

Defined in Data.Glb

Methods

glb :: Bool -> Bool -> Bool Source #

glbs1 :: [Bool] -> Bool Source #

HasGlb Char Source # 
Instance details

Defined in Data.Glb

Methods

glb :: Char -> Char -> Char Source #

glbs1 :: [Char] -> Char Source #

HasGlb Double Source # 
Instance details

Defined in Data.Glb

HasGlb Float Source # 
Instance details

Defined in Data.Glb

Methods

glb :: Float -> Float -> Float Source #

glbs1 :: [Float] -> Float Source #

HasGlb Int Source # 
Instance details

Defined in Data.Glb

Methods

glb :: Int -> Int -> Int Source #

glbs1 :: [Int] -> Int Source #

HasGlb Integer Source # 
Instance details

Defined in Data.Glb

HasGlb Ordering Source # 
Instance details

Defined in Data.Glb

HasGlb () Source # 
Instance details

Defined in Data.Glb

Methods

glb :: () -> () -> () Source #

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

HasGlb Void Source # 
Instance details

Defined in Data.Glb

Methods

glb :: Void -> Void -> Void Source #

glbs1 :: [Void] -> Void Source #

HasGlb TypeRep Source # 
Instance details

Defined in Data.Glb

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

glb :: Maybe a -> Maybe a -> Maybe a Source #

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

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

Defined in Data.Glb

Methods

glb :: ZipList a -> ZipList a -> ZipList a Source #

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

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

Defined in Data.Glb

Methods

glb :: Identity a -> Identity a -> Identity a Source #

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

HasGlb (TypeRep a) Source # 
Instance details

Defined in Data.Glb

Methods

glb :: TypeRep a -> TypeRep a -> TypeRep a Source #

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

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

Defined in Data.Glb

Methods

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

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

HasGlb (Proxy a) Source # 
Instance details

Defined in Data.Glb

Methods

glb :: Proxy a -> Proxy a -> Proxy a Source #

glbs1 :: [Proxy a] -> Proxy a Source #

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

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

Defined in Data.Glb

Methods

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

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

glbBottom :: String -> a Source #

Bottom for a glb. In the form of error "glb: bottom (<reason>)", though not really an error.

flatGlb :: Eq a => a -> a -> a Source #

glb on flat types with equality. Gives bottom for unequal arguments.

class GHasGlb f Source #

Used for generic deriving of HasGlb

Minimal complete definition

gglb

Instances

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

Defined in Data.Glb

Methods

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

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

Defined in Data.Glb

Methods

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

genericGlb :: (Generic a, GHasGlb (Rep a)) => a -> a -> a Source #

A suitable definition of glb for instances of Generic.