schedule-0.3.0.0: Pure deterministic scheduled computations

Safe HaskellNone
LanguageHaskell2010

Data.Rsv.RMMap

Contents

Description

This module implements a reservation multi-map.

Each insert is indexed by a key; many inserts (of the same or different items) may be performed on the same key.

A reservation data structure is one that allows multiple inserts of the same item, by returning a unique handle for each insert operation that must be given to the delete operation.

This API is experimental at the moment, and parts of it may change.

Synopsis

Documentation

data RMMap k a Source #

Constructors

RMMap 

Fields

Instances
(Eq k, Eq a) => Eq (RMMap k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Methods

(==) :: RMMap k a -> RMMap k a -> Bool #

(/=) :: RMMap k a -> RMMap k a -> Bool #

(Ord k, Read k, Read a) => Read (RMMap k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

(Show k, Show a) => Show (RMMap k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Methods

showsPrec :: Int -> RMMap k a -> ShowS #

show :: RMMap k a -> String #

showList :: [RMMap k a] -> ShowS #

Generic (RMMap k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Associated Types

type Rep (RMMap k a) :: Type -> Type #

Methods

from :: RMMap k a -> Rep (RMMap k a) x #

to :: Rep (RMMap k a) x -> RMMap k a #

type Rep (RMMap k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

type Rep (RMMap k a)

_handles :: forall k a. Lens' (RMMap k a) RHandles Source #

_content :: forall k a k a. Lens (RMMap k a) (RMMap k a) (Map k (Entries a)) (Map k (Entries a)) Source #

data Delete k a Source #

Instances
Eq k => Eq (Delete k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Methods

(==) :: Delete k a -> Delete k a -> Bool #

(/=) :: Delete k a -> Delete k a -> Bool #

Ord k => Ord (Delete k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Methods

compare :: Delete k a -> Delete k a -> Ordering #

(<) :: Delete k a -> Delete k a -> Bool #

(<=) :: Delete k a -> Delete k a -> Bool #

(>) :: Delete k a -> Delete k a -> Bool #

(>=) :: Delete k a -> Delete k a -> Bool #

max :: Delete k a -> Delete k a -> Delete k a #

min :: Delete k a -> Delete k a -> Delete k a #

Read k => Read (Delete k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Show k => Show (Delete k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Methods

showsPrec :: Int -> Delete k a -> ShowS #

show :: Delete k a -> String #

showList :: [Delete k a] -> ShowS #

Generic (Delete k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

Associated Types

type Rep (Delete k a) :: Type -> Type #

Methods

from :: Delete k a -> Rep (Delete k a) x #

to :: Rep (Delete k a) x -> Delete k a #

type Rep (Delete k a) Source # 
Instance details

Defined in Data.Rsv.RMMap

type Rep (Delete k a) = D1 (MetaData "Delete" "Data.Rsv.RMMap" "schedule-0.3.0.0-rXAR2JhUGJ487cqZKqedA" False) (C1 (MetaCons "Delete" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 k) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RHandle)))

checkValidity :: RMMap k a -> Maybe Text Source #

Check the map that its internal invariants all hold.

You must run this on every instance obtained not via the API functions here. For example, you must run this on instances obtained via deserialisation, which in general cannot check the complex invariants maintained by the API functions. Also, for all handles you obtain via a similarly non-standard method, including by deserialisation of a parent data structure, you must run checkHandle map handle.

Nothing means the check passed; Just errmsg gives a failure reason.

Note: this does not guard against all malicious behaviour, but it does guard against violation (either malicious or accidental) of the runtime invariants assumed by this data structure.

checkHandle :: RMMap k a -> Delete k a -> Bool Source #

Check that an existing handle is consistent with the current state of the structure, i.e. it is not a handle that could be generated in the future.

Read operations

(!) :: Ord k => RMMap k a -> k -> Seq a Source #

toList :: RMMap k a -> [Delete k a] Source #

Write operations

enqueue :: Ord k => (k, a) -> RMMap k a -> (Delete k a, RMMap k a) Source #

Append an item on a key, returning a handle to remove it with. The same item may be added twice, in which case it will occupy multiple positions in the map, and the handles distinguish these occurences.

unqueue :: Ord k => Delete k a -> RMMap k a -> (Maybe (k, a), RMMap k a) Source #

Delete an item corresponding to a given handle. If the item was already removed, Nothing is returned instead.

dequeue :: Ord k => k -> RMMap k a -> (Maybe (Delete k a, a), RMMap k a) Source #

Remove an item from a key, from the front. Return Nothing if key is empty.