hails-0.1.1: IFC enforcing web platform framework

Safe HaskellUnsafe

Hails.Data.LBson.TCB

Contents

Description

This module exports an interface for LBSON (Labeled BSON) object. An LBSON object is either a BSON object (see Bson) with the added support for labeled Values. More specifically, a LBSON document is a list of Fields (which are 'Key'-'Value' pairs), where the Value of a Field can either be a standard Value type or a Labeled Value type.

Synopsis

UTF-8 String

Document

type Document l = [Field l]Source

A LBSON document is a list of Fields

look :: (Monad m, Label l) => Key -> Document l -> m (Value l)Source

Value of field in document, or fail (Nothing) if field not found

lookup :: (Val l v, Monad m, Label l) => Key -> Document l -> m vSource

Lookup value of field in document and cast to expected type. Fail (Nothing) if field not found or value not of expected type.

valueAt :: Label l => Key -> [Field l] -> Value lSource

Value of field in document. Error if missing.

at :: forall v l. (Val l v, Label l) => Key -> Document l -> vSource

Typed value of field in document. Error if missing or wrong type.

include :: Label l => [Key] -> Document l -> Document lSource

Only include fields of document in key list

exclude :: Label l => [Key] -> Document l -> Document lSource

Exclude fields from document in key list

merge :: Label l => Document l -> Document l -> Document lSource

Merge documents with preference given to first one when both have the same key. I.e. for every (k := v) in first argument, if k exists in second argument then replace its value with v, otherwise add (k := v) to second argument.

Field

data Field l Source

A Field is a 'Key'-'Value' pair.

Constructors

:= 

Fields

key :: !Key
 
value :: Value l
 

Instances

Typeable1 Field 
(LabelState l p s, Serialize l) => Insert l p s (Document l) 
(LabelState l p s, Serialize l, Insert l p s (Document l)) => Insert l p s (Labeled l (Document l)) 
Label l => Eq (Field l) 
Label l => Show (Field l) 
(Serialize l, Label l) => BsonDocSerialize (Document l) 

(=:) :: (Val l v, Label l) => Key -> v -> Field lSource

Field with given label and typed value

(=?) :: (Val l a, Label l) => Key -> Maybe a -> Document lSource

If Just value then return one field document, otherwise return empty document

type Key = LabelSource

A Key, or attribute is a BSON label.

hailsInternalKeyPrefix :: KeySource

This prefix is reserved for HAILS keys. It should not be used by arbitrary code.

isUnsafeKey :: Key -> BoolSource

Check if a key is unsafe.

Value

data Value l Source

A Value is either a standard BSON value, a labeled value, or a policy-labeled value.

Constructors

BsonVal Value

Unlabeled BSON value

LabeledVal (Labeled l Value)

Labeled (LBSON) value

PolicyLabeledVal (PolicyLabeled l Value)

Policy labeled (LBSON) value

Instances

Typeable1 Value 
Label l => Val l (Value l)

Every Value is a Val.

Label l => Eq (Value l)

Instance for Eq, only comparing unlabeled BSON values.

Label l => Show (Value l)

Instance for Show, only showing unlabeled BSON values.

class (Typeable a, Show a, Eq a, Label l) => Val l a whereSource

Haskell types of this class correspond to LBSON value types.

Methods

val :: a -> Value lSource

cast' :: Value l -> Maybe aSource

Instances

(Val a, Label l) => Val l a

Every type that is an instance of BSON Val is an instance of LBSON Val. This requires the use of OverlappingInstances extension.

Label l => Val l (Value l)

Every Value is a Val.

(Val a, Label l) => Val l (PolicyLabeled l a)

Convert between a policy-labeled value and a labeled BSON value.

(Val a, Label l) => Val l (Labeled l a)

Convert between a labeled value and a labeled BSON value.

cast :: forall m l a. (Label l, Val l a, Monad m) => Value l -> m aSource

Convert Value to expected type, or fail (Nothing) if not of that type

typed :: (Val l a, Label l) => Value l -> aSource

Convert Value to expected type. Error if not that type.

Policy labeled values

data PolicyLabeled l a Source

Simple sum type used to denote a policy-labeled type. A PolicyLabeled type can be either labeled (policy applied), or unabled (policy not yet applied).

Constructors

PU a

Policy was not applied

PL (Labeled l a)

Policy applied

Instances

Typeable2 PolicyLabeled 
(Val a, Label l) => Val l (PolicyLabeled l a)

Convert between a policy-labeled value and a labeled BSON value.

Label l => Eq (PolicyLabeled l a)

Necessary instance that just fails.

(Show a, Label l) => Show (PolicyLabeled l a)

Necessary instance that just fails.

pu :: (Label l, Val a) => a -> PolicyLabeled l aSource

Wrap an unlabeled value by PolicyLabeled.

pl :: (Label l, Val a) => Labeled l a -> PolicyLabeled l aSource

Wrap an already-labeled value by PolicyLabeled.

Special Bson value types

newtype UUID

Constructors

UUID ByteString 

newtype MD5

Constructors

MD5 ByteString 

Instances

data Regex

The first string is the regex pattern, the second is the regex options string. Options are identified by characters, which must be listed in alphabetical order. Valid options are *i* for case insensitive matching, *m* for multiline matching, *x* for verbose mode, *l* to make \w, \W, etc. locale dependent, *s* for dotall mode ("." matches everything), and *u* to make \w, \W, etc. match unicode.

Constructors

Regex UString UString 

data Javascript

Javascript code with possibly empty environment mapping variables to values that the code may reference

newtype Symbol

Constructors

Symbol UString 

ObjectId

data ObjectId

A BSON ObjectID is a 12-byte value consisting of a 4-byte timestamp (seconds since epoch), a 3-byte machine id, a 2-byte process id, and a 3-byte counter. Note that the timestamp and counter fields must be stored big endian unlike the rest of BSON. This is because they are compared byte-by-byte and we want to ensure a mostly increasing order.

Constructors

Oid Word32 Word64 

timestamp :: ObjectId -> UTCTime

Time when objectId was created

genObjectId :: LabelState l p s => LIO l p s ObjectIdSource

Generate fresh ObjectId.

Serializing Value, converting to Bson documents

safeToBsonValue :: Label l => Value l -> Maybe BsonValueSource

Safely convert from a Value to a BsonValue.

safeFromBsonValue :: (Serialize l, Label l) => BsonValue -> Maybe (Value l)Source

Safely convert from a BsonValue to a Value.

encodeDoc :: BsonDocSerialize doc => doc -> ByteStringSource

Encodea document

decodeDoc :: BsonDocSerialize doc => ByteString -> docSource

Decode a document

toBsonDoc :: (Serialize l, Label l) => Document l -> DocumentSource

Convert a Document to a Bson Document. It is an error to call this function with malformed Documents (i.e., those for which a policy has not been applied.

fromBsonDoc :: (Serialize l, Label l) => Document -> Document lSource

Convert a Bson Document to a Document. This implementation is relaxed and omits any fields that were not converted. Use the fromBsonDocStrict for a strict conversion.

fromBsonDocStrict :: (Serialize l, Label l) => Document -> Maybe (Document l)Source

Same as fromBsonDoc, but fails (returns Nothing) if any of the field values failed to be serialized.

sanitizeBsonValue :: Value -> ValueSource

If value is a document, remove any fields that have hailsInternalKeyPrefix as a prefix, otherwise return the value unchanged. This is equivilant to exceptInternal except it operates on BSON values as opposed to Hails Documents.