lattices-2.1: Fine-grained library for constructing and manipulating lattices
Copyright (C) 2010-2015 Maximilian Bolingbroke 2015-2019 Oleg Grenrus
License BSD-3-Clause (see the file LICENSE)
Maintainer Oleg Grenrus <oleg.grenrus@iki.fi>
Safe Haskell Safe
Language Haskell2010

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 Lexicographic ( Ordered Timestamp) v where the lattice structure handles the, presumably rare, case of matching Timestamp s. Typically this is done in an arbitary, but deterministic manner.

Constructors

Lexicographic !k !v

Instances

Instances details
BoundedJoinSemiLattice k => Monad ( Lexicographic k) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Functor ( Lexicographic k) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

BoundedJoinSemiLattice k => Applicative ( Lexicographic k) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Foldable ( Lexicographic k) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Traversable ( Lexicographic k) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Generic1 ( Lexicographic k :: Type -> Type ) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Associated Types

type Rep1 ( Lexicographic k) :: k -> Type Source #

( Eq k, Eq v) => Eq ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Data k, Data v) => Data ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

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) Source #

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

toConstr :: Lexicographic k v -> Constr Source #

dataTypeOf :: Lexicographic k v -> DataType Source #

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

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

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

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

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

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

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

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

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

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

( Ord k, Ord v) => Ord ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Read k, Read v) => Read ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Show k, Show v) => Show ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Generic ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

Associated Types

type Rep ( Lexicographic k v) :: Type -> Type Source #

( Function k, Function v) => Function ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Arbitrary k, Arbitrary v) => Arbitrary ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( CoArbitrary k, CoArbitrary v) => CoArbitrary ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( NFData k, NFData v) => NFData ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Hashable k, Hashable v) => Hashable ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Universe k, Universe v) => Universe ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( Finite k, Finite v) => Finite ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( PartialOrd k, PartialOrd v) => PartialOrd ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( PartialOrd k, BoundedMeetSemiLattice k, BoundedJoinSemiLattice v, BoundedMeetSemiLattice v) => BoundedMeetSemiLattice ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( PartialOrd k, BoundedJoinSemiLattice k, BoundedJoinSemiLattice v, BoundedMeetSemiLattice v) => BoundedJoinSemiLattice ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

( PartialOrd k, Lattice k, BoundedJoinSemiLattice v, BoundedMeetSemiLattice v) => Lattice ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

type Rep1 ( Lexicographic k :: Type -> Type ) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic

type Rep ( Lexicographic k v) Source #
Instance details

Defined in Algebra.Lattice.Lexicographic