Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- genObjectId :: IO ObjectId
- fval :: (forall a. Val a => a -> b) -> Value -> b
- (=:) :: Val v => Label -> v -> Field
- data ObjectId
- data UpdateOption = MultiUpdate
- type MongoAction = Action
- type MongoCollection = Collection
- type MongoDatabase = Database
- type MongoDocument = Document
- type MongoField = Field
- type MongoLabel = Label
- type MongoQuery = Query
- type MongoValue = Value
- type MongoVal = Val
- pattern MongoArray :: [Value] -> MongoValue
- pattern MongoBin :: Binary -> MongoValue
- pattern MongoBool :: Bool -> MongoValue
- pattern MongoDoc :: Document -> MongoValue
- pattern MongoFloat :: Double -> MongoValue
- pattern MongoFun :: Function -> MongoValue
- pattern MongoInt32 :: Int32 -> MongoValue
- pattern MongoInt64 :: Int64 -> MongoValue
- pattern MongoJavaScr :: Javascript -> MongoValue
- pattern MongoMd5 :: MD5 -> MongoValue
- pattern MongoMinMax :: MinMaxKey -> MongoValue
- pattern MongoNull :: MongoValue
- pattern MongoObjId :: ObjectId -> MongoValue
- pattern MongoRegEx :: Regex -> MongoValue
- pattern MongoStamp :: MongoStamp -> MongoValue
- pattern MongoString :: Text -> MongoValue
- pattern MongoSym :: Symbol -> MongoValue
- pattern MongoUserDef :: UserDefined -> MongoValue
- pattern MongoUTC :: UTCTime -> MongoValue
- pattern MongoUuid :: UUID -> MongoValue
- mongoFailed :: WriteResult -> Bool
- mongoInsert_ :: MonadIO m => MongoCollection -> MongoDocument -> MongoAction m ()
- mongoModified :: WriteResult -> Maybe Int
- mongoSelect :: MongoSelector -> MongoCollection -> MongoQuery
- mongoUpdateMany :: MonadIO m => MongoCollection -> [(MongoSelector, MongoDocument, [UpdateOption])] -> MongoAction m WriteResult
Documentation
genObjectId :: IO ObjectId #
Create a fresh 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.
data UpdateOption #
MultiUpdate | If set, the database will update all matching objects in the collection. Otherwise only updates first matching doc |
Instances
Eq UpdateOption | |
Defined in Database.MongoDB.Internal.Protocol (==) :: UpdateOption -> UpdateOption -> Bool # (/=) :: UpdateOption -> UpdateOption -> Bool # | |
Show UpdateOption | |
Defined in Database.MongoDB.Internal.Protocol showsPrec :: Int -> UpdateOption -> ShowS # show :: UpdateOption -> String # showList :: [UpdateOption] -> ShowS # |
type MongoAction = Action Source #
type MongoCollection = Collection Source #
type MongoDatabase = Database Source #
type MongoDocument = Document Source #
type MongoField = Field Source #
type MongoLabel = Label Source #
type MongoQuery = Query Source #
type MongoValue = Value Source #
pattern MongoArray :: [Value] -> MongoValue Source #
pattern MongoBin :: Binary -> MongoValue Source #
pattern MongoBool :: Bool -> MongoValue Source #
pattern MongoDoc :: Document -> MongoValue Source #
pattern MongoFloat :: Double -> MongoValue Source #
pattern MongoFun :: Function -> MongoValue Source #
pattern MongoInt32 :: Int32 -> MongoValue Source #
pattern MongoInt64 :: Int64 -> MongoValue Source #
pattern MongoJavaScr :: Javascript -> MongoValue Source #
pattern MongoMd5 :: MD5 -> MongoValue Source #
pattern MongoMinMax :: MinMaxKey -> MongoValue Source #
pattern MongoNull :: MongoValue Source #
pattern MongoObjId :: ObjectId -> MongoValue Source #
pattern MongoRegEx :: Regex -> MongoValue Source #
pattern MongoStamp :: MongoStamp -> MongoValue Source #
pattern MongoString :: Text -> MongoValue Source #
pattern MongoSym :: Symbol -> MongoValue Source #
pattern MongoUserDef :: UserDefined -> MongoValue Source #
pattern MongoUTC :: UTCTime -> MongoValue Source #
pattern MongoUuid :: UUID -> MongoValue Source #
mongoFailed :: WriteResult -> Bool Source #
mongoInsert_ :: MonadIO m => MongoCollection -> MongoDocument -> MongoAction m () Source #
mongoModified :: WriteResult -> Maybe Int Source #
mongoSelect :: MongoSelector -> MongoCollection -> MongoQuery Source #
mongoUpdateMany :: MonadIO m => MongoCollection -> [(MongoSelector, MongoDocument, [UpdateOption])] -> MongoAction m WriteResult Source #