summaryrefslogtreecommitdiff
path: root/src/Data/Torrent/Layout.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Torrent/Layout.hs')
-rw-r--r--src/Data/Torrent/Layout.hs321
1 files changed, 0 insertions, 321 deletions
diff --git a/src/Data/Torrent/Layout.hs b/src/Data/Torrent/Layout.hs
deleted file mode 100644
index cc529840..00000000
--- a/src/Data/Torrent/Layout.hs
+++ /dev/null
@@ -1,321 +0,0 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- Layout of files in torrent.
9--
10{-# LANGUAGE BangPatterns #-}
11{-# LANGUAGE FlexibleInstances #-}
12{-# LANGUAGE StandaloneDeriving #-}
13{-# LANGUAGE GeneralizedNewtypeDeriving #-}
14{-# LANGUAGE DeriveDataTypeable #-}
15{-# LANGUAGE DeriveFunctor #-}
16{-# LANGUAGE DeriveFoldable #-}
17{-# LANGUAGE DeriveTraversable #-}
18{-# LANGUAGE TemplateHaskell #-}
19{-# OPTIONS -fno-warn-orphans #-}
20module Data.Torrent.Layout
21 ( -- * File attributes
22 FileOffset
23 , FileSize
24
25 -- * Single file info
26 , FileInfo (..)
27
28 -- ** Lens
29 , fileLength
30 , filePath
31 , fileMD5Sum
32
33 -- * File layout
34 , LayoutInfo (..)
35 , joinFilePath
36
37 -- ** Lens
38 , singleFile
39 , multiFile
40 , rootDirName
41
42 -- ** Predicates
43 , isSingleFile
44 , isMultiFile
45
46 -- ** Query
47 , suggestedName
48 , contentLength
49 , fileCount
50 , blockCount
51
52 -- * Flat file layout
53 , FileLayout
54 , flatLayout
55 , accumPositions
56 , fileOffset
57
58 -- * Internal
59 , sizeInBase
60 , getLayoutInfo
61 , putLayoutInfo
62 ) where
63
64import Control.Applicative
65import Control.DeepSeq
66import Control.Lens
67import Data.BEncode
68import Data.BEncode.Types
69import Data.ByteString as BS
70import Data.ByteString.Base16 as Base16
71import Data.ByteString.Char8 as BC
72import Data.Default
73import Data.Foldable as F
74import Data.List as L
75import Data.Text as T
76import Data.Text.Encoding as T
77import Data.Typeable
78import Text.PrettyPrint as PP
79import Text.PrettyPrint.Class
80import System.FilePath
81import System.Posix.Types
82
83{-----------------------------------------------------------------------
84-- File attribytes
85-----------------------------------------------------------------------}
86
87-- | Size of a file in bytes.
88type FileSize = FileOffset
89
90deriving instance BEncode FileOffset
91
92{-----------------------------------------------------------------------
93-- File info both either from info dict or file list
94-----------------------------------------------------------------------}
95
96-- | Contain metainfo about one single file.
97data FileInfo a = FileInfo {
98 fiLength :: {-# UNPACK #-} !FileSize
99 -- ^ Length of the file in bytes.
100
101 -- TODO unpacked MD5 sum
102 , fiMD5Sum :: !(Maybe ByteString)
103 -- ^ 32 character long MD5 sum of the file. Used by third-party
104 -- tools, not by bittorrent protocol itself.
105
106 , fiName :: !a
107 -- ^ One or more string elements that together represent the
108 -- path and filename. Each element in the list corresponds to
109 -- either a directory name or (in the case of the last element)
110 -- the filename. For example, the file:
111 --
112 -- > "dir1/dir2/file.ext"
113 --
114 -- would consist of three string elements:
115 --
116 -- > ["dir1", "dir2", "file.ext"]
117 --
118 } deriving (Show, Read, Eq, Typeable
119 , Functor, Foldable
120 )
121
122makeLensesFor
123 [ ("fiLength", "fileLength")
124 , ("fiMD5Sum", "fileMD5Sum")
125 , ("fiName" , "filePath" )
126 ]
127 ''FileInfo
128
129instance NFData a => NFData (FileInfo a) where
130 rnf FileInfo {..} = rnf fiName
131 {-# INLINE rnf #-}
132
133instance BEncode (FileInfo [ByteString]) where
134 toBEncode FileInfo {..} = toDict $
135 "length" .=! fiLength
136 .: "md5sum" .=? fiMD5Sum
137 .: "path" .=! fiName
138 .: endDict
139 {-# INLINE toBEncode #-}
140
141 fromBEncode = fromDict $ do
142 FileInfo <$>! "length"
143 <*>? "md5sum"
144 <*>! "path"
145 {-# INLINE fromBEncode #-}
146
147type Put a = a -> BDict -> BDict
148
149putFileInfoSingle :: Put (FileInfo ByteString)
150putFileInfoSingle FileInfo {..} cont =
151 "length" .=! fiLength
152 .: "md5sum" .=? fiMD5Sum
153 .: "name" .=! fiName
154 .: cont
155
156getFileInfoSingle :: Get (FileInfo ByteString)
157getFileInfoSingle = do
158 FileInfo <$>! "length"
159 <*>? "md5sum"
160 <*>! "name"
161
162instance BEncode (FileInfo ByteString) where
163 toBEncode = toDict . (`putFileInfoSingle` endDict)
164 {-# INLINE toBEncode #-}
165
166 fromBEncode = fromDict getFileInfoSingle
167 {-# INLINE fromBEncode #-}
168
169instance Pretty (FileInfo BS.ByteString) where
170 pretty FileInfo {..} =
171 "Path: " <> text (T.unpack (T.decodeUtf8 fiName))
172 $$ "Size: " <> text (show fiLength)
173 $$ maybe PP.empty ppMD5 fiMD5Sum
174 where
175 ppMD5 md5 = "MD5 : " <> text (show (Base16.encode md5))
176
177-- | Join file path.
178joinFilePath :: FileInfo [ByteString] -> FileInfo ByteString
179joinFilePath = fmap (BS.intercalate "/")
180
181{-----------------------------------------------------------------------
182-- Original torrent file layout info
183-----------------------------------------------------------------------}
184
185-- | Original (found in torrent file) layout info is either:
186--
187-- * Single file with its /name/.
188--
189-- * Multiple files with its relative file /paths/.
190--
191data LayoutInfo
192 = SingleFile
193 { -- | Single file info.
194 liFile :: !(FileInfo ByteString)
195 }
196 | MultiFile
197 { -- | List of the all files that torrent contains.
198 liFiles :: ![FileInfo [ByteString]]
199
200 -- | The /suggested/ name of the root directory in which to
201 -- store all the files.
202 , liDirName :: !ByteString
203 } deriving (Show, Read, Eq, Typeable)
204
205makeLensesFor
206 [ ("liFile" , "singleFile" )
207 , ("liFiles" , "multiFile" )
208 , ("liDirName", "rootDirName")
209 ]
210 ''LayoutInfo
211
212instance NFData LayoutInfo where
213 rnf SingleFile {..} = ()
214 rnf MultiFile {..} = rnf liFiles
215
216-- | Empty multifile layout.
217instance Default LayoutInfo where
218 def = MultiFile [] ""
219
220getLayoutInfo :: Get LayoutInfo
221getLayoutInfo = single <|> multi
222 where
223 single = SingleFile <$> getFileInfoSingle
224 multi = MultiFile <$>! "files" <*>! "name"
225
226putLayoutInfo :: Put LayoutInfo
227putLayoutInfo SingleFile {..} = putFileInfoSingle liFile
228putLayoutInfo MultiFile {..} = \ cont ->
229 "files" .=! liFiles
230 .: "name" .=! liDirName
231 .: cont
232
233instance BEncode LayoutInfo where
234 toBEncode = toDict . (`putLayoutInfo` endDict)
235 fromBEncode = fromDict getLayoutInfo
236
237instance Pretty LayoutInfo where
238 pretty SingleFile {..} = pretty liFile
239 pretty MultiFile {..} = vcat $ L.map (pretty . joinFilePath) liFiles
240
241-- | Test if this is single file torrent.
242isSingleFile :: LayoutInfo -> Bool
243isSingleFile SingleFile {} = True
244isSingleFile _ = False
245{-# INLINE isSingleFile #-}
246
247-- | Test if this is multifile torrent.
248isMultiFile :: LayoutInfo -> Bool
249isMultiFile MultiFile {} = True
250isMultiFile _ = False
251{-# INLINE isMultiFile #-}
252
253-- | Get name of the torrent based on the root path piece.
254suggestedName :: LayoutInfo -> ByteString
255suggestedName (SingleFile FileInfo {..}) = fiName
256suggestedName MultiFile {..} = liDirName
257{-# INLINE suggestedName #-}
258
259-- | Find sum of sizes of the all torrent files.
260contentLength :: LayoutInfo -> FileSize
261contentLength SingleFile { liFile = FileInfo {..} } = fiLength
262contentLength MultiFile { liFiles = tfs } = L.sum (L.map fiLength tfs)
263
264-- | Get number of all files in torrent.
265fileCount :: LayoutInfo -> Int
266fileCount SingleFile {..} = 1
267fileCount MultiFile {..} = L.length liFiles
268
269-- | Find number of blocks of the specified size. If torrent size is
270-- not a multiple of block size then the count is rounded up.
271blockCount :: Int -> LayoutInfo -> Int
272blockCount blkSize ci = contentLength ci `sizeInBase` blkSize
273
274{-----------------------------------------------------------------------
275-- Flat layout
276-----------------------------------------------------------------------}
277
278-- | File layout specifies the order and the size of each file in the
279-- storage. Note that order of files is highly important since we
280-- coalesce all the files in the given order to get the linear block
281-- address space.
282--
283type FileLayout a = [(FilePath, a)]
284
285-- | Extract files layout from torrent info with the given root path.
286flatLayout
287 :: FilePath -- ^ Root path for the all torrent files.
288 -> LayoutInfo -- ^ Torrent content information.
289 -> FileLayout FileSize -- ^ The all file paths prefixed with the given root.
290flatLayout prefixPath SingleFile { liFile = FileInfo {..} }
291 = [(prefixPath </> BC.unpack fiName, fiLength)]
292flatLayout prefixPath MultiFile {..} = L.map mkPath liFiles
293 where -- TODO use utf8 encoding in name
294 mkPath FileInfo {..} = (path, fiLength)
295 where
296 path = prefixPath </> BC.unpack liDirName
297 </> joinPath (L.map BC.unpack fiName)
298
299-- | Calculate offset of each file based on its length, incrementally.
300accumPositions :: FileLayout FileSize -> FileLayout (FileOffset, FileSize)
301accumPositions = go 0
302 where
303 go !_ [] = []
304 go !offset ((n, s) : xs) = (n, (offset, s)) : go (offset + s) xs
305
306-- | Gives global offset of a content file for a given full path.
307fileOffset :: FilePath -> FileLayout FileOffset -> Maybe FileOffset
308fileOffset = lookup
309{-# INLINE fileOffset #-}
310
311{-----------------------------------------------------------------------
312-- Internal utilities
313-----------------------------------------------------------------------}
314
315-- | Divide and round up.
316sizeInBase :: Integral a => a -> Int -> Int
317sizeInBase n b = fromIntegral (n `div` fromIntegral b) + align
318 where
319 align = if n `mod` fromIntegral b == 0 then 0 else 1
320{-# SPECIALIZE sizeInBase :: Int -> Int -> Int #-}
321{-# SPECIALIZE sizeInBase :: Integer -> Int -> Int #-}