diff options
author | Sam Truzjan <pxqr.sta@gmail.com> | 2013-12-03 16:15:32 +0400 |
---|---|---|
committer | Sam Truzjan <pxqr.sta@gmail.com> | 2013-12-03 16:15:32 +0400 |
commit | d6a0442a56d7b977d5f1d1d162517c9086c413eb (patch) | |
tree | 83a1de6acdd77c7bc1ae60c7418a6f43927251c6 /src/System/Torrent/FileMap.hs | |
parent | 5570963d8b22713d4f6ed9c0e2c7f686d5bc75da (diff) |
New storage
Diffstat (limited to 'src/System/Torrent/FileMap.hs')
-rw-r--r-- | src/System/Torrent/FileMap.hs | 151 |
1 files changed, 151 insertions, 0 deletions
diff --git a/src/System/Torrent/FileMap.hs b/src/System/Torrent/FileMap.hs new file mode 100644 index 00000000..80907a30 --- /dev/null +++ b/src/System/Torrent/FileMap.hs | |||
@@ -0,0 +1,151 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | ||
2 | {-# LANGUAGE ViewPatterns #-} | ||
3 | {-# OPTIONS -fno-warn-orphans #-} | ||
4 | module System.Torrent.FileMap | ||
5 | ( FileMap | ||
6 | |||
7 | -- * Construction | ||
8 | , Mode (..) | ||
9 | , def | ||
10 | , mmapFiles | ||
11 | , unmapFiles | ||
12 | |||
13 | -- * Query | ||
14 | , System.Torrent.FileMap.size | ||
15 | |||
16 | -- * Modification | ||
17 | , readBytes | ||
18 | , writeBytes | ||
19 | , unsafeReadBytes | ||
20 | |||
21 | -- * Unsafe conversions | ||
22 | , fromLazyByteString | ||
23 | , toLazyByteString | ||
24 | ) where | ||
25 | |||
26 | import Control.Applicative | ||
27 | import Control.Monad as L | ||
28 | import Data.ByteString as BS | ||
29 | import Data.ByteString.Internal as BS | ||
30 | import Data.ByteString.Lazy as BL | ||
31 | import Data.ByteString.Lazy.Internal as BL | ||
32 | import Data.Default | ||
33 | import Data.Vector as V -- TODO use unboxed vector | ||
34 | import Foreign | ||
35 | import System.IO.MMap | ||
36 | |||
37 | import Data.Torrent.Layout | ||
38 | |||
39 | |||
40 | data FileEntry = FileEntry | ||
41 | { filePosition :: {-# UNPACK #-} !FileOffset | ||
42 | , fileBytes :: {-# UNPACK #-} !BS.ByteString | ||
43 | } deriving (Show, Eq) | ||
44 | |||
45 | type FileMap = Vector FileEntry | ||
46 | |||
47 | instance Default Mode where | ||
48 | def = ReadWriteEx | ||
49 | |||
50 | mmapFiles :: Mode -> FileLayout FileSize -> IO FileMap | ||
51 | mmapFiles mode layout = V.fromList <$> L.mapM mkEntry (accumPositions layout) | ||
52 | where | ||
53 | mkEntry (path, (pos, expectedSize)) = do | ||
54 | let esize = fromIntegral expectedSize -- FIXME does this safe? | ||
55 | (fptr, moff, msize) <- mmapFileForeignPtr path mode $ Just (0, esize) | ||
56 | if msize /= esize | ||
57 | then error "mmapFiles" -- TODO unmap mapped files on exception | ||
58 | else return $ FileEntry pos (PS fptr moff msize) | ||
59 | |||
60 | unmapFiles :: FileMap -> IO () | ||
61 | unmapFiles = V.mapM_ unmapEntry | ||
62 | where | ||
63 | unmapEntry (FileEntry _ (PS fptr _ _)) = finalizeForeignPtr fptr | ||
64 | |||
65 | fromLazyByteString :: BL.ByteString -> FileMap | ||
66 | fromLazyByteString lbs = V.unfoldr f (0, lbs) | ||
67 | where | ||
68 | f (_, Empty ) = Nothing | ||
69 | f (pos, Chunk x xs) = Just (FileEntry pos x, ((pos + chunkSize), xs)) | ||
70 | where chunkSize = fromIntegral $ BS.length x | ||
71 | |||
72 | -- | /O(n)/. | ||
73 | toLazyByteString :: FileMap -> BL.ByteString | ||
74 | toLazyByteString = V.foldr f Empty | ||
75 | where | ||
76 | f FileEntry {..} bs = Chunk fileBytes bs | ||
77 | |||
78 | -- | /O(1)/. | ||
79 | size :: FileMap -> FileOffset | ||
80 | size m | ||
81 | | V.null m = 0 | ||
82 | | FileEntry {..} <- V.unsafeLast m | ||
83 | = filePosition + fromIntegral (BS.length fileBytes) | ||
84 | |||
85 | bsearch :: FileOffset -> FileMap -> Maybe Int | ||
86 | bsearch x m | ||
87 | | V.null m = Nothing | ||
88 | | otherwise = branch (V.length m `div` 2) | ||
89 | where | ||
90 | branch c @ ((m !) -> FileEntry {..}) | ||
91 | | x < filePosition = bsearch x (V.take c m) | ||
92 | | x >= filePosition + fileSize = do | ||
93 | ix <- bsearch x (V.drop (succ c) m) | ||
94 | return $ succ c + ix | ||
95 | | otherwise = Just c | ||
96 | where | ||
97 | fileSize = fromIntegral (BS.length fileBytes) | ||
98 | |||
99 | -- | /O(log n)/. | ||
100 | drop :: FileOffset -> FileMap -> (FileSize, FileMap) | ||
101 | drop off m | ||
102 | | Just ix <- bsearch off m | ||
103 | , FileEntry {..} <- m ! ix = (off - filePosition, V.drop ix m) | ||
104 | | otherwise = (0 , V.empty) | ||
105 | |||
106 | -- | /O(log n)/. | ||
107 | take :: FileSize -> FileMap -> (FileMap, FileSize) | ||
108 | take len m | ||
109 | | len >= s = (m , 0) | ||
110 | | Just ix <- bsearch (pred len) m = let m' = V.take (succ ix) m | ||
111 | in (m', System.Torrent.FileMap.size m' - len) | ||
112 | | otherwise = (V.empty , 0) | ||
113 | where | ||
114 | s = System.Torrent.FileMap.size m | ||
115 | |||
116 | -- | /O(log n + m)/. Do not use this function with 'unmapFiles'. | ||
117 | unsafeReadBytes :: FileOffset -> FileSize -> FileMap -> BL.ByteString | ||
118 | unsafeReadBytes off s m | ||
119 | | (l , m') <- System.Torrent.FileMap.drop off m | ||
120 | , (m'', _ ) <- System.Torrent.FileMap.take (off + s) m' | ||
121 | = BL.take (fromIntegral s) $ BL.drop (fromIntegral l) $ toLazyByteString m'' | ||
122 | |||
123 | readBytes :: FileOffset -> FileSize -> FileMap -> IO BL.ByteString | ||
124 | readBytes off s m = do | ||
125 | let bs_copy = BL.copy $ unsafeReadBytes off s m | ||
126 | forceLBS bs_copy | ||
127 | return bs_copy | ||
128 | where | ||
129 | forceLBS Empty = return () | ||
130 | forceLBS (Chunk _ x) = forceLBS x | ||
131 | |||
132 | bscpy :: BL.ByteString -> BL.ByteString -> IO () | ||
133 | bscpy (PS _ _ 0 `Chunk` dest_rest) src = bscpy dest_rest src | ||
134 | bscpy dest (PS _ _ 0 `Chunk` src_rest) = bscpy dest src_rest | ||
135 | bscpy (PS dest_fptr dest_off dest_size `Chunk` dest_rest) | ||
136 | (PS src_fptr src_off src_size `Chunk` src_rest) | ||
137 | = do let csize = min dest_size src_size | ||
138 | withForeignPtr dest_fptr $ \dest_ptr -> | ||
139 | withForeignPtr src_fptr $ \src_ptr -> | ||
140 | memcpy (dest_ptr `advancePtr` dest_off) | ||
141 | (src_ptr `advancePtr` src_off) | ||
142 | (fromIntegral csize) -- TODO memmove? | ||
143 | bscpy (PS dest_fptr (dest_off + csize) (dest_size - csize) `Chunk` dest_rest) | ||
144 | (PS src_fptr (src_off + csize) (src_size - csize) `Chunk` src_rest) | ||
145 | bscpy _ _ = return () | ||
146 | |||
147 | writeBytes :: FileOffset -> BL.ByteString -> FileMap -> IO () | ||
148 | writeBytes off lbs m = bscpy dest src | ||
149 | where | ||
150 | src = BL.take (fromIntegral (BL.length dest)) lbs | ||
151 | dest = unsafeReadBytes off (fromIntegral (BL.length lbs)) m \ No newline at end of file | ||