summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-11-01 13:12:05 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-11-01 13:12:05 +0400
commit50f03abc7b4e05f38d64851ca8c6724b4fb0c4d1 (patch)
tree0a51f14b18f2b7123e04e01664291863111882b1
parent74f2cf6141d2a9aebe8bd5c7fdb5c116f38ef4a1 (diff)
Document Tree module
-rw-r--r--bittorrent.cabal2
-rw-r--r--src/Data/Torrent/InfoHash.hs9
-rw-r--r--src/Data/Torrent/Layout.hs2
-rw-r--r--src/Data/Torrent/Tree.hs30
4 files changed, 31 insertions, 12 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index 49f444e2..65e8208d 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -41,7 +41,7 @@ library
41 , RecordWildCards 41 , RecordWildCards
42 hs-source-dirs: src 42 hs-source-dirs: src
43 exposed-modules: Data.Torrent 43 exposed-modules: Data.Torrent
44 , Data.Torrent.Bitfield 44-- , Data.Torrent.Bitfield
45 , Data.Torrent.Block 45 , Data.Torrent.Block
46 , Data.Torrent.InfoHash 46 , Data.Torrent.InfoHash
47 , Data.Torrent.Layout 47 , Data.Torrent.Layout
diff --git a/src/Data/Torrent/InfoHash.hs b/src/Data/Torrent/InfoHash.hs
index 5ec429b5..ac13aa6c 100644
--- a/src/Data/Torrent/InfoHash.hs
+++ b/src/Data/Torrent/InfoHash.hs
@@ -1,3 +1,12 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- Infohash is a unique identifier of torrent.
9--
1{-# LANGUAGE FlexibleInstances #-} 10{-# LANGUAGE FlexibleInstances #-}
2{-# LANGUAGE GeneralizedNewtypeDeriving #-} 11{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3module Data.Torrent.InfoHash 12module Data.Torrent.InfoHash
diff --git a/src/Data/Torrent/Layout.hs b/src/Data/Torrent/Layout.hs
index 6f0668f2..ea8fa894 100644
--- a/src/Data/Torrent/Layout.hs
+++ b/src/Data/Torrent/Layout.hs
@@ -5,7 +5,7 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8-- 8-- Layout of files in torrent.
9-- 9--
10{-# LANGUAGE BangPatterns #-} 10{-# LANGUAGE BangPatterns #-}
11{-# LANGUAGE FlexibleInstances #-} 11{-# LANGUAGE FlexibleInstances #-}
diff --git a/src/Data/Torrent/Tree.hs b/src/Data/Torrent/Tree.hs
index 8c18041a..cf71c2ec 100644
--- a/src/Data/Torrent/Tree.hs
+++ b/src/Data/Torrent/Tree.hs
@@ -5,21 +5,25 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8-- Directory tree can be used to easily manipulate file layout info.
9--
8{-# LANGUAGE FlexibleInstances #-} 10{-# LANGUAGE FlexibleInstances #-}
9{-# LANGUAGE TemplateHaskell #-} 11{-# LANGUAGE TemplateHaskell #-}
10{-# LANGUAGE DeriveDataTypeable #-} 12{-# LANGUAGE DeriveDataTypeable #-}
11module Data.Torrent.Tree 13module Data.Torrent.Tree
12 ( DirTree (..) 14 ( -- * Directory tree
15 DirTree (..)
16
17 -- * Construction
13 , build 18 , build
14 19
20 -- * Query
15 , Data.Torrent.Tree.lookup 21 , Data.Torrent.Tree.lookup
16 , lookupDir 22 , lookupDir
17
18 , fileNumber 23 , fileNumber
19 , dirNumber 24 , dirNumber
20 ) where 25 ) where
21 26
22import Control.Arrow
23import Data.ByteString as BS 27import Data.ByteString as BS
24import Data.ByteString.Char8 as BC 28import Data.ByteString.Char8 as BC
25import Data.Foldable 29import Data.Foldable
@@ -30,10 +34,12 @@ import Data.Monoid
30import Data.Torrent.Layout 34import Data.Torrent.Layout
31 35
32 36
37-- | 'DirTree' is more convenient form of 'LayoutInfo'.
33data DirTree a = Dir { children :: Map ByteString (DirTree a) } 38data DirTree a = Dir { children :: Map ByteString (DirTree a) }
34 | File { node :: FileInfo a } 39 | File { node :: FileInfo a }
35 deriving Show 40 deriving Show
36 41
42-- | Build directory tree from a list of files.
37build :: LayoutInfo -> DirTree () 43build :: LayoutInfo -> DirTree ()
38build SingleFile {liFile = FileInfo {..}} = Dir 44build SingleFile {liFile = FileInfo {..}} = Dir
39 { children = M.singleton fiName (File fi) } 45 { children = M.singleton fiName (File fi) }
@@ -46,26 +52,30 @@ build MultiFile {..} = Dir $ M.singleton liDirName files
46 where 52 where
47 ent = File $ FileInfo fiLength fiMD5Sum () 53 ent = File $ FileInfo fiLength fiMD5Sum ()
48 54
49decompress :: DirTree () -> [FileInfo ()] 55--decompress :: DirTree () -> [FileInfo ()]
50decompress = undefined 56--decompress = undefined
51 57
58-- | Lookup file by path.
52lookup :: [FilePath] -> DirTree a -> Maybe (DirTree a) 59lookup :: [FilePath] -> DirTree a -> Maybe (DirTree a)
53lookup [] t = Just t 60lookup [] t = Just t
54lookup (p : ps) (Dir m) | Just subTree <- M.lookup (BC.pack p) m 61lookup (p : ps) (Dir m) | Just subTree <- M.lookup (BC.pack p) m
55 = Data.Torrent.Tree.lookup ps subTree 62 = Data.Torrent.Tree.lookup ps subTree
56lookup _ _ = Nothing 63lookup _ _ = Nothing
57 64
65-- | Lookup directory by path.
58lookupDir :: [FilePath] -> DirTree a -> Maybe [(ByteString, DirTree a)] 66lookupDir :: [FilePath] -> DirTree a -> Maybe [(ByteString, DirTree a)]
59lookupDir ps d 67lookupDir ps d = do
60 | Just subTree <- Data.Torrent.Tree.lookup ps d = 68 subTree <- Data.Torrent.Tree.lookup ps d
61 case subTree of 69 case subTree of
62 File _ -> Nothing 70 File _ -> Nothing
63 Dir es -> Just $ M.toList es 71 Dir es -> Just $ M.toList es
64 72
73-- | Get total count of files in directory and subdirectories.
65fileNumber :: DirTree a -> Sum Int 74fileNumber :: DirTree a -> Sum Int
66fileNumber File {..} = Sum 1 75fileNumber File {..} = Sum 1
67fileNumber Dir {..} = foldMap fileNumber children 76fileNumber Dir {..} = foldMap fileNumber children
68 77
78-- | Get total count of directories in the directory and subdirectories.
69dirNumber :: DirTree a -> Sum Int 79dirNumber :: DirTree a -> Sum Int
70dirNumber File {..} = Sum 0 80dirNumber File {..} = Sum 0
71dirNumber Dir {..} = Sum 1 <> foldMap dirNumber children 81dirNumber Dir {..} = Sum 1 <> foldMap dirNumber children