summaryrefslogtreecommitdiff
path: root/bittorrent/src/System/Torrent/Storage.hs
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-09-15 06:22:10 -0400
committerjoe <joe@jerkface.net>2017-09-15 06:22:10 -0400
commit12cbb3af2413dc28838ed271351dda16df8f7bdb (patch)
tree2db77a787e18a81a8369a8d73fee369d8826f064 /bittorrent/src/System/Torrent/Storage.hs
parent362357c6d08cbd8dffa627a1e80199dcb9ba231f (diff)
Separating dht-client library from bittorrent package.
Diffstat (limited to 'bittorrent/src/System/Torrent/Storage.hs')
-rw-r--r--bittorrent/src/System/Torrent/Storage.hs221
1 files changed, 221 insertions, 0 deletions
diff --git a/bittorrent/src/System/Torrent/Storage.hs b/bittorrent/src/System/Torrent/Storage.hs
new file mode 100644
index 00000000..1d77e55d
--- /dev/null
+++ b/bittorrent/src/System/Torrent/Storage.hs
@@ -0,0 +1,221 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- This module implements mapping from single continious piece space
9-- to file storage. Storage can be used in two modes:
10--
11-- * As in memory storage - in this case we don't touch filesystem.
12--
13-- * As ordinary mmaped file storage - when we need to store
14-- data in the filesystem.
15--
16{-# LANGUAGE RecordWildCards #-}
17{-# LANGUAGE DeriveDataTypeable #-}
18module System.Torrent.Storage
19 ( -- * Storage
20 Storage
21 , StorageFailure (..)
22
23 -- * Construction
24 , Mode (..)
25 , def
26 , open
27 , openInfoDict
28 , close
29 , withStorage
30
31 -- * Query
32 , totalPieces
33 , verifyPiece
34 , genPieceInfo
35 , getBitfield
36
37 -- * Modification
38 , writePiece
39 , readPiece
40 , hintRead
41 , unsafeReadPiece
42
43 -- * Streaming
44 , sourceStorage
45 , sinkStorage
46 ) where
47
48import Control.Applicative
49import Control.Exception
50import Control.Monad as M
51import Control.Monad.Trans
52import Data.ByteString.Lazy as BL
53import Data.Conduit as C
54import Data.Conduit.Binary as C
55import Data.Conduit.List as C
56import Data.Typeable
57
58import Data.Torrent
59import Network.BitTorrent.Exchange.Bitfield as BF
60import System.Torrent.FileMap as FM
61
62
63-- | Some storage operations may throw an exception if misused.
64data StorageFailure
65 -- | Occurs on a write operation if the storage has been opened
66 -- using 'ReadOnly' mode.
67 = StorageIsRO
68
69 -- | Piece index is out of bounds.
70 | InvalidIndex PieceIx
71
72 -- | Piece size do not match with one passed to the 'open'
73 -- function.
74 | InvalidSize PieceSize
75 deriving (Show, Eq, Typeable)
76
77instance Exception StorageFailure
78
79-- | Pieces store.
80data Storage = Storage
81 { mode :: !Mode
82 , pieceLen :: {-# UNPACK #-} !PieceSize
83 , fileMap :: {-# UNPACK #-} !FileMap
84 }
85
86-- | Map torrent files:
87--
88-- * when torrent first created use 'ReadWriteEx' mode;
89--
90-- * when seeding, validation 'ReadOnly' mode.
91--
92open :: Mode -> PieceSize -> FileLayout FileSize -> IO Storage
93open mode s l
94 | s <= 0 = throwIO (InvalidSize s)
95 | otherwise = Storage mode s <$> mmapFiles mode l
96
97-- | Like 'open', but use 'InfoDict' file layout.
98openInfoDict :: Mode -> FilePath -> InfoDict -> IO Storage
99openInfoDict mode rootPath InfoDict {..} =
100 open mode (piPieceLength idPieceInfo) (flatLayout rootPath idLayoutInfo)
101
102-- | Unmaps all files forcefully. It is recommended but not required.
103close :: Storage -> IO ()
104close Storage {..} = unmapFiles fileMap
105
106-- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'.
107withStorage :: Mode -> PieceSize -> FileLayout FileSize
108 -> (Storage -> IO ()) -> IO ()
109withStorage m s l = bracket (open m s l) close
110
111-- TODO allocateStorage?
112
113-- | Count of pieces in the storage.
114totalPieces :: Storage -> PieceCount
115totalPieces Storage {..} = FM.size fileMap `sizeInBase` pieceLen
116
117isValidIx :: PieceIx -> Storage -> Bool
118isValidIx i s = 0 <= i && i < totalPieces s
119
120-- | Put piece data at the piece index by overwriting existing
121-- data.
122--
123-- This operation may throw 'StorageFailure'.
124--
125writePiece :: Piece BL.ByteString -> Storage -> IO ()
126writePiece p @ Piece {..} s @ Storage {..}
127 | mode == ReadOnly = throwIO StorageIsRO
128 | isNotValidIx pieceIndex = throwIO (InvalidIndex pieceIndex)
129 | isNotValidSize pieceIndex (pieceSize p)
130 = throwIO (InvalidSize (pieceSize p))
131 | otherwise = writeBytes offset pieceData fileMap
132 where
133 isNotValidSize pix psize
134 | succ pix == pcount = psize /= lastPieceLen -- last piece may be shorter
135 | otherwise = psize /= pieceLen
136 where
137 lastPieceLen = fromIntegral (FM.size fileMap `rem` fromIntegral pieceLen)
138 {-# INLINE isNotValidSize #-}
139
140 isNotValidIx i = i < 0 || i >= pcount
141 {-# INLINE isNotValidIx #-}
142
143 pcount = totalPieces s
144 offset = fromIntegral pieceIndex * fromIntegral pieceLen
145
146-- | Read specific piece from storage.
147--
148-- This operation may throw 'StorageFailure'.
149--
150readPiece :: PieceIx -> Storage -> IO (Piece BL.ByteString)
151readPiece pix s @ Storage {..}
152 | not (isValidIx pix s) = throwIO (InvalidIndex pix)
153 | otherwise = Piece pix <$> readBytes offset sz fileMap
154 where
155 offset = fromIntegral pix * fromIntegral pieceLen
156 sz = fromIntegral pieceLen
157
158-- | Hint about the coming 'readPiece'. Ignores invalid indexes, for e.g.:
159--
160-- @forall s. hindRead (-1) s == return ()@
161--
162hintRead :: PieceIx -> Storage -> IO ()
163hintRead _pix Storage {..} = return ()
164
165-- | Zero-copy version of readPiece. Can be used only with 'ReadOnly'
166-- storages.
167unsafeReadPiece :: PieceIx -> Storage -> IO (Piece BL.ByteString)
168unsafeReadPiece pix s @ Storage {..}
169 | not (isValidIx pix s) = throwIO (InvalidIndex pix)
170 | otherwise = return $ Piece pix (unsafeReadBytes offset sz fileMap)
171 where
172 offset = fromIntegral pix * fromIntegral pieceLen
173 sz = fromIntegral pieceLen
174
175-- | Stream storage pieces from first to the last.
176sourceStorage :: Storage -> Source IO (Piece BL.ByteString)
177sourceStorage s = go 0
178 where
179 go pix
180 | pix < totalPieces s = do
181 piece <- liftIO $ readPiece pix s
182 liftIO $ hintRead (succ pix) s
183 yield piece
184 go (succ pix)
185 | otherwise = return ()
186
187-- | Write stream of pieces to the storage. Fail if storage is 'ReadOnly'.
188sinkStorage :: Storage -> Sink (Piece BL.ByteString) IO ()
189sinkStorage s = do
190 awaitForever $ \ piece ->
191 liftIO $ writePiece piece s
192
193-- | This function can be used to generate 'InfoDict' from a set of
194-- opened files.
195genPieceInfo :: Storage -> IO PieceInfo
196genPieceInfo s = do
197 hashes <- sourceStorage s $= C.map hashPiece $$ C.sinkLbs
198 return $ PieceInfo (pieceLen s) (HashList (BL.toStrict hashes))
199
200-- | Verify specific piece using infodict hash list.
201verifyPiece :: Storage -> PieceInfo -> PieceIx -> IO Bool
202verifyPiece s pinfo pix = do
203 piece <- unsafeReadPiece pix s
204 return $! checkPieceLazy pinfo piece
205
206-- | Verify storage.
207--
208-- Throws 'InvalidSize' if piece info size do not match with storage
209-- piece size.
210--
211getBitfield :: Storage -> PieceInfo -> IO Bitfield
212getBitfield s @ Storage {..} pinfo @ PieceInfo {..}
213 | pieceLen /= piPieceLength = throwIO (InvalidSize piPieceLength)
214 | otherwise = M.foldM checkPiece (BF.haveNone total) [0..total - 1]
215 where
216 total = totalPieces s
217
218 checkPiece :: Bitfield -> PieceIx -> IO Bitfield
219 checkPiece bf pix = do
220 valid <- verifyPiece s pinfo pix
221 return $ if valid then BF.insert pix bf else bf