crjdt-haskell-0.2.1: A Conflict-Free Replicated JSON Datatype for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Crjdt

Contents

Description

This module exports all necessarry data types and functions for expressing and executing commands which allow modifying and querying the state of JSON in local replica

Synopsis

Expressions

iter :: Expr -> Expr Source #

Starts iterating over the list.

   do
    let planetList = doc .> "planet" .> iter
    insert "Earth" planetList
 

next :: Expr -> Expr Source #

Moves to the next element in the list.

key :: Key Void -> Expr -> Expr Source #

Get value of given key in given expression.

doc :: Expr Source #

The root of the JSON object.

var :: Text -> Expr Source #

Variable.

Commands

newtype Command a Source #

Constructors

Command 

Fields

Instances

Monad Command Source # 

Methods

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

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

return :: a -> Command a #

fail :: String -> Command a #

Functor Command Source # 

Methods

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

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

Applicative Command Source # 

Methods

pure :: a -> Command a #

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

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

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

MonadFree Cmd Command Source # 

Methods

wrap :: Cmd (Command a) -> Command a #

yield :: Command () Source #

Apply commands received from other replicas to current replica.

keys :: Expr -> Command (Set (Key Void)) Source #

Get all keys of object pointed by given Expr.

values :: Expr -> Command [Val] Source #

Get all values of object pointed by given Expr.

insert :: Val -> Expr -> Command () Source #

Insert a Val in the list.

delete :: Expr -> Command () Source #

Delete the list element.

bind :: Text -> Expr -> Command Expr Source #

Let binding.

(-<) :: Text -> Expr -> Command Expr Source #

Let binding.

assign :: Expr -> Val -> Command () Source #

Assign value to the key pointed by given Expr.

(=:) :: Expr -> Val -> Command () infixr 5 Source #

Assign value to the key pointed by given Expr.

Values

string :: Text -> Val Source #

String literal.

   doc .> "planet" .= string "Earth"
 

emptyMap :: Val Source #

emptyMap corresponds to {}.

emptyList :: Val Source #

emptyList corresponds to [].

Evaluation and Execution

eval :: Ctx m => Expr -> m Result Source #

execute :: Ctx m => Command a -> m a Source #

Re-exports

data Void :: * #

Uninhabited data type

Since: 4.8.0.0

Instances

Eq Void 

Methods

(==) :: Void -> Void -> Bool #

(/=) :: Void -> Void -> Bool #

Data Void 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void #

toConstr :: Void -> Constr #

dataTypeOf :: Void -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Void) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) #

gmapT :: (forall b. Data b => b -> b) -> Void -> Void #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r #

gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void #

Ord Void 

Methods

compare :: Void -> Void -> Ordering #

(<) :: Void -> Void -> Bool #

(<=) :: Void -> Void -> Bool #

(>) :: Void -> Void -> Bool #

(>=) :: Void -> Void -> Bool #

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Read Void

Reading a Void value is always a parse error, considering Void as a data type with no constructors.

Show Void 

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Ix Void 

Methods

range :: (Void, Void) -> [Void] #

index :: (Void, Void) -> Void -> Int #

unsafeIndex :: (Void, Void) -> Void -> Int

inRange :: (Void, Void) -> Void -> Bool #

rangeSize :: (Void, Void) -> Int #

unsafeRangeSize :: (Void, Void) -> Int

Generic Void 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Semigroup Void 

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Exception Void 
IsString (Key Void) # 

Methods

fromString :: String -> Key Void #

type Rep Void 
type Rep Void = D1 (MetaData "Void" "Data.Void" "base" False) V1

(.>) :: b -> (b -> a) -> a infixl 4 Source #

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

Since: 4.8.0.0

Others