2010-01-17 01:22:05 +00:00
|
|
|
{-
|
|
|
|
|
|
|
|
Copyright (C) 2010 Scott R Parish <srp@srparish.net>
|
|
|
|
|
|
|
|
Permission is hereby granted, free of charge, to any person obtaining
|
|
|
|
a copy of this software and associated documentation files (the
|
|
|
|
"Software"), to deal in the Software without restriction, including
|
|
|
|
without limitation the rights to use, copy, modify, merge, publish,
|
|
|
|
distribute, sublicense, and/or sell copies of the Software, and to
|
|
|
|
permit persons to whom the Software is furnished to do so, subject to
|
|
|
|
the following conditions:
|
|
|
|
|
|
|
|
The above copyright notice and this permission notice shall be
|
|
|
|
included in all copies or substantial portions of the Software.
|
|
|
|
|
|
|
|
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
|
|
|
|
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
|
|
|
|
MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
|
|
|
|
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
|
|
|
|
LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION
|
|
|
|
OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION
|
|
|
|
WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2010-01-09 22:49:06 +00:00
|
|
|
module Database.MongoDB.BSON
|
|
|
|
(
|
2010-01-18 19:24:14 +00:00
|
|
|
-- * Types
|
2010-01-17 17:41:24 +00:00
|
|
|
BsonValue(..),
|
2010-01-21 04:29:27 +00:00
|
|
|
BsonDoc,
|
2010-01-18 05:08:14 +00:00
|
|
|
BinarySubType(..),
|
2010-01-18 21:03:25 +00:00
|
|
|
-- * BsonDoc Operations
|
2010-03-08 12:57:20 +00:00
|
|
|
empty,
|
2010-01-21 04:29:27 +00:00
|
|
|
-- * Type Conversion
|
|
|
|
fromBson, toBson,
|
|
|
|
fromBsonDoc, toBsonDoc,
|
|
|
|
-- * Binary encoding/decoding
|
|
|
|
getBsonDoc, putBsonDoc,
|
2010-03-13 06:23:05 +00:00
|
|
|
-- * ObjectId creation
|
2010-03-14 02:46:57 +00:00
|
|
|
ObjectIdGen, mkObjectIdGen, genObjectId,
|
2010-01-09 22:49:06 +00:00
|
|
|
)
|
|
|
|
where
|
2010-01-18 21:03:25 +00:00
|
|
|
import Prelude hiding (lookup)
|
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
import qualified Control.Arrow as Arrow
|
|
|
|
import Control.Exception
|
2010-01-07 03:56:57 +00:00
|
|
|
import Control.Monad
|
|
|
|
import Data.Binary
|
|
|
|
import Data.Binary.Get
|
|
|
|
import Data.Binary.IEEE754
|
|
|
|
import Data.Binary.Put
|
2010-03-13 06:23:05 +00:00
|
|
|
import Data.Bits
|
2010-01-19 00:32:44 +00:00
|
|
|
import Data.ByteString.Char8 as C8 hiding (empty)
|
2010-01-07 03:56:57 +00:00
|
|
|
import qualified Data.ByteString.Lazy as L
|
|
|
|
import qualified Data.ByteString.Lazy.UTF8 as L8
|
2010-01-18 05:08:14 +00:00
|
|
|
import qualified Data.ByteString.UTF8 as S8
|
2010-03-13 06:23:05 +00:00
|
|
|
import Data.Digest.OpenSSL.MD5
|
2010-01-07 03:56:57 +00:00
|
|
|
import Data.Int
|
2010-03-13 06:23:05 +00:00
|
|
|
import Data.IORef
|
2010-01-07 03:56:57 +00:00
|
|
|
import qualified Data.List as List
|
2010-03-08 12:57:20 +00:00
|
|
|
import qualified Data.Map as Map
|
2010-01-07 03:56:57 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
2010-01-18 15:57:25 +00:00
|
|
|
import Data.Typeable
|
2010-01-10 02:45:45 +00:00
|
|
|
import Database.MongoDB.Util
|
2010-03-13 06:23:05 +00:00
|
|
|
import Network.BSD
|
|
|
|
import Numeric
|
2010-03-14 02:46:57 +00:00
|
|
|
import System.IO.Unsafe
|
2010-03-13 06:23:05 +00:00
|
|
|
import System.Posix.Process
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-03-15 12:17:57 +00:00
|
|
|
-- | BsonValue is the type that can be used as a value in a 'BsonDoc'.
|
2010-01-17 17:41:24 +00:00
|
|
|
data BsonValue
|
|
|
|
= BsonDouble Double
|
|
|
|
| BsonString L8.ByteString
|
2010-03-06 18:28:57 +00:00
|
|
|
| BsonDoc BsonDoc
|
2010-01-17 17:41:24 +00:00
|
|
|
| BsonArray [BsonValue]
|
|
|
|
| BsonUndefined
|
|
|
|
| BsonBinary BinarySubType L.ByteString
|
2010-03-13 06:23:05 +00:00
|
|
|
| BsonObjectId Integer
|
2010-01-17 17:41:24 +00:00
|
|
|
| BsonBool !Bool
|
|
|
|
| BsonDate POSIXTime
|
|
|
|
| BsonNull
|
|
|
|
| BsonRegex L8.ByteString String
|
2010-03-08 13:04:04 +00:00
|
|
|
| BsonJSCode L8.ByteString
|
2010-01-17 17:41:24 +00:00
|
|
|
| BsonSymbol L8.ByteString
|
2010-03-08 13:04:04 +00:00
|
|
|
| BsonJSCodeWScope L8.ByteString BsonDoc
|
2010-01-17 17:41:24 +00:00
|
|
|
| BsonInt32 Int32
|
|
|
|
| BsonInt64 Int64
|
|
|
|
| BsonMinKey
|
|
|
|
| BsonMaxKey
|
2010-01-07 03:56:57 +00:00
|
|
|
deriving (Show, Eq, Ord)
|
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
type BsonDoc = [(L8.ByteString, BsonValue)]
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-01-19 00:32:44 +00:00
|
|
|
-- | An empty BsonDoc
|
|
|
|
empty :: BsonDoc
|
2010-03-08 12:57:20 +00:00
|
|
|
empty = []
|
2010-01-18 21:03:25 +00:00
|
|
|
|
2010-01-07 03:56:57 +00:00
|
|
|
data DataType =
|
2010-03-08 13:04:04 +00:00
|
|
|
DataMinKey | -- -1
|
|
|
|
DataNumber | -- 1
|
|
|
|
DataString | -- 2
|
|
|
|
DataDoc | -- 3
|
|
|
|
DataArray | -- 4
|
|
|
|
DataBinary | -- 5
|
|
|
|
DataUndefined | -- 6
|
|
|
|
DataOid | -- 7
|
|
|
|
DataBoolean | -- 8
|
|
|
|
DataDate | -- 9
|
|
|
|
DataNull | -- 10
|
|
|
|
DataRegex | -- 11
|
|
|
|
DataRef | -- 12
|
|
|
|
DataJSCode | -- 13
|
|
|
|
DataSymbol | -- 14
|
|
|
|
DataJSCodeWScope | -- 15
|
|
|
|
DataInt | -- 16
|
|
|
|
DataTimestamp | -- 17
|
|
|
|
DataLong | -- 18
|
|
|
|
DataMaxKey -- 127
|
2010-01-07 03:56:57 +00:00
|
|
|
deriving (Show, Read, Enum, Eq, Ord)
|
|
|
|
|
|
|
|
toDataType :: Int -> DataType
|
2010-01-25 02:58:49 +00:00
|
|
|
toDataType (-1) = DataMinKey
|
|
|
|
toDataType 127 = DataMaxKey
|
2010-01-07 03:56:57 +00:00
|
|
|
toDataType d = toEnum d
|
|
|
|
|
2010-03-13 05:03:37 +00:00
|
|
|
fromDataType :: DataType -> Int8
|
2010-01-25 02:58:49 +00:00
|
|
|
fromDataType DataMinKey = - 1
|
|
|
|
fromDataType DataMaxKey = 127
|
2010-03-13 05:03:37 +00:00
|
|
|
fromDataType d = fromIntegral $ fromEnum d
|
2010-01-07 03:56:57 +00:00
|
|
|
|
|
|
|
data BinarySubType =
|
2010-01-25 02:58:49 +00:00
|
|
|
BSTUNDEFINED1 |
|
2010-01-07 03:56:57 +00:00
|
|
|
BSTFunction | -- 1
|
|
|
|
BSTByteArray | -- 2
|
|
|
|
BSTUUID | -- 3
|
2010-01-25 02:58:49 +00:00
|
|
|
BSTUNDEFINED2 |
|
2010-01-07 03:56:57 +00:00
|
|
|
BSTMD5 | -- 5
|
|
|
|
BSTUserDefined
|
|
|
|
deriving (Show, Read, Enum, Eq, Ord)
|
|
|
|
|
|
|
|
toBinarySubType :: Int -> BinarySubType
|
|
|
|
toBinarySubType 0x80 = BSTUserDefined
|
|
|
|
toBinarySubType d = toEnum d
|
|
|
|
|
2010-03-13 05:03:37 +00:00
|
|
|
fromBinarySubType :: BinarySubType -> Int8
|
2010-01-07 03:56:57 +00:00
|
|
|
fromBinarySubType BSTUserDefined = 0x80
|
2010-03-13 05:03:37 +00:00
|
|
|
fromBinarySubType d = fromIntegral $ fromEnum d
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-03-13 06:23:05 +00:00
|
|
|
data ObjectIdGen = ObjectIdGen {
|
|
|
|
oigMachine :: Integer,
|
|
|
|
oigInc :: IORef Integer
|
|
|
|
}
|
|
|
|
|
2010-03-14 02:46:57 +00:00
|
|
|
globalObjectIdInc :: IORef Integer
|
|
|
|
{-# NOINLINE globalObjectIdInc #-}
|
|
|
|
globalObjectIdInc = unsafePerformIO (newIORef 0)
|
|
|
|
|
2010-03-15 12:17:57 +00:00
|
|
|
-- | Create a new 'ObjectIdGen', the structure that must be passed to
|
|
|
|
-- genObjectId to create a 'ObjectId'.
|
2010-03-13 06:23:05 +00:00
|
|
|
mkObjectIdGen :: IO ObjectIdGen
|
|
|
|
mkObjectIdGen = do
|
|
|
|
host <- liftM (fst . (!! 0) . readHex . List.take 6 . md5sum . C8.pack)
|
|
|
|
getHostName
|
2010-03-14 02:46:57 +00:00
|
|
|
return ObjectIdGen {oigMachine = host, oigInc = globalObjectIdInc}
|
2010-03-13 06:23:05 +00:00
|
|
|
|
2010-03-15 12:17:57 +00:00
|
|
|
-- | Create a new 'ObjectId'.
|
2010-03-13 06:23:05 +00:00
|
|
|
genObjectId :: ObjectIdGen -> IO BsonValue
|
|
|
|
genObjectId oig = do
|
|
|
|
now <- liftM (truncate . (realToFrac :: POSIXTime -> Double)) getPOSIXTime
|
|
|
|
pid <- liftM fromIntegral getProcessID
|
|
|
|
inc <- atomicModifyIORef (oigInc oig) $ \i -> ((i+1) `rem` 0x10000, i)
|
|
|
|
return $ BsonObjectId
|
|
|
|
((now `shiftL` 64) .|.
|
|
|
|
oigMachine oig `shiftL` 40 .|.
|
|
|
|
(0xffff .&. pid) `shiftL` 24 .|.
|
|
|
|
(inc `div` 0x100) `shiftL` 8 .|. (inc `rem` 0x100))
|
|
|
|
|
2010-03-15 12:17:57 +00:00
|
|
|
-- | Decode binary bytes into 'BsonDoc'.
|
2010-01-21 04:29:27 +00:00
|
|
|
getBsonDoc :: Get BsonDoc
|
|
|
|
getBsonDoc = liftM snd getDoc
|
|
|
|
|
2010-03-15 12:17:57 +00:00
|
|
|
-- | Encode 'BsonDoc' into binary bytes.
|
2010-01-21 04:29:27 +00:00
|
|
|
putBsonDoc :: BsonDoc -> Put
|
|
|
|
putBsonDoc = putObj
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-01-17 17:41:24 +00:00
|
|
|
getVal :: DataType -> Get (Integer, BsonValue)
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataNumber = liftM ((,) 8 . BsonDouble) getFloat64le
|
|
|
|
getVal DataString = do
|
2010-01-07 03:56:57 +00:00
|
|
|
sLen1 <- getI32
|
2010-01-17 03:40:22 +00:00
|
|
|
(_sLen2, s) <- getS
|
2010-01-17 17:41:24 +00:00
|
|
|
return (fromIntegral $ 4 + sLen1, BsonString s)
|
2010-03-06 18:28:57 +00:00
|
|
|
getVal DataDoc = getDoc >>= \(len, obj) -> return (len, BsonDoc obj)
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataArray = do
|
2010-03-08 12:57:20 +00:00
|
|
|
bytes <- getI32
|
|
|
|
arr <- getInnerArray (bytes - 4)
|
|
|
|
getNull
|
|
|
|
return (fromIntegral bytes, BsonArray arr)
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataBinary = do
|
2010-03-11 02:34:53 +00:00
|
|
|
len1 <- getI32
|
|
|
|
st <- getI8
|
|
|
|
(len, hdrLen) <- if toBinarySubType st == BSTByteArray
|
|
|
|
then do
|
|
|
|
len2 <- getI32
|
|
|
|
assert (len1 - 4 == len2) $ return ()
|
|
|
|
return (len2, 4 + 1 + 4)
|
|
|
|
else return (len1, 4 + 1)
|
|
|
|
bs <- getLazyByteString $ fromIntegral len
|
|
|
|
return (hdrLen + fromIntegral len, BsonBinary (toBinarySubType st) bs)
|
|
|
|
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataUndefined = return (1, BsonUndefined)
|
2010-03-13 06:23:05 +00:00
|
|
|
getVal DataOid = do
|
|
|
|
oid1 <- getWord64be
|
|
|
|
oid2 <- getWord32be
|
|
|
|
let oid = (fromIntegral oid1 `shiftL` 32) .|. fromIntegral oid2
|
|
|
|
return (12, BsonObjectId oid)
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataBoolean = liftM ((,) (1::Integer) . BsonBool . (/= (0::Int))) getI8
|
|
|
|
getVal DataDate = liftM ((,) 8 . BsonDate . flip (/) 1000 . realToFrac) getI64
|
|
|
|
getVal DataNull = return (1, BsonNull)
|
2010-03-08 13:04:04 +00:00
|
|
|
getVal DataRegex = fail "DataJSCode not yet supported" -- TODO
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataRef = fail "DataRef is deprecated"
|
2010-03-08 13:04:04 +00:00
|
|
|
getVal DataJSCode = do
|
|
|
|
sLen1 <- getI32
|
|
|
|
(_sLen2, s) <- getS
|
|
|
|
return (fromIntegral $ 4 + sLen1, BsonJSCode s)
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataSymbol = do
|
2010-01-17 03:40:22 +00:00
|
|
|
sLen1 <- getI32
|
|
|
|
(_sLen2, s) <- getS
|
2010-01-17 17:41:24 +00:00
|
|
|
return (fromIntegral $ 4 + sLen1, BsonString s)
|
2010-03-08 13:04:04 +00:00
|
|
|
getVal DataJSCodeWScope = do
|
2010-02-05 13:31:01 +00:00
|
|
|
sLen1 <- getI32
|
|
|
|
(_, qry) <- getS
|
|
|
|
(_, scope) <- getDoc
|
2010-03-08 13:04:04 +00:00
|
|
|
return (fromIntegral sLen1, BsonJSCodeWScope qry scope)
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataInt = liftM ((,) 4 . BsonInt32 . fromIntegral) getI32
|
|
|
|
getVal DataTimestamp = fail "DataTimestamp not yet supported" -- TODO
|
2010-01-17 03:40:22 +00:00
|
|
|
|
2010-01-25 02:58:49 +00:00
|
|
|
getVal DataLong = liftM ((,) 8 . BsonInt64) getI64
|
|
|
|
getVal DataMinKey = return (0, BsonMinKey)
|
|
|
|
getVal DataMaxKey = return (0, BsonMaxKey)
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
getInnerObj :: Int32 -> Get BsonDoc
|
|
|
|
getInnerObj 1 = return []
|
|
|
|
getInnerObj bytesLeft = do
|
2010-01-07 03:56:57 +00:00
|
|
|
typ <- getDataType
|
|
|
|
(keySz, key) <- getS
|
|
|
|
(valSz, val) <- getVal typ
|
2010-03-08 12:57:20 +00:00
|
|
|
rest <- getInnerObj (bytesLeft - 1 - fromIntegral keySz - fromIntegral valSz)
|
|
|
|
return $ (key, val) : rest
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-01-21 04:29:27 +00:00
|
|
|
getRawObj :: Get (Integer, BsonDoc)
|
2010-01-07 03:56:57 +00:00
|
|
|
getRawObj = do
|
|
|
|
bytes <- getI32
|
2010-03-08 12:57:20 +00:00
|
|
|
obj <- getInnerObj (bytes - 4)
|
2010-01-07 03:56:57 +00:00
|
|
|
getNull
|
2010-01-10 02:45:45 +00:00
|
|
|
return (fromIntegral bytes, obj)
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
getInnerArray :: Int32 -> Get [BsonValue]
|
|
|
|
getInnerArray 1 = return []
|
|
|
|
getInnerArray bytesLeft = do
|
|
|
|
typ <- getDataType
|
|
|
|
(keySz, _key) <- getS
|
|
|
|
(valSz, val) <- getVal typ
|
|
|
|
rest <- getInnerArray
|
|
|
|
(bytesLeft - 1 - fromIntegral keySz - fromIntegral valSz)
|
|
|
|
return $ val : rest
|
|
|
|
|
2010-01-17 17:41:24 +00:00
|
|
|
getDoc :: Get (Integer, BsonDoc)
|
2010-01-21 04:29:27 +00:00
|
|
|
getDoc = getRawObj
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-01-17 03:40:22 +00:00
|
|
|
getDataType :: Get DataType
|
2010-01-07 03:56:57 +00:00
|
|
|
getDataType = liftM toDataType getI8
|
|
|
|
|
2010-01-17 17:41:24 +00:00
|
|
|
putType :: BsonValue -> Put
|
2010-01-25 02:58:49 +00:00
|
|
|
putType BsonDouble{} = putDataType DataNumber
|
|
|
|
putType BsonString{} = putDataType DataString
|
2010-03-06 18:28:57 +00:00
|
|
|
putType BsonDoc{} = putDataType DataDoc
|
2010-01-25 02:58:49 +00:00
|
|
|
putType BsonArray{} = putDataType DataArray
|
|
|
|
putType BsonBinary{} = putDataType DataBinary
|
|
|
|
putType BsonUndefined = putDataType DataUndefined
|
|
|
|
putType BsonObjectId{} = putDataType DataOid
|
|
|
|
putType BsonBool{} = putDataType DataBoolean
|
|
|
|
putType BsonDate{} = putDataType DataDate
|
|
|
|
putType BsonNull = putDataType DataNull
|
|
|
|
putType BsonRegex{} = putDataType DataRegex
|
|
|
|
-- putType = putDataType DataRef
|
2010-03-08 13:04:04 +00:00
|
|
|
putType BsonJSCode {} = putDataType DataJSCode
|
2010-01-25 02:58:49 +00:00
|
|
|
putType BsonSymbol{} = putDataType DataSymbol
|
2010-03-08 13:04:04 +00:00
|
|
|
putType BsonJSCodeWScope{} = putDataType DataJSCodeWScope
|
2010-01-25 02:58:49 +00:00
|
|
|
putType BsonInt32 {} = putDataType DataInt
|
|
|
|
putType BsonInt64 {} = putDataType DataLong
|
|
|
|
-- putType = putDataType DataTimestamp
|
|
|
|
putType BsonMinKey = putDataType DataMinKey
|
|
|
|
putType BsonMaxKey = putDataType DataMaxKey
|
2010-01-17 17:41:24 +00:00
|
|
|
|
|
|
|
putVal :: BsonValue -> Put
|
|
|
|
putVal (BsonDouble d) = putFloat64le d
|
2010-02-05 13:31:01 +00:00
|
|
|
putVal (BsonString s) = putStrSz s
|
2010-03-06 18:28:57 +00:00
|
|
|
putVal (BsonDoc o) = putObj o
|
2010-01-17 17:41:24 +00:00
|
|
|
putVal (BsonArray es) = putOutterObj bs
|
2010-01-17 03:40:22 +00:00
|
|
|
where bs = runPut $ forM_ (List.zip [(0::Int) .. ] es) $ \(i, e) ->
|
2010-01-25 02:58:49 +00:00
|
|
|
putType e >> putS (L8.fromString $ show i) >> putVal e
|
2010-03-14 18:25:44 +00:00
|
|
|
putVal (BsonBinary t bs) = do
|
|
|
|
putI32 $ fromIntegral $ (if t == BSTByteArray then 4 else 0) + L.length bs
|
|
|
|
putI8 $ fromBinarySubType t
|
|
|
|
when (t == BSTByteArray) $ putI32 $ fromIntegral $ L.length bs
|
|
|
|
putLazyByteString bs
|
2010-01-17 17:41:24 +00:00
|
|
|
putVal BsonUndefined = putNothing
|
2010-03-13 06:23:05 +00:00
|
|
|
putVal (BsonObjectId o) = putWord64be (fromIntegral $ o `shiftR` 32) >>
|
|
|
|
putWord32be (fromIntegral $ o .&. 0xffffffff)
|
2010-03-13 05:03:37 +00:00
|
|
|
putVal (BsonBool False) = putI8 0
|
|
|
|
putVal (BsonBool True) = putI8 1
|
2010-01-17 17:41:24 +00:00
|
|
|
putVal (BsonDate pt) = putI64 $ round $ 1000 * (realToFrac pt :: Double)
|
|
|
|
putVal BsonNull = putNothing
|
|
|
|
putVal (BsonRegex r opt)= do putS r
|
|
|
|
putByteString $ pack $ List.sort opt
|
|
|
|
putNull
|
2010-03-08 13:04:04 +00:00
|
|
|
putVal (BsonJSCode c) = putStrSz c
|
2010-01-17 17:41:24 +00:00
|
|
|
putVal (BsonSymbol s) = putI32 (fromIntegral $ 1 + L8.length s) >> putS s
|
2010-03-08 13:04:04 +00:00
|
|
|
putVal (BsonJSCodeWScope q s) =
|
2010-02-05 13:31:01 +00:00
|
|
|
let bytes = runPut (putStrSz q >> putObj s)
|
2010-02-06 21:52:23 +00:00
|
|
|
in putI32 ((+4) $ fromIntegral $ L.length bytes) >> putLazyByteString bytes
|
2010-03-08 13:04:04 +00:00
|
|
|
putVal (BsonInt32 i) = putI32 i
|
|
|
|
putVal (BsonInt64 i) = putI64 i
|
2010-01-17 17:41:24 +00:00
|
|
|
putVal BsonMinKey = putNothing
|
|
|
|
putVal BsonMaxKey = putNothing
|
|
|
|
|
|
|
|
putObj :: BsonDoc -> Put
|
2010-01-07 03:56:57 +00:00
|
|
|
putObj obj = putOutterObj bs
|
2010-03-08 12:57:20 +00:00
|
|
|
where bs = runPut $ forM_ obj $ \(k, v) -> putType v >> putS k >> putVal v
|
2010-01-07 03:56:57 +00:00
|
|
|
|
2010-01-17 03:40:22 +00:00
|
|
|
putOutterObj :: L.ByteString -> Put
|
2010-01-07 03:56:57 +00:00
|
|
|
putOutterObj bytes = do
|
|
|
|
-- the length prefix and null term are included in the length
|
2010-01-10 02:45:45 +00:00
|
|
|
putI32 $ fromIntegral $ 4 + 1 + L.length bytes
|
2010-01-07 03:56:57 +00:00
|
|
|
putLazyByteString bytes
|
|
|
|
putNull
|
|
|
|
|
2010-01-17 03:40:22 +00:00
|
|
|
putDataType :: DataType -> Put
|
2010-01-07 03:56:57 +00:00
|
|
|
putDataType = putI8 . fromDataType
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
class BsonDocConv a where
|
|
|
|
-- | Convert a BsonDoc into another form such as a Map or a tuple
|
|
|
|
-- list with String keys.
|
|
|
|
fromBsonDoc :: BsonDoc -> a
|
|
|
|
-- | Convert a Map or a tuple list with String keys into a BsonDoc.
|
|
|
|
toBsonDoc :: a -> BsonDoc
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
instance BsonDocConv [(L8.ByteString, BsonValue)] where
|
|
|
|
fromBsonDoc = id
|
|
|
|
toBsonDoc = id
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
instance BsonDocConv [(String, BsonValue)] where
|
|
|
|
fromBsonDoc = List.map $ Arrow.first L8.toString
|
|
|
|
toBsonDoc = List.map $ Arrow.first L8.fromString
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
instance BsonDocConv (Map.Map L8.ByteString BsonValue) where
|
|
|
|
fromBsonDoc = Map.fromList
|
|
|
|
toBsonDoc = Map.toList
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
instance BsonDocConv (Map.Map String BsonValue) where
|
|
|
|
fromBsonDoc = Map.fromList . fromBsonDoc
|
|
|
|
toBsonDoc = toBsonDoc . Map.toList
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
data BsonUnsupportedConversion = BsonUnsupportedConversion
|
|
|
|
deriving (Eq, Show, Read)
|
2010-01-21 02:55:33 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
bsonUnsupportedConversion :: TyCon
|
|
|
|
bsonUnsupportedConversion =
|
|
|
|
mkTyCon "Database.MongoDB.BSON.BsonUnsupportedConversion "
|
2010-01-21 02:55:33 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
instance Typeable BsonUnsupportedConversion where
|
|
|
|
typeOf _ = mkTyConApp bsonUnsupportedConversion []
|
2010-01-21 02:55:33 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
instance Exception BsonUnsupportedConversion
|
2010-01-21 02:55:33 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
throwUnsupConv :: a
|
|
|
|
throwUnsupConv = throw BsonUnsupportedConversion
|
2010-01-18 05:08:14 +00:00
|
|
|
|
2010-03-08 12:57:20 +00:00
|
|
|
class BsonConv a where
|
|
|
|
-- | Convert a native Haskell type into a BsonValue.
|
|
|
|
toBson :: a -> BsonValue
|
|
|
|
-- | Convert a BsonValue into a native Haskell type.
|
|
|
|
fromBson :: BsonValue -> a
|
|
|
|
|
|
|
|
instance BsonConv Double where
|
|
|
|
toBson = BsonDouble
|
|
|
|
fromBson (BsonDouble d) = d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Float where
|
|
|
|
toBson = BsonDouble . realToFrac
|
|
|
|
fromBson (BsonDouble d) = realToFrac d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv L8.ByteString where
|
|
|
|
toBson = BsonString
|
|
|
|
fromBson (BsonString s) = s
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv String where
|
|
|
|
toBson = BsonString . L8.fromString
|
|
|
|
fromBson (BsonString s) = L8.toString s
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv S8.ByteString where
|
|
|
|
toBson bs = BsonString $ L.fromChunks [bs]
|
|
|
|
fromBson (BsonString s) = C8.concat $ L.toChunks s
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv BsonDoc where
|
|
|
|
toBson = BsonDoc
|
|
|
|
fromBson (BsonDoc d) = d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [(String, BsonValue)] where
|
|
|
|
toBson = toBson . toBsonDoc
|
|
|
|
fromBson (BsonDoc d) = fromBsonDoc d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv (Map.Map L8.ByteString BsonValue) where
|
|
|
|
toBson = toBson . toBsonDoc
|
|
|
|
fromBson (BsonDoc d) = fromBsonDoc d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv (Map.Map String BsonValue) where
|
|
|
|
toBson = toBson . toBsonDoc
|
|
|
|
fromBson (BsonDoc d) = fromBsonDoc d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv POSIXTime where
|
|
|
|
toBson = BsonDate
|
|
|
|
fromBson (BsonDate d) = d
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Bool where
|
|
|
|
toBson = BsonBool
|
|
|
|
fromBson (BsonBool b) = b
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Int where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Int8 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Int16 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Int32 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Int64 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Integer where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Word where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Word8 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Word16 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Word32 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv Word64 where
|
|
|
|
toBson i | i >= fromIntegral (minBound::Int32) &&
|
|
|
|
i <= fromIntegral (maxBound::Int32) = BsonInt32 $ fromIntegral i
|
|
|
|
| otherwise = BsonInt64 $ fromIntegral i
|
|
|
|
fromBson (BsonInt32 i) = fromIntegral i
|
|
|
|
fromBson (BsonInt64 i) = fromIntegral i
|
|
|
|
fromBson _ = throwUnsupConv
|
2010-03-09 14:22:30 +00:00
|
|
|
|
|
|
|
instance BsonConv [Double] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Float] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Int] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Int8] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Int16] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Int32] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Int64] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Integer] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Word] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Word8] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Word16] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Word32] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Word64] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [Bool] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [POSIXTime] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [String] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [L8.ByteString] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [S8.ByteString] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
|
|
|
|
|
|
|
instance BsonConv [BsonDoc] where
|
|
|
|
toBson = BsonArray . List.map toBson
|
|
|
|
fromBson (BsonArray ss) = List.map fromBson ss
|
|
|
|
fromBson _ = throwUnsupConv
|
2010-03-08 13:01:32 +00:00
|
|
|
|
|
|
|
instance (BsonConv a) => BsonConv (Maybe a) where
|
|
|
|
toBson Nothing = BsonNull
|
|
|
|
toBson (Just a) = toBson a
|
|
|
|
fromBson BsonNull = Nothing
|
|
|
|
fromBson a = Just $ fromBson a
|