@@ -3,10 +3,9 @@ module Database.PostgreSQL.Protocol.Store.Encode where
3
3
import Data.Monoid (Monoid (.. ), (<>) )
4
4
import Foreign (poke , plusPtr , Ptr )
5
5
import Data.Int (Int16 , Int32 )
6
- import Data.Word (Word8 , Word16 , Word32 )
7
- import Data.Char (ord )
8
- import Data.Bits (shiftR )
6
+ import Data.Word
9
7
8
+ import Foreign
10
9
import Data.ByteString (ByteString )
11
10
import Data.ByteString.Internal as B (toForeignPtr )
12
11
import Data.Store.Core (Poke (.. ), unsafeEncodeWith , pokeStatePtr ,
@@ -15,65 +14,78 @@ import Data.Store.Core (Poke(..), unsafeEncodeWith, pokeStatePtr,
15
14
data Encode = Encode {- # UNPACK #-} !Int ! (Poke () )
16
15
17
16
instance Monoid Encode where
18
- mempty = Encode 0 . Poke $ \ _ offset -> pure (offset, () )
19
17
{-# INLINE mempty #-}
18
+ mempty = Encode 0 . Poke $ \ _ offset -> pure (offset, () )
20
19
21
- (Encode len1 f1) `mappend` (Encode len2 f2) = Encode (len1 + len2) (f1 *> f2)
22
20
{-# INLINE mappend #-}
21
+ (Encode len1 f1) `mappend` (Encode len2 f2) = Encode (len1 + len2) (f1 *> f2)
23
22
23
+ {-# INLINE getEncodeLen #-}
24
24
getEncodeLen :: Encode -> Int
25
25
getEncodeLen (Encode len _) = len
26
- {-# INLINE getEncodeLen #-}
27
26
27
+ {-# INLINE runEncode #-}
28
28
runEncode :: Encode -> ByteString
29
29
runEncode (Encode len f) = unsafeEncodeWith f len
30
- {-# INLINE runEncode #-}
31
30
32
- fixedPrim :: Int -> (Ptr Word8 -> IO () ) -> Encode
33
- fixedPrim len f = Encode len . Poke $ \ state offset -> do
31
+ {-# INLINE fixed #-}
32
+ fixed :: Int -> (Ptr Word8 -> IO () ) -> Encode
33
+ fixed len f = Encode len . Poke $ \ state offset -> do
34
34
f $ pokeStatePtr state `plusPtr` offset
35
35
let ! newOffset = offset + len
36
36
return (newOffset, () )
37
- {-# INLINE fixedPrim #-}
38
37
39
- putWord8 :: Word8 -> Encode
40
- putWord8 w = fixedPrim 1 $ \ p -> poke p w
41
- {-# INLINE putWord8 #-}
38
+ {-# INLINE putByteString #-}
39
+ putByteString :: ByteString -> Encode
40
+ putByteString bs =
41
+ let (ptr, offset, len) = toForeignPtr bs
42
+ in Encode len $ pokeFromForeignPtr ptr offset len
42
43
43
- putChar8 :: Char -> Encode
44
- putChar8 = putWord8 . fromIntegral . ord
45
- {-# INLINE putChar8 #-}
44
+ -- | C-like string
45
+ {-# INLINE putByteStringNull #-}
46
+ putByteStringNull :: ByteString -> Encode
47
+ putByteStringNull bs = putByteString bs <> putWord8 0
48
+
49
+ {-# INLINE putWord8 #-}
50
+ putWord8 :: Word8 -> Encode
51
+ putWord8 w = fixed 1 $ \ p -> poke p w
46
52
47
- putWord16BE :: Word16 -> Encode
48
- putWord16BE w = fixedPrim 2 $ \ p -> do
49
- poke p (fromIntegral (shiftR w 8 ) :: Word8 )
50
- poke (p `plusPtr` 1 ) (fromIntegral w :: Word8 )
51
53
{-# INLINE putWord16BE #-}
54
+ putWord16BE :: Word16 -> Encode
55
+ putWord16BE w = fixed 2 $ \ p -> poke (castPtr p) (byteSwap16 w)
52
56
53
- putWord32BE :: Word32 -> Encode
54
- putWord32BE w = fixedPrim 4 $ \ p -> do
55
- poke p (fromIntegral (shiftR w 24 ) :: Word8 )
56
- poke (p `plusPtr` 1 ) (fromIntegral (shiftR w 16 ) :: Word8 )
57
- poke (p `plusPtr` 2 ) (fromIntegral (shiftR w 8 ) :: Word8 )
58
- poke (p `plusPtr` 3 ) (fromIntegral w :: Word8 )
59
57
{-# INLINE putWord32BE #-}
58
+ putWord32BE :: Word32 -> Encode
59
+ putWord32BE w = fixed 4 $ \ p -> poke (castPtr p) (byteSwap32 w)
60
60
61
- putInt32BE :: Int32 -> Encode
62
- putInt32BE = putWord32BE . fromIntegral
63
- {-# INLINE putInt32BE #-}
61
+ {-# INLINE putWord64BE #-}
62
+ putWord64BE :: Word64 -> Encode
63
+ putWord64BE w = fixed 8 $ \ p -> poke (castPtr p) (byteSwap64 w)
64
64
65
+ {-# INLINE putInt16BE #-}
65
66
putInt16BE :: Int16 -> Encode
66
67
putInt16BE = putWord16BE . fromIntegral
67
- {-# INLINE putInt16BE #-}
68
68
69
- putByteString :: ByteString -> Encode
70
- putByteString bs =
71
- let (ptr, offset, len) = toForeignPtr bs
72
- in Encode len $ pokeFromForeignPtr ptr offset len
73
- {-# INLINE putByteString #-}
74
-
75
- -- | C-like string
76
- putPgString :: ByteString -> Encode
77
- putPgString bs = putByteString bs <> putWord8 0
78
- {-# INLINE putPgString #-}
69
+ {-# INLINE putInt32BE #-}
70
+ putInt32BE :: Int32 -> Encode
71
+ putInt32BE = putWord32BE . fromIntegral
79
72
73
+ {-# INLINE putInt64BE #-}
74
+ putInt64BE :: Int64 -> Encode
75
+ putInt64BE = putWord64BE . fromIntegral
76
+
77
+ {-# INLINE putFloat32BE #-}
78
+ putFloat32BE :: Float -> Encode
79
+ putFloat32BE float = fixed 4 $ \ ptr -> byteSwap32 <$> floatToWord float
80
+ >>= poke (castPtr ptr)
81
+
82
+ {-# INLINE putFloat64BE #-}
83
+ putFloat64BE :: Double -> Encode
84
+ putFloat64BE double = fixed 8 $ \ ptr -> byteSwap64 <$> floatToWord double
85
+ >>= poke (castPtr ptr)
86
+
87
+ {-# INLINE floatToWord #-}
88
+ floatToWord :: (Storable word , Storable float ) => float -> IO word
89
+ floatToWord float = alloca $ \ buf -> do
90
+ poke (castPtr buf) float
91
+ peek buf
0 commit comments