summaryrefslogtreecommitdiff
path: root/src/System
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2014-04-08 04:53:22 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2014-04-08 04:53:22 +0400
commit11fca56c179ce2da7d279293a6b3c7d1bb35c74c (patch)
tree1c58fba6451e3261828c4bba6a05dbc79cd28c56 /src/System
parent590990b3be7638d62076bb47c94aebfb3eb23c1a (diff)
Hide Tree.hs module
Diffstat (limited to 'src/System')
-rw-r--r--src/System/Torrent/Tree.hs83
1 files changed, 83 insertions, 0 deletions
diff --git a/src/System/Torrent/Tree.hs b/src/System/Torrent/Tree.hs
new file mode 100644
index 00000000..41cfb360
--- /dev/null
+++ b/src/System/Torrent/Tree.hs
@@ -0,0 +1,83 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- Directory tree can be used to easily manipulate file layout info.
9--
10{-# LANGUAGE FlexibleInstances #-}
11{-# LANGUAGE TemplateHaskell #-}
12{-# LANGUAGE DeriveDataTypeable #-}
13module System.Torrent.Tree
14 ( -- * Directory tree
15 DirTree (..)
16
17 -- * Construction
18 , build
19
20 -- * Query
21 , System.Torrent.Tree.lookup
22 , lookupDir
23 , fileNumber
24 , dirNumber
25 ) where
26
27import Data.ByteString as BS
28import Data.ByteString.Char8 as BC
29import Data.Foldable
30import Data.List as L
31import Data.Map as M
32import Data.Monoid
33
34import Data.Torrent
35
36
37-- | 'DirTree' is more convenient form of 'LayoutInfo'.
38data DirTree a = Dir { children :: Map ByteString (DirTree a) }
39 | File { node :: FileInfo a }
40 deriving Show
41
42-- | Build directory tree from a list of files.
43build :: LayoutInfo -> DirTree ()
44build SingleFile {liFile = FileInfo {..}} = Dir
45 { children = M.singleton fiName (File fi) }
46 where
47 fi = FileInfo fiLength fiMD5Sum ()
48build MultiFile {..} = Dir $ M.singleton liDirName files
49 where
50 files = Dir $ M.fromList $ L.map mkFileEntry liFiles
51 mkFileEntry FileInfo {..} = (L.head fiName, ent) -- TODO FIXME
52 where
53 ent = File $ FileInfo fiLength fiMD5Sum ()
54
55--decompress :: DirTree () -> [FileInfo ()]
56--decompress = undefined
57
58-- TODO pretty print
59
60-- | Lookup file by path.
61lookup :: [FilePath] -> DirTree a -> Maybe (DirTree a)
62lookup [] t = Just t
63lookup (p : ps) (Dir m) | Just subTree <- M.lookup (BC.pack p) m
64 = System.Torrent.Tree.lookup ps subTree
65lookup _ _ = Nothing
66
67-- | Lookup directory by path.
68lookupDir :: [FilePath] -> DirTree a -> Maybe [(ByteString, DirTree a)]
69lookupDir ps d = do
70 subTree <- System.Torrent.Tree.lookup ps d
71 case subTree of
72 File _ -> Nothing
73 Dir es -> Just $ M.toList es
74
75-- | Get total count of files in directory and subdirectories.
76fileNumber :: DirTree a -> Sum Int
77fileNumber File {..} = Sum 1
78fileNumber Dir {..} = foldMap fileNumber children
79
80-- | Get total count of directories in the directory and subdirectories.
81dirNumber :: DirTree a -> Sum Int
82dirNumber File {..} = Sum 0
83dirNumber Dir {..} = Sum 1 <> foldMap dirNumber children