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