Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type Document = [Field]
- (!?) :: Val a => Document -> Label -> Maybe a
- look :: MonadFail m => Label -> Document -> m Value
- lookup :: (Val v, MonadFail m) => Label -> Document -> m v
- valueAt :: Label -> Document -> Value
- at :: Val v => Label -> Document -> v
- include :: [Label] -> Document -> Document
- exclude :: [Label] -> Document -> Document
- merge :: Document -> Document -> Document
- data Field = (:=) {}
- (=:) :: Val v => Label -> v -> Field
- (=?) :: Val a => Label -> Maybe a -> Document
- type Label = Text
- data Value
- class (Typeable a, Show a, Eq a) => Val a where
- fval :: (forall a. Val a => a -> b) -> Value -> b
- cast :: (Val a, MonadFail m) => Value -> m a
- typed :: Val a => Value -> a
- typeOfVal :: Value -> TypeRep
- newtype Binary = Binary ByteString
- newtype Function = Function ByteString
- newtype UUID = UUID ByteString
- newtype MD5 = MD5 ByteString
- newtype UserDefined = UserDefined ByteString
- data Regex = Regex Text Text
- data Javascript = Javascript Document Text
- newtype Symbol = Symbol Text
- newtype MongoStamp = MongoStamp Int64
- data MinMaxKey
- data ObjectId = Oid !Word32 !Word64
- timestamp :: ObjectId -> UTCTime
- genObjectId :: IO ObjectId
- showHexLen :: (Show n, Integral n) => Int -> n -> ShowS
Document
(!?) :: Val a => Document -> Label -> Maybe a Source #
Recursively lookup a nested field in a Document.
look :: MonadFail m => Label -> Document -> m Value Source #
Value of field in document, or fail (Nothing) if field not found
lookup :: (Val v, MonadFail 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.
at :: Val v => Label -> Document -> v Source #
Typed value of field in document. Error if missing or wrong type.
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
A BSON field is a named value, where the name (label) is a string and the value is a BSON Value
(=?) :: Val a => Label -> Maybe a -> Document infix 0 Source #
If Just value then return one field document, otherwise return empty document
Value
A BSON value is one of the following types of values
class (Typeable a, Show a, Eq a) => Val a where Source #
Haskell types of this class correspond to BSON value types
valList :: [a] -> Value Source #
valMaybe :: Maybe a -> Value Source #
cast' :: Value -> Maybe a Source #
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 UTCTime Source # | |
Val POSIXTime 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 # | |
Val a => Val (Maybe a) Source # | |
cast :: (Val a, MonadFail m) => Value -> m a Source #
Convert Value to expected type, or fail (Nothing) if not of that type
Special Bson value types
newtype UserDefined Source #
Instances
Eq UserDefined Source # | |
Defined in Data.Bson (==) :: UserDefined -> UserDefined -> Bool # (/=) :: UserDefined -> UserDefined -> Bool # | |
Ord UserDefined Source # | |
Defined in Data.Bson compare :: UserDefined -> UserDefined -> Ordering # (<) :: UserDefined -> UserDefined -> Bool # (<=) :: UserDefined -> UserDefined -> Bool # (>) :: UserDefined -> UserDefined -> Bool # (>=) :: UserDefined -> UserDefined -> Bool # max :: UserDefined -> UserDefined -> UserDefined # min :: UserDefined -> UserDefined -> UserDefined # | |
Read UserDefined Source # | |
Defined in Data.Bson readsPrec :: Int -> ReadS UserDefined # readList :: ReadS [UserDefined] # readPrec :: ReadPrec UserDefined # readListPrec :: ReadPrec [UserDefined] # | |
Show UserDefined Source # | |
Defined in Data.Bson showsPrec :: Int -> UserDefined -> ShowS # show :: UserDefined -> String # showList :: [UserDefined] -> ShowS # | |
Val UserDefined 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.
data Javascript Source #
Javascript code with possibly empty environment mapping variables to values that the code may reference
Instances
Eq Javascript Source # | |
Defined in Data.Bson (==) :: Javascript -> Javascript -> Bool # (/=) :: Javascript -> Javascript -> Bool # | |
Ord Javascript Source # | |
Defined in Data.Bson compare :: Javascript -> Javascript -> Ordering # (<) :: Javascript -> Javascript -> Bool # (<=) :: Javascript -> Javascript -> Bool # (>) :: Javascript -> Javascript -> Bool # (>=) :: Javascript -> Javascript -> Bool # max :: Javascript -> Javascript -> Javascript # min :: Javascript -> Javascript -> Javascript # | |
Show Javascript Source # | |
Defined in Data.Bson showsPrec :: Int -> Javascript -> ShowS # show :: Javascript -> String # showList :: [Javascript] -> ShowS # | |
Val Javascript Source # | |
newtype MongoStamp Source #
Instances
Eq MongoStamp Source # | |
Defined in Data.Bson (==) :: MongoStamp -> MongoStamp -> Bool # (/=) :: MongoStamp -> MongoStamp -> Bool # | |
Ord MongoStamp Source # | |
Defined in Data.Bson compare :: MongoStamp -> MongoStamp -> Ordering # (<) :: MongoStamp -> MongoStamp -> Bool # (<=) :: MongoStamp -> MongoStamp -> Bool # (>) :: MongoStamp -> MongoStamp -> Bool # (>=) :: MongoStamp -> MongoStamp -> Bool # max :: MongoStamp -> MongoStamp -> MongoStamp # min :: MongoStamp -> MongoStamp -> MongoStamp # | |
Read MongoStamp Source # | |
Defined in Data.Bson readsPrec :: Int -> ReadS MongoStamp # readList :: ReadS [MongoStamp] # readPrec :: ReadPrec MongoStamp # readListPrec :: ReadPrec [MongoStamp] # | |
Show MongoStamp Source # | |
Defined in Data.Bson showsPrec :: Int -> MongoStamp -> ShowS # show :: MongoStamp -> String # showList :: [MongoStamp] -> ShowS # | |
Val MongoStamp Source # | |
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.
genObjectId :: IO ObjectId Source #
Create a fresh ObjectId