hails-0.11.2.1: Multi-app web platform framework

Safe HaskellTrustworthy
LanguageHaskell98

Hails.Data.Hson

Contents

Description

This module exports the type for a Hails BSON document, HsonDoc and related classes for creating such documents. A Hails document is similar to Data.Bson's documents, but differs in two ways. First, Hails restricts the number of types to a subset of BSON's (see BsonVal). This restriction is primarily due to the fact that many of the BSON types are redundant and not used (at least within Hails). Second, Hails allows for documents to contain policy-labeled values.

Policy labeled values (PolicyLabeled) are permitted only at the "top-level" of a document. (This is primarily done to keep policy-specification simple and may change in the future.) Consequently to allow for nested documents and documents containing an array of values we separate top-level fields (HsonField), that may contain policy labeled values, from potentially-nested fields (BsonField). A top-level field HsonField is thus either a BsonField or a PolicyLabled value.

Example:

module Main (x, y) where

import Data.Text (Text)

import LIO.DCLabel
import LIO.Labeled.TCB (labelTCB)
import Hails.Data.Hson

-- | Create document, verbose approach
x :: HsonDocument
x = [ "myInt"  =: BsonInt32 42
    , "nested" =: BsonDoc [ "flag" =: BsonBool True]
    , "secret" =: (HsonLabeled $ hasPolicy (labelTCB dcPub (BsonString "hi")))
    ]

-- | Create same document, clean approach
y :: HsonDocument
y = [ "myInt" -: (42 :: Int)
    , "nested"  -: ([ "flag" -: True] :: BsonDocument)
    , "secret" -: labelTCB dcPub (toBsonValue ("hi" :: Text))
    ]

Both x and y with -XOverloadedStrings:

[myInt -: 42,nested -: [flag -: True],secret -: HsonLabeled]

Synopsis

Documents

type HsonDocument = [HsonField] Source

A top-level document containing HsonFields.

type BsonDocument = [BsonField] Source

A (possibly top-)level document containing BsonFields.

Operations on documents

class Field v f => DocOps v f | v -> f, f -> v where Source

Class used to implement operatoins on documents that return HsonValues or BsonValues. The main role of this function is to impose the functional dependency between values and fields. As a consequence looking up and getting valueAt in a HsonDocument (resp. BsonDocument) will return a HsonValue (resp. BsonValue). This eliminates the need to specify the end type of very query, but forces the programmer to cast between Hson and Bson values.

Minimal complete definition

serialize

Methods

look :: (Field v f, Monad m) => FieldName -> [f] -> m v Source

Find value of field in document, or fail not found.

valueAt :: Field v f => FieldName -> [f] -> v Source

Same as look, but fails if the value is not found.

serialize :: [f] -> ByteString Source

class DocValOps d v where Source

Class used to implement operations on documents that return Haskell values (as opposed to HsonValue or BsonValue).

Minimal complete definition

lookup

Methods

lookup :: Monad m => FieldName -> d -> m v Source

Same as look, but returns "unwrapped" value.

at :: FieldName -> d -> v Source

Same as valueAt, but returns "unwrapped" value.

include :: IsField f => [FieldName] -> [f] -> [f] Source

Only include fields specified.

exclude :: IsField f => [FieldName] -> [f] -> [f] Source

Exclude fields specified.

merge :: IsField f => [f] -> [f] -> [f] Source

Merge documents with preference given to first one when both have the same field name.

Converting tofrom HsonBson

isBsonDoc :: HsonDocument -> Bool Source

Returns true if the document is composed solely of BsonValues. This function is useful when converting from HsonDocument to BsonDocument.

hsonDocToBsonDoc :: HsonDocument -> BsonDocument Source

This is a relaxed version of hsonDocToBsonDocStrict that only converts fields containing BsonValues. In other words, the PolicyLabeled values are dropped.

hsonDocToBsonDocStrict :: Monad m => HsonDocument -> m BsonDocument Source

Convert an HsonDocument to a BsonDocument. If any of the fields contain PolicyLabeled values (i.e., are HsonLabeled values) this function fails, otherwise it returns the converted document. To check for failure use isBsonDoc.

Converting labeled requests

labeledRequestToHson :: MonadLIO DCLabel m => DCLabeled Request -> m (DCLabeled HsonDocument) Source

Convert a labeled request to a labeled document. Values of fields that have a name that ends with [] are converted to arrays and the suffix [] is stripped from the name.

Fields

type FieldName = Text Source

The name of a field.

class IsField f where Source

Class for retrieving the name of a field.

Methods

fieldName :: f -> FieldName Source

Get the name of a field.

class (IsField f, Show v, Show f) => Field v f where Source

Class used to define fields.

Methods

(=:) :: FieldName -> v -> f infix 0 Source

Given a name and value construct either a HsonField or BsonField

fieldValue :: Monad m => f -> m v Source

Get the field value.

class (Show v, Show f) => GenField v f where Source

Class used to define fields.

Methods

(-:) :: FieldName -> v -> f infix 0 Source

Given a name and Haskell value construct either a HsonField or a BsonField

Values

data HsonValue Source

An HsonValue is a top-level value that may either be a BsonValue or a policy labeled value. The separation of values into BsonValue and HsonValue is solely due to the restriction that policy-labeled values may only occur at the top level and BsonValues may be nested (e.g. using BsonArray and BsonDoc).

Constructors

HsonValue BsonValue

Bson value

HsonLabeled PolicyLabeled

Policy labeled value

data BsonValue Source

A BsonValue is a subset of BSON (Data.Bson) values. Note that a BsonValue cannot contain any labeled values; all labeled values occur in a document as HsonValues. Correspondingly, BsonValues may be arbitrarily nested.

Constructors

BsonFloat Double

Float value

BsonString Text

String value

BsonDoc BsonDocument

Inner document

BsonArray [BsonValue]

List of values

BsonBlob Binary

Binary blob value

BsonObjId ObjectId

Object Id value

BsonBool Bool

Boolean value

BsonUTC UTCTime

Time stamp value

BsonNull

The NULL value

BsonInt32 Int32

32-bit integer

BsonInt64 Int64

64-bit integer

data PolicyLabeled Source

A PolicyLabeled value can be either an unlabeled value for which the policy needs to be applied (NeedPolicyTCB), or an already labeled value (HasPolicyTCB). PolicyLabeled is a partially-opaque type; code should not be able to inspect the value of an unlabeleda value, but may inspect an already labeled value.

needPolicy :: BsonValue -> PolicyLabeled Source

Create a policy labeled value given an unlabeled HsonValue.

hasPolicy :: DCLabeled BsonValue -> PolicyLabeled Source

Create a policy labeled value a labeled HsonValue.

getPolicyLabeled :: Monad m => PolicyLabeled -> m (DCLabeled BsonValue) Source

Get the policy labeled value, only if the policy has been applied.

newtype Binary Source

Arbitrary binary blob

Constructors

Binary 

Fields

unBinary :: S8
 

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 

genObjectId :: MonadLIO DCLabel m => m ObjectId Source

Create a fresh ObjectId.