summaryrefslogtreecommitdiff
path: root/src/Data/Torrent/Block.hs
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-11-29 18:37:42 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-11-29 18:37:42 +0400
commit88b590239ad66f8624723beefefa8b0ef56942e1 (patch)
treec5e2e3afcb0ca97d469b371cbfada675a462442c /src/Data/Torrent/Block.hs
parentc689257a818c0a7581666f4bdfd4549e52dbd075 (diff)
More safiety in InfoHash convertions
Diffstat (limited to 'src/Data/Torrent/Block.hs')
-rw-r--r--src/Data/Torrent/Block.hs23
1 files changed, 0 insertions, 23 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs
index 987de653..37889a7a 100644
--- a/src/Data/Torrent/Block.hs
+++ b/src/Data/Torrent/Block.hs
@@ -37,9 +37,6 @@ import Data.Aeson.TH
37import qualified Data.ByteString.Lazy as Lazy 37import qualified Data.ByteString.Lazy as Lazy
38import Data.Char 38import Data.Char
39import Data.List as L 39import Data.List as L
40import Data.Binary as B
41import Data.Binary.Get as B
42import Data.Binary.Put as B
43import Data.Serialize as S 40import Data.Serialize as S
44import Text.PrettyPrint 41import Text.PrettyPrint
45import Text.PrettyPrint.Class 42import Text.PrettyPrint.Class
@@ -110,14 +107,6 @@ putInt :: S.Putter Int
110putInt = S.putWord32be . fromIntegral 107putInt = S.putWord32be . fromIntegral
111{-# INLINE putInt #-} 108{-# INLINE putInt #-}
112 109
113getIntB :: B.Get Int
114getIntB = fromIntegral <$> B.getWord32be
115{-# INLINE getIntB #-}
116
117putIntB :: Int -> B.Put
118putIntB = B.putWord32be . fromIntegral
119{-# INLINE putIntB #-}
120
121instance Serialize BlockIx where 110instance Serialize BlockIx where
122 {-# SPECIALIZE instance Serialize BlockIx #-} 111 {-# SPECIALIZE instance Serialize BlockIx #-}
123 get = BlockIx <$> getInt 112 get = BlockIx <$> getInt
@@ -131,18 +120,6 @@ instance Serialize BlockIx where
131 putInt ixLength 120 putInt ixLength
132 {-# INLINE put #-} 121 {-# INLINE put #-}
133 122
134instance Binary BlockIx where
135 {-# SPECIALIZE instance Binary BlockIx #-}
136 get = BlockIx <$> getIntB
137 <*> getIntB
138 <*> getIntB
139 {-# INLINE get #-}
140
141 put BlockIx {..} = do
142 putIntB ixPiece
143 putIntB ixOffset
144 putIntB ixLength
145
146instance Pretty BlockIx where 123instance Pretty BlockIx where
147 pretty BlockIx {..} = 124 pretty BlockIx {..} =
148 "piece = " <> int ixPiece <> "," <+> 125 "piece = " <> int ixPiece <> "," <+>