-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathTree.hs
165 lines (137 loc) · 5.39 KB
/
Tree.hs
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
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
{-# OPTIONS -fno-warn-orphans #-}
--
-- Copyright (c) 2005-8 Don Stewart - http://www.cse.unsw.edu.au/~dons
-- Copyright (c) 2019-2020, 2025 Galen Huntington
--
-- This program is free software; you can redistribute it and/or
-- modify it under the terms of the GNU General Public License as
-- published by the Free Software Foundation; either version 2 of
-- the License, or (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program; if not, write to the Free Software
-- Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA
-- 02111-1307, USA.
--
--
-- functions for manipulating file trees
--
module Tree where
import Base
import FastIO
import qualified Data.ByteString.Char8 as P
import Data.Array
import System.IO (hPrint, stderr)
type FilePathP = ByteString
-- | A filesystem hierarchy is flattened to just the end nodes
type DirArray = Array Int Dir
-- | The complete list of .mp3 files
type FileArray = Array Int File
-- | A directory entry is the directory name, and a list of bound
-- indicies into the Files array.
data Dir =
Dir { dname :: !FilePathP -- ^ directory name
, dsize :: !Int -- ^ number of file entries
, dlo :: !Int -- ^ index of first entry
, dhi :: !Int } -- ^ index of last entry
-- Most data is allocated in this structure
data File =
File { fbase :: !FilePathP -- ^ basename of file
, fdir :: !Int } -- ^ index of Dir entry
data Tree = Tree !DirArray !FileArray
--
-- | Given the start directories, populate the dirs and files arrays
--
buildTree :: [FilePathP] -> IO Tree
buildTree fs = do
(os, dirs) <- partition fs -- note we will lose the ordering of files given on cmd line.
let loop [] = pure []
loop (a:xs) = do
(m, ds) <- expandDir a
ms <- loop $ ds ++ xs -- add to work list
pure $ m : ms
ms' <- catMaybes <$> loop dirs
let extras = merge . doOrphans $ os
ms = ms' ++ extras
let (_,n,dirls,filels) = foldl' make (0,0,[],[]) ms
dirsArray = listArray (0,length dirls - 1) (reverse dirls)
fileArray = listArray (0, n-1) (reverse filels)
pure $! Tree dirsArray fileArray
-- | Is the tree empty?
isEmpty :: Tree -> Bool
isEmpty (Tree _ files) = null files
-- | Create nodes based on dirname for orphan files on cmdline
doOrphans :: [FilePathP] -> [(FilePathP, [FilePathP])]
doOrphans = map \f -> (dirnameP f, [basenameP f])
-- | Merge entries with the same root node into a single node
merge :: [(FilePathP, [FilePathP])] -> [(FilePathP, [FilePathP])]
merge [] = []
merge xs =
let xs' = sortBy (\a b -> fst a `compare` fst b) xs
xs''= groupBy (\a b -> fst a == fst b) xs'
in mapMaybe flatten xs''
where
flatten :: [(FilePathP,[FilePathP])] -> Maybe (FilePathP, [FilePathP])
flatten [] = Nothing -- can't happen
flatten (x:ys) = let d = fst x in Just (d, snd x ++ concatMap snd ys)
-- | fold builder, for generating Dirs and Files
make :: (Int,Int,[Dir],[File]) -> (FilePathP,[FilePathP]) -> (Int,Int,[Dir],[File])
make (i,n,acc1,acc2) (d,fs) =
let (dir, n') = listToDir n d fs
fs'= map makeFile fs
in (i+1, n', dir:acc1, reverse fs' ++ acc2)
where
makeFile f = File (basenameP f) i
------------------------------------------------------------------------
-- | Expand a single directory into a maybe a pair of the dir name and any files
-- Return any extra directories to search in
--
-- Assumes no evil sym links
--
expandDir :: FilePathP -> IO (Maybe (FilePathP, [FilePathP]), [FilePathP])
expandDir !f = do
ls_raw <- handle @SomeException (\e -> hPrint stderr e $> [])
$ packedGetDirectoryContents f
let ls = (map \s -> P.intercalate (P.singleton '/') [f,s])
. sort . filter validFiles $ ls_raw
(fs',ds) <- partition ls
let fs = filter onlyMp3s fs'
v = if null fs then Nothing else Just (f,fs)
pure (v,ds)
where
notEdge p = p /= dot && p /= dotdot
validFiles p = notEdge p
onlyMp3s p = mp3 == (P.map toLower . P.drop (P.length p - 3) $ p)
mp3 = "mp3"
dot = "."
dotdot = ".."
--
-- | Given an the next index into the files array, a directory name, and
-- a list of files in that dir, build a Dir and return the next index
-- into the array
--
listToDir :: Int -> FilePathP -> [FilePathP] -> (Dir, Int)
listToDir n d fs =
let dir = Dir { dname = packedFileNameEndClean d
, dsize = len
, dlo = n
, dhi = n + len - 1
} in (dir, n')
where
len = length fs
n' = n + len
-- | break a list of file paths into a pair of sublists corresponding
-- to the paths that point to files and to directories.
partition :: [FilePathP] -> IO ([FilePathP], [FilePathP])
partition [] = pure ([],[])
partition (a:xs) = do
(fs,ds) <- partition xs
x <- doesFileExist a
if x then do y <- isReadable a
pure if y then (a:fs, ds) else (fs, ds)
else pure (fs, a:ds)