lattices-1.5.0: Fine-grained library for constructing and manipulating lattices

Copyright(C) 2010-2015 Maximilian Bolingbroke, 2015 Oleg Grenrus
LicenseBSD-3-Clause (see the file LICENSE)
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellSafe
LanguageHaskell2010

Algebra.Lattice.Lexicographic

Description

 

Synopsis

Documentation

data Lexicographic k v Source

A pair lattice with a lexicographic ordering. This means in a join the second component of the resulting pair is the second component of the pair with the larger first component. If the first components are equal, then the second components will be joined. The meet is similar only it prefers the smaller first component.

An application of this type is versioning. For example, a Last-Writer-Wins register would look like 'Lexicographc (Ordered Timestamp) v' where the lattice structure handles the, presumably rare, case of matching Timestamps. Typically this is done in an arbitary, but deterministic manner.

Constructors

Lexicographic !k !v 

Instances

BoundedJoinSemiLattice k => Monad (Lexicographic k) Source 

Methods

(>>=) :: Lexicographic k a -> (a -> Lexicographic k b) -> Lexicographic k b

(>>) :: Lexicographic k a -> Lexicographic k b -> Lexicographic k b

return :: a -> Lexicographic k a

fail :: String -> Lexicographic k a

Functor (Lexicographic k) Source 

Methods

fmap :: (a -> b) -> Lexicographic k a -> Lexicographic k b

(<$) :: a -> Lexicographic k b -> Lexicographic k a

BoundedJoinSemiLattice k => Applicative (Lexicographic k) Source 

Methods

pure :: a -> Lexicographic k a

(<*>) :: Lexicographic k (a -> b) -> Lexicographic k a -> Lexicographic k b

(*>) :: Lexicographic k a -> Lexicographic k b -> Lexicographic k b

(<*) :: Lexicographic k a -> Lexicographic k b -> Lexicographic k a

Foldable (Lexicographic k) Source 

Methods

fold :: Monoid m => Lexicographic k m -> m

foldMap :: Monoid m => (a -> m) -> Lexicographic k a -> m

foldr :: (a -> b -> b) -> b -> Lexicographic k a -> b

foldr' :: (a -> b -> b) -> b -> Lexicographic k a -> b

foldl :: (b -> a -> b) -> b -> Lexicographic k a -> b

foldl' :: (b -> a -> b) -> b -> Lexicographic k a -> b

foldr1 :: (a -> a -> a) -> Lexicographic k a -> a

foldl1 :: (a -> a -> a) -> Lexicographic k a -> a

toList :: Lexicographic k a -> [a]

null :: Lexicographic k a -> Bool

length :: Lexicographic k a -> Int

elem :: Eq a => a -> Lexicographic k a -> Bool

maximum :: Ord a => Lexicographic k a -> a

minimum :: Ord a => Lexicographic k a -> a

sum :: Num a => Lexicographic k a -> a

product :: Num a => Lexicographic k a -> a

Traversable (Lexicographic k) Source 

Methods

traverse :: Applicative f => (a -> f b) -> Lexicographic k a -> f (Lexicographic k b)

sequenceA :: Applicative f => Lexicographic k (f a) -> f (Lexicographic k a)

mapM :: Monad m => (a -> m b) -> Lexicographic k a -> m (Lexicographic k b)

sequence :: Monad m => Lexicographic k (m a) -> m (Lexicographic k a)

Generic1 (Lexicographic k) Source 

Associated Types

type Rep1 (Lexicographic k :: * -> *) :: * -> *

(Eq k, Eq v) => Eq (Lexicographic k v) Source 

Methods

(==) :: Lexicographic k v -> Lexicographic k v -> Bool

(/=) :: Lexicographic k v -> Lexicographic k v -> Bool

(Data k, Data v) => Data (Lexicographic k v) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lexicographic k v -> c (Lexicographic k v)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Lexicographic k v)

toConstr :: Lexicographic k v -> Constr

dataTypeOf :: Lexicographic k v -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Lexicographic k v))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Lexicographic k v))

gmapT :: (forall b. Data b => b -> b) -> Lexicographic k v -> Lexicographic k v

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lexicographic k v -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lexicographic k v -> r

gmapQ :: (forall d. Data d => d -> u) -> Lexicographic k v -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Lexicographic k v -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lexicographic k v -> m (Lexicographic k v)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lexicographic k v -> m (Lexicographic k v)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lexicographic k v -> m (Lexicographic k v)

(Ord k, Ord v) => Ord (Lexicographic k v) Source 
(Read k, Read v) => Read (Lexicographic k v) Source 
(Show k, Show v) => Show (Lexicographic k v) Source 
Generic (Lexicographic k v) Source 

Associated Types

type Rep (Lexicographic k v) :: * -> *

Methods

from :: Lexicographic k v -> Rep (Lexicographic k v) x

to :: Rep (Lexicographic k v) x -> Lexicographic k v

(NFData k, NFData v) => NFData (Lexicographic k v) Source 

Methods

rnf :: Lexicographic k v -> ()

(Hashable k, Hashable v) => Hashable (Lexicographic k v) Source 

Methods

hashWithSalt :: Int -> Lexicographic k v -> Int

hash :: Lexicographic k v -> Int

(PartialOrd k, PartialOrd v) => PartialOrd (Lexicographic k v) Source 

Methods

leq :: Lexicographic k v -> Lexicographic k v -> Bool Source

(PartialOrd k, BoundedLattice k, BoundedLattice v) => BoundedLattice (Lexicographic k v) Source 
(PartialOrd k, BoundedMeetSemiLattice k, BoundedMeetSemiLattice v) => BoundedMeetSemiLattice (Lexicographic k v) Source 

Methods

top :: Lexicographic k v Source

(PartialOrd k, BoundedJoinSemiLattice k, BoundedJoinSemiLattice v) => BoundedJoinSemiLattice (Lexicographic k v) Source 
(PartialOrd k, Lattice k, Lattice v) => Lattice (Lexicographic k v) Source 
(PartialOrd k, MeetSemiLattice k, MeetSemiLattice v) => MeetSemiLattice (Lexicographic k v) Source 
(PartialOrd k, JoinSemiLattice k, JoinSemiLattice v) => JoinSemiLattice (Lexicographic k v) Source 
type Rep1 (Lexicographic k) Source 
type Rep (Lexicographic k v) Source