hcdu/app/Main.hs

194 lines
5.5 KiB
Haskell
Raw Normal View History

2023-10-16 09:07:50 +00:00
{-# LANGUAGE BlockArguments #-}
2023-10-12 13:01:36 +00:00
module Main where
2023-10-16 13:57:45 +00:00
import System.Posix.Directory ( getWorkingDirectory, changeWorkingDirectory )
2023-10-14 11:49:13 +00:00
import System.Directory ( pathIsSymbolicLink
, doesFileExist
, getFileSize
, doesDirectoryExist )
import Data.Functor ( (<&>) )
import Control.Monad ( filterM )
2023-10-16 13:57:45 +00:00
import Control.Monad.IO.Class
2023-10-14 11:49:13 +00:00
import System.Directory.Extra ( listContents )
2023-10-16 13:57:45 +00:00
import System.IO.Error
2023-10-14 11:49:13 +00:00
import Brick
2023-10-16 09:07:50 +00:00
import Brick.Widgets.Edit
2023-10-14 11:49:13 +00:00
import Graphics.Vty
import Data.List.Extra
import qualified Data.Ord
2023-10-16 09:07:50 +00:00
import Data.Maybe
2023-10-12 14:37:54 +00:00
2023-10-13 13:54:57 +00:00
listNonSymFiles :: FilePath -> IO [FilePath]
2023-10-16 09:07:50 +00:00
listNonSymFiles dir = filterM ((not <$>) . pathIsSymbolicLink) =<< filterM doesFileExist =<< listContents dir
2023-10-12 14:37:54 +00:00
2023-10-13 13:54:57 +00:00
listNonSymDirectories :: FilePath -> IO [FilePath]
2023-10-16 09:07:50 +00:00
listNonSymDirectories dir = filterM ((not <$>) . pathIsSymbolicLink) =<< filterM doesDirectoryExist =<< listContents dir
listSym :: FilePath -> IO [FilePath]
listSym dir = filterM pathIsSymbolicLink =<< listContents dir
2023-10-13 13:24:26 +00:00
2023-10-16 13:57:45 +00:00
handlePermissionError :: IOError -> IO Integer
handlePermissionError e = if isPermissionError e then pure 0 else ioError e
2023-10-13 13:54:57 +00:00
getSizeSubpaths :: FilePath -> IO [(FilePath, Integer)]
getSizeSubpaths x = do
sub <- listNonSymDirectories x
2023-10-16 13:57:45 +00:00
subby <- mapM
(\y -> (y,) . sum . map snd <$>
getSizeSubpaths y)
sub
2023-10-16 09:07:50 +00:00
syms <- listSym x
2023-10-16 13:57:45 +00:00
local <- listNonSymFiles x >>=
(\y -> mapM
(flip catchIOError handlePermissionError . getFileSize) y <&>
zip y)
2023-10-16 09:07:50 +00:00
pure $ sortOn (Data.Ord.Down . snd) $ local ++ subby ++ zip syms [0..0]
2023-10-14 11:35:22 +00:00
2023-10-16 13:57:45 +00:00
data ScrollDirection where
SUp :: ScrollDirection
SDown :: ScrollDirection
2023-10-14 11:35:22 +00:00
data AppS = AppS
{
2023-10-16 14:27:20 +00:00
appCWD :: FilePath
, appCursor :: Int
, appFocus :: Maybe FilePath
, appSubFiles :: [(FilePath, Integer)]
2023-10-14 11:35:22 +00:00
}
2023-10-16 09:07:50 +00:00
app :: App AppS e ()
2023-10-14 11:35:22 +00:00
app =
2023-10-16 09:07:50 +00:00
App { appDraw = pure . browse
2023-10-16 13:57:45 +00:00
, appHandleEvent = eventHandler
2023-10-14 11:35:22 +00:00
, appStartEvent = pure ()
2023-10-16 09:07:50 +00:00
, appAttrMap = attributeMap
, appChooseCursor = showFirstCursor
2023-10-14 11:35:22 +00:00
}
2023-10-16 09:07:50 +00:00
attributeMap :: AppS -> AttrMap
attributeMap = const $ attrMap defAttr
[ (attrName "selected", withStyle defAttr reverseVideo)
, (editAttr, fg brightBlack)
]
select :: Widget () -> Widget ()
select = withAttr (attrName "selected")
2023-10-16 16:47:09 +00:00
unitSize :: Integer -> String
unitSize s
2023-10-16 17:10:17 +00:00
| s3 >= 1 / 2 =
show (f s3) ++ " GB"
| s2 >= 1 / 2 =
show (f s2) ++ " MB"
| s1 >= 1 / 2 =
show (f s1) ++ " KB"
| otherwise =
show s ++ " B"
2023-10-16 16:47:09 +00:00
where k2 = 1024 :: Double
2023-10-16 17:10:17 +00:00
s3 = fromInteger s / (k2^(3 :: Int))
s2 = fromInteger s / (k2^(2 :: Int))
s1 = fromInteger s / (k2^(1 :: Int))
2023-10-16 16:47:09 +00:00
f :: Double -> Double
f q = fromInteger (truncate $ q * 100) / 100
2023-10-16 09:07:50 +00:00
browse :: AppS -> Widget ()
browse s =
str "Path" <+> padLeft Max (str "Size") <=>
2023-10-16 14:27:20 +00:00
viewport () Vertical (foldr (widgetCons s) emptyWidget (appSubFiles s))
2023-10-16 09:07:50 +00:00
widgetCons :: AppS -> (FilePath, Integer) -> Widget () -> Widget ()
2023-10-16 13:57:45 +00:00
widgetCons s w@(f,_) ws =
2023-10-16 14:27:20 +00:00
(<=> ws) if Just f == appFocus s then
2023-10-16 13:57:45 +00:00
select . visible $ pathWidget w else
pathWidget w
2023-10-16 09:07:50 +00:00
pathWidget :: (FilePath, Integer) -> Widget ()
2023-10-16 16:47:09 +00:00
pathWidget (f, s) = str (show f) <+> padLeft Max (str (unitSize s))
2023-10-16 09:07:50 +00:00
2023-10-14 11:35:22 +00:00
sizeDir :: AppS -> IO AppS
sizeDir s = do
2023-10-16 14:27:20 +00:00
subFiles <- getSizeSubpaths $ appCWD s
2023-10-16 14:14:18 +00:00
pure $
s {
2023-10-16 14:27:20 +00:00
appCursor = 0
, appFocus = map fst subFiles !? 0
, appSubFiles = subFiles
2023-10-16 14:14:18 +00:00
}
2023-10-14 11:35:22 +00:00
2023-10-16 09:07:50 +00:00
changeDir :: AppS -> IO AppS
changeDir so
2023-10-16 14:27:20 +00:00
| isJust $ appFocus so = do
2023-10-16 13:57:45 +00:00
allowed <- doesDirectoryExist path
if allowed then do
changeWorkingDirectory path
let s =
so {
2023-10-16 14:27:20 +00:00
appCWD = path
, appSubFiles = []
2023-10-16 13:57:45 +00:00
} in
sizeDir s else
pure so
2023-10-16 09:07:50 +00:00
| otherwise = pure so
2023-10-16 14:27:20 +00:00
where path = fromJust $ appFocus so
2023-10-16 13:57:45 +00:00
overDir :: IO AppS
overDir = do
changeWorkingDirectory ".."
a <- getWorkingDirectory
changeDir $ initialState a
2023-10-14 11:35:22 +00:00
scroll :: ScrollDirection -> AppS -> AppS
scroll d s = s {
2023-10-16 14:27:20 +00:00
appCursor = newCursor
, appFocus = maybeNewPath
2023-10-14 11:35:22 +00:00
}
where cursor =
2023-10-16 14:27:20 +00:00
appCursor s +
2023-10-14 11:35:22 +00:00
case d of
SUp -> (-1)
SDown -> 1
2023-10-16 14:27:20 +00:00
newCursor = max 0 (min (subtract 1 . length $ appSubFiles s) cursor)
maybeNewPath = fst <$> appSubFiles s !? newCursor
2023-10-14 11:35:22 +00:00
2023-10-16 13:57:45 +00:00
eventHandler :: BrickEvent () e -> EventM () AppS ()
eventHandler (VtyEvent (EvKey k _)) = do
s <- get
case k of
(KChar 'q') -> halt
KEsc -> halt
(KChar 'j') -> put $ scroll SDown s
KDown -> put $ scroll SDown s
2023-10-16 14:27:20 +00:00
(KChar 'k') -> put $ scroll SUp s
2023-10-16 13:57:45 +00:00
KUp -> put $ scroll SUp s
(KChar 'h') -> put =<< liftIO overDir
KLeft -> put =<< liftIO overDir
2023-10-16 09:07:50 +00:00
2023-10-16 13:57:45 +00:00
(KChar ' ') -> put =<< liftIO (changeDir s)
KEnter -> put =<< liftIO (changeDir s)
(KChar 'l') -> put =<< liftIO (changeDir s)
KRight -> put =<< liftIO (changeDir s)
_ -> continueWithoutRedraw
eventHandler _ = undefined
initialState :: FilePath -> AppS
initialState f =
AppS {
2023-10-16 14:27:20 +00:00
appCWD = f
, appCursor = 0
, appFocus = pure f
, appSubFiles = []
2023-10-16 13:57:45 +00:00
}
2023-10-12 14:37:54 +00:00
2023-10-12 13:01:36 +00:00
main :: IO ()
2023-10-12 14:37:54 +00:00
main = do
2023-10-13 13:24:26 +00:00
a <- getWorkingDirectory
2023-10-16 09:07:50 +00:00
b <- changeDir $ initialState a
_ <- defaultMain app b
return ()