bson-0.3.2.2: BSON documents are JSON-like objects with a standard binary encoding.

Safe HaskellNone
LanguageHaskell2010

Data.Bson

Contents

Description

A BSON document is a JSON-like object with a standard binary encoding defined at bsonspec.org. This implements version 1.0 of that spec.

Use the GHC language extension OverloadedStrings to automatically convert String literals to Text

Synopsis

Document

type Document = [Field] Source #

A BSON document is a list of Fields

(!?) :: Val a => Document -> Label -> Maybe a Source #

Recursively lookup a nested field in a Document.

look :: Monad m => Label -> Document -> m Value Source #

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

lookup :: (Val v, Monad m) => Label -> Document -> m v Source #

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 -> Document -> Value Source #

Value of field in document. Error if missing.

at :: Val v => Label -> Document -> v Source #

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

include :: [Label] -> Document -> Document Source #

Only include fields of document in label list

exclude :: [Label] -> Document -> Document Source #

Exclude fields from document in label list

merge :: Document -> Document -> Document Source #

Merge documents with preference given to first one when both have the same label. 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 Source #

A BSON field is a named value, where the name (label) is a string and the value is a BSON Value

Constructors

(:=) infix 0 

Fields

(=:) :: Val v => Label -> v -> Field infix 0 Source #

Field with given label and typed value

(=?) :: Val a => Label -> Maybe a -> Document infix 0 Source #

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

type Label = Text Source #

The name of a BSON field

Value

class (Typeable a, Show a, Eq a) => Val a where Source #

Haskell types of this class correspond to BSON value types

Minimal complete definition

val, cast'

Instances

Val Bool Source # 
Val Char Source # 
Val Double Source # 
Val Float Source # 
Val Int Source # 
Val Int32 Source # 
Val Int64 Source # 
Val Integer Source # 
Val Text Source # 
Val POSIXTime Source # 
Val UTCTime Source # 
Val ObjectId Source # 
Val MinMaxKey Source # 
Val MongoStamp Source # 
Val Symbol Source # 
Val Javascript Source # 
Val Regex Source # 
Val UserDefined Source # 
Val MD5 Source # 
Val UUID Source # 
Val Function Source # 
Val Binary Source # 
Val Value Source # 
Val Field Source # 
Val a => Val [a] Source # 

Methods

val :: [a] -> Value Source #

valList :: [[a]] -> Value Source #

valMaybe :: Maybe [a] -> Value Source #

cast' :: Value -> Maybe [a] Source #

cast'List :: Value -> Maybe [[a]] Source #

cast'Maybe :: Value -> Maybe (Maybe [a]) Source #

Val a => Val (Maybe a) Source # 

fval :: (forall a. Val a => a -> b) -> Value -> b Source #

Apply generic function to typed value

cast :: (Val a, Monad m) => Value -> m a Source #

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

typed :: Val a => Value -> a Source #

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

typeOfVal :: Value -> TypeRep Source #

Type of typed value

Special Bson value types

newtype MD5 Source #

Constructors

MD5 ByteString 

data Regex Source #

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 Text Text 

ObjectId

data ObjectId Source #

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

Time when objectId was created

genObjectId :: IO ObjectId Source #

Create a fresh ObjectId

showHexLen :: (Show n, Integral n) => Int -> n -> ShowS Source #

showHex of n padded with leading zeros if necessary to fill d digits