summaryrefslogtreecommitdiff
path: root/src/System
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-06-20 21:25:57 +0400
committerSam T <pxqr.sta@gmail.com>2013-06-20 21:25:57 +0400
commite028ac4b464d73f6afee1727d68cedc4e3ed24d5 (patch)
treee93a7ef7898fed8928c24896175c7cafd46d6bb2 /src/System
parent3325e02fa3a75878ad6f5519d88396e2cbaa3887 (diff)
~ merge mmap-fixed package into bittorrent.
reason: mmap-fixed is pretty useless out of scope of bittorrent, at least i don't think that it'll be used some time that way. Moreover we can hide some internal stuff and simplify interface and simplify user code. Using mmap-fixed we can provide Storage datatype with all necessary operations needed to keep torrent content in memory of FS. Also that seems pretty annoying to merge this 2 repos into one using git merge(there are not so many stuff anyway), so I just did that manually. :<
Diffstat (limited to 'src/System')
-rw-r--r--src/System/IO/MMap/Fixed.hs203
1 files changed, 203 insertions, 0 deletions
diff --git a/src/System/IO/MMap/Fixed.hs b/src/System/IO/MMap/Fixed.hs
new file mode 100644
index 00000000..9d2e354f
--- /dev/null
+++ b/src/System/IO/MMap/Fixed.hs
@@ -0,0 +1,203 @@
1-- TODO pprint
2-- TODO see if this IntervalMap is overkill: Interval dataty have 4 constrs
3-- TODO clarify lifetime in docs
4-- TODO use madvise
5-- TODO unmap selected interval
6-- TODO tests
7-- TODO benchmarks
8-- TODO unmap overlapped regions
9-- [A] TODO lazy mapping for 32 bit arch;
10-- we need tricky algorithm and a lot of perf tests
11-- TODO use memmove in write bytes
12-- TODO write elem, write byte, read byte
13-- |
14-- Copyright : (c) Sam T. 2013
15-- License : MIT
16-- Maintainer : pxqr.sta@gmail.com
17-- Stability : experimental
18-- Portability : portable
19--
20-- This library provides mechanism to mmap files to fixed address
21-- with fine-grained control. Hovewer, instead of using MAP_FIXED we
22-- create our own address space upon virtual address space. If you
23-- would like you could call this space as "fixed address space".
24--
25-- This solves a few problems:
26--
27-- * Page already in use. If you mmap one file at 0..x addresses and
28-- want to map second file to x..y addresses using MAP_FIXED you
29-- can get in troubles: page might be mapped already. Raw call to
30-- mmap will silently unmap x..y addresses and then mmap our second
31-- file. So here we have extra unmap we would like to avoid.
32--
33-- * Page boundaries. If you mmap one file at x..x+1 you could
34-- not map next file to say addresses x+1..x+2.
35--
36-- Internally we make ordinary call to mmap to map a file and then
37-- using /interval map/ we map fixed address space to virtual
38-- address space. It takes TODO time in TODO cases.
39--
40-- Basically this library could be used when we need coalesce
41-- several files in arbitrary way. We could map at any position as
42-- long as offset + size fit in 'Int'.
43--
44-- For other details see:
45--
46-- > http://hackage.haskell.org/package/mmap
47-- > man mmap
48--
49module System.IO.MMap.Fixed
50 ( -- * Intervals
51 FixedOffset, FileOffset, FixedInterval, FileInterval
52 , interval, fileInterval
53
54 -- * Construction
55 , Fixed, Bytes
56 , System.IO.MMap.Fixed.empty, insertTo
57 , coalesceFiles
58
59 -- ** Specialized 'insertTo'
60 , mmapTo, mallocTo
61
62 -- * Query
63 , upperAddr
64
65 -- * Access
66 , viewBytes, readBytes, writeBytes
67 , readElem, writeElem
68 ) where
69
70import Data.ByteString.Lazy as Lazy
71import Data.ByteString.Lazy.Internal as Lazy
72import Data.ByteString.Internal as B
73import Data.List as L
74import Data.Int
75import Data.IntervalMap.Strict as M
76import Data.IntervalMap.Interval
77import System.IO.MMap
78import Foreign
79
80
81type FixedOffset = Int
82type FileOffset = Int64
83type Size = Int
84
85
86type FileInterval = (FileOffset, Size)
87type FixedInterval = Interval FixedOffset
88
89
90interval :: FixedOffset -> Size -> FixedInterval
91interval off s = IntervalCO off (off + fromIntegral (max 0 s))
92{-# INLINE interval #-}
93
94fileInterval :: FileOffset -> Size -> FileInterval
95fileInterval off s = (off, s)
96{-# INLINE fileInterval #-}
97
98intervalSize :: FixedInterval -> Size
99intervalSize i = upperBound i - lowerBound i
100{-# INLINE intervalSize #-}
101
102
103type Bytes = (ForeignPtr Word8, Size)
104
105type FixedMap = IntervalMap FixedOffset Bytes
106
107newtype Fixed = Fixed { imap :: FixedMap }
108
109instance Show Fixed where
110 show = show . M.toList . imap
111
112
113mapIM :: (FixedMap -> FixedMap) -> Fixed -> Fixed
114mapIM f s = s { imap = f (imap s) }
115
116empty :: Fixed
117empty = Fixed M.empty
118
119coalesceFiles :: [(FilePath, Int)] -> IO Fixed
120coalesceFiles = go 0 System.IO.MMap.Fixed.empty
121 where
122 go _ s [] = return s
123 go offset s ((path, bsize) : xs) = do
124 s' <- mmapTo path (0, bsize) offset s
125 go (offset + bsize) s' xs
126
127upperAddr :: Fixed -> FixedOffset
128upperAddr = upperBound . fst . findLast . imap
129
130insertTo :: FixedInterval -> Bytes -> Fixed -> Fixed
131insertTo fi mm = mapIM (M.insert fi mm)
132{-# INLINE insertTo #-}
133
134mmapTo :: FilePath -> FileInterval -> FixedOffset -> Fixed -> IO Fixed
135mmapTo path mrange to s = do
136 (fptr, offset, fsize) <- mmapFileForeignPtr path ReadWriteEx (Just mrange)
137
138 let fixed = interval to fsize
139 let mmaped = (fptr, offset)
140
141 return $ insertTo fixed mmaped s
142
143mallocTo :: FixedInterval -> Fixed -> IO Fixed
144mallocTo fi s = do
145 let bsize = intervalSize fi
146 fptr <- mallocForeignPtrBytes bsize
147 return (insertTo fi (fptr, 0) s)
148
149-- | Note: this is unsafe operation.
150viewBytes :: FixedInterval -> Fixed -> Lazy.ByteString
151viewBytes fi s = fromChunks $ L.map mk $ (imap s `intersecting` fi)
152 where
153 mk (i, (fptr, offset)) =
154 let dropB = max 0 (lowerBound fi - lowerBound i)
155 dropT = max 0 (upperBound i - upperBound fi)
156 bsize = intervalSize i - (dropT + dropB)
157 in fromForeignPtr fptr (offset + dropB) bsize
158
159
160readBytes :: FixedInterval -> Fixed -> IO Lazy.ByteString
161readBytes fi s = let c = Lazy.copy (viewBytes fi s) in mkCopy c >> return c
162{-# INLINE readBytes #-}
163
164writeBytes :: FixedInterval -> Lazy.ByteString -> Fixed -> IO ()
165writeBytes fi bs s = bscpy (viewBytes fi s) bs
166{-# INLINE writeBytes #-}
167
168-- | Note: this operation takes O(log(files count)) time, if possible
169-- use readBytes.
170readElem :: Storable a => Fixed -> FixedOffset -> IO a
171readElem s offset = go undefined
172 where
173 go :: Storable a => a -> IO a
174 go dont_touch = do
175 let bsize = sizeOf dont_touch
176 let PS fptr off _ = Lazy.toStrict (viewBytes (interval offset bsize) s)
177 withForeignPtr fptr $ \ ptr -> peekByteOff ptr off
178
179writeElem :: Storable a => Fixed -> FixedOffset -> a -> IO ()
180writeElem s offset x = do
181 let bsize = sizeOf x
182 let PS fptr off _ = Lazy.toStrict (viewBytes (interval offset bsize) s)
183 withForeignPtr fptr $ \ptr -> pokeByteOff ptr off x
184
185
186mkCopy :: Lazy.ByteString -> IO ()
187mkCopy Empty = return ()
188mkCopy (Chunk _ x) = mkCopy x
189
190bscpy :: Lazy.ByteString -> Lazy.ByteString -> IO ()
191bscpy (PS _ _ 0 `Chunk` dest_rest) src = bscpy dest_rest src
192bscpy dest (PS _ _ 0 `Chunk` src_rest) = bscpy dest src_rest
193bscpy (PS dest_fptr dest_off dest_size `Chunk` dest_rest)
194 (PS src_fptr src_off src_size `Chunk` src_rest)
195 = do let csize = min dest_size src_size
196 withForeignPtr dest_fptr $ \dest_ptr ->
197 withForeignPtr src_fptr $ \src_ptr ->
198 memcpy (dest_ptr `advancePtr` dest_off)
199 (src_ptr `advancePtr` src_off)
200 (fromIntegral csize) -- TODO memmove?
201 bscpy (PS dest_fptr (dest_off + csize) (dest_size - csize) `Chunk` dest_rest)
202 (PS src_fptr (src_off + csize) (src_size - csize) `Chunk` src_rest)
203bscpy _ _ = return () \ No newline at end of file