首页
学习
活动
专区
圈层
工具
发布
首页
学习
活动
专区
圈层
工具
MCP广场
社区首页 >问答首页 >命令行工具,列出本地驱动器上的视频文件

命令行工具,列出本地驱动器上的视频文件
EN

Code Review用户
提问于 2018-08-05 20:20:12
回答 2查看 120关注 0票数 6

解释

大约一个月前我开始学习Haskell。作为练习,我重新创建了一个小的命令行工具,这是我以前用PowerShell编写的。在当前状态下,它在特定目录及其子目录中显示视频列表。稍后,我将添加播放或删除这些视频的功能(这应该很容易)。但最重要的是显示列表。目前,这些代码就是这么做的。

到目前为止,我非常喜欢Haskell,但我对这段代码的冗长和复杂感到不快。它是100行,似乎很难读。PowerShell脚本只有70行(完整的回放和删除视频),文字较少,很容易阅读。

这主要是因为我缺乏知识,如何编写好的Haskell代码?还是Haskell不是完成这类任务的好工具?

特别困扰我的是:

  • 我有所有这些小功能,它们执行一项特定的任务,并相互调用以实现最终目标。如果一个人对代码不熟悉,就很难阅读它。因为函数没有在一个明显的控制结构中连接,所以我们必须分析每个函数,看看它调用了什么其他函数,等等,直到图片完成为止。将其与命令式语言进行比较:有一些易于阅读的if语句和一些大型代码块。一目了然,人们就可以看到在哪里做了什么,如果感兴趣的话,就可以更多地了解实现的细节。很容易对程序的总体结构有一种感觉。
  • getRecursiveContents (我从互联网上复制了这个)。它又大又复杂。递归获取文件是一项日常任务--真的没有这样的库函数吗?
  • 很好,我可以描述一个定制类型在打印时应该如何Show本身。但是因为我处理的是列表,所以我不得不unlines $ map show它,这不是很漂亮。

目录结构

代码语言:javascript
运行
复制
└───Videos
    │   Heat.1995.1080p.BRrip.x264.YIFY.mp4
    │   heat.png
    │   leon.png
    │   Leon.the.Professional.Extended.1994.BrRip.x264.YIFY.mp4
    │   mononoke hime.png
    │   Mononoke.hime.[Princess.Mononoke].[DUAL.AUDIO]1997.HDTVRip.x264.YIFY.mkv
    │   Oblivion.2013.1080p.BluRay.x264.YIFY.mp4
    │   oblivion.png
    │   terminator 2.png
    │   Terminator.2.Judgment.Day.1991.DC.1080p.BRrip.x264.GAZ.YIFY.mp4
    │   traffic.png
    │
    └───Series
            S01E01.Some.Show.mp4
            S01E02.Some.Show.mp4
            S01E03.Some.Show.mp4

输出

代码语言:javascript
运行
复制
     Videos
  1  Heat.1995.1080p.BRrip.x264.YIFY
  2  Leon.the.Professional.Extended.1994.BrRip.x264.YIFY
  3  Mononoke.hime.[Princess.Mononoke].[DUAL.AUDIO]1997.HDTVRip.x264.YIFY
  4  Oblivion.2013.1080p.BluRay.x264.YIFY
  5  Terminator.2.Judgment.Day.1991.DC.1080p.BRrip.x264.GAZ.YIFY

     Series
  6  S01E01.Some.Show
  7  S01E02.Some.Show
  8  S01E03.Some.Show

代码语言:javascript
运行
复制
module Main where

import Control.Monad (forM)
import Data.Char (toLower)
import Data.List (isInfixOf, nub, sort, sortBy)
import Data.List.Split (splitOn)
import System.Directory (doesDirectoryExist, listDirectory)
import System.FilePath (takeBaseName, takeDirectory, takeExtension, ())
import Text.Printf (printf)


videoDirectory = "C:\\Users\\Swonkie\\Downloads\\Videos"
videoExtensions = [".mp4", ".mkv", ".avi", ".m4v"]

-- ANSI / VT color codes
color = "\ESC[1;31m"
reset = "\ESC[m"

type Library = [Directory]

data Directory = Directory { name  :: String
                           , files :: [Video]
                           }
instance Show Directory where
    show (Directory name files) = "     " ++ color ++ name ++ reset ++ "\n" ++ (unlines $ map show files)

data Video = Video { index  :: Integer
                   , path   :: FilePath
                   }
instance Show Video where
    show (Video i path) = printf "%3d  %s" i (takeBaseName path)


isVideoFile :: FilePath -> Bool
isVideoFile path = takeExtension path `elem` videoExtensions

-- | not used yet
getVideoByIndex :: [Video] -> Integer -> Maybe Video
getVideoByIndex files i =
    if length v > 0
        then Just (head v)
        else Nothing
    where v = filter (\ v -> index v == i) files

-- | not used yet
getVideoByName :: [Video] -> String -> Maybe Video
getVideoByName files s =
    if length v > 0
        then Just (head v)
        else Nothing
    where v = filter (\ v -> isInfixOf (map toLower s) (map toLower $ takeBaseName $ path v)) files


-- | The name of the folder containing the file, without its parent folders.
bottomFolder :: FilePath -> String
bottomFolder path = last $ splitOn "\\" $ takeDirectory path

-- | A list of all unique directory names which appear in the list of videos.
getDirectories :: [Video] -> [String]
getDirectories videos = nub $ map (bottomFolder . path) videos

-- | Filters the list of videos down to only those which are in a specific directory.
getVideosInDirectory :: [Video] -> String -> [Video]
getVideosInDirectory videos name = filter (\ v -> (bottomFolder $ path v) == name) videos

-- | Bundles the videos in a specific directory in a Directory type.
getDirectory :: [Video] -> String -> Directory
getDirectory videos name = Directory name (getVideosInDirectory videos name)

-- | Creates Video objects with indexes
getVideos :: [FilePath] -> [Video]
getVideos list = [Video (fst tp) (snd tp) | tp <- zip [1..] list]

-- | Gets all the directories of the videos and creates a list of Directory types.
getLibrary :: [Video] -> Library
getLibrary videos = map (getDirectory videos) $ getDirectories videos

getRecursiveContents :: FilePath -> IO [FilePath]
getRecursiveContents topdir = do
    names <- listDirectory topdir
    paths <- forM names $ \ name -> do
        let path = topdir  name
        isDirectory <- doesDirectoryExist path
        if isDirectory
            then getRecursiveContents path
            else return [path]
    return (concat paths)

main :: IO ()
main = do
    -- get all video files recursively
    files <- getRecursiveContents videoDirectory    
    let videoFiles = sort $ filter isVideoFile files

    -- adding a character to the end of the path is a hack, to have subdirs sorted below parent dirs
    -- apparently "end of string" is last in the sort order, not first (weird)
    let sortedByDirectory = sortBy (\ a b -> compare (takeDirectory a ++ "$") (takeDirectory b ++ "$")) videoFiles
    let lib = getLibrary $ getVideos sortedByDirectory

    -- show the list of videos
    putStrLn ""
    putStr $ unlines $ map show lib
EN

回答 2

Code Review用户

回答已采纳

发布于 2018-08-06 08:37:20

欢迎来到Haskell编程世界。系好安全带,这将是一段旅程。

案例研究:getVideoBy*

您的函数getVideoByIndexgetVideoByName为改进提供了一个很好的案例研究。目前,这两个功能看起来非常相似。这就引出了我们的第一个原则。

,不要重复,

这两个函数的工作原理相同,我们在结果列表中应用了filter,然后应用了head。我们可以将该函数提取为一个单独的函数:

代码语言:javascript
运行
复制
find :: (a -> Bool) -> [a] -> Maybe a
find p xs = 
    if length v > 0 
        then Just (head v)
        else Nothing
    where v = filter p xs

-- | not used yet
getVideoByIndex :: [Video] -> Integer -> Maybe Video
getVideoByIndex files i = find (\v -> index v == i) files

-- | not used yet
getVideoByName :: [Video] -> String -> Maybe Video
getVideoByName files s = find (\ v -> isInfixOf (map toLower s) (map toLower $ takeBaseName $ path v)) files

现在,对find的任何改进都将同时改进这两个功能。

使用null而不是length来检查列表是否为空

接下来,我们将检查length v。这是次优的,因为length是\\mathcal O(n)\$。此外,它将在无限列表上失败,例如length [1..] > 0永远不会退出。

相反,我们使用null,它是\\mathcal O(1)\$:

代码语言:javascript
运行
复制
find :: (a -> Bool) -> [a] -> Maybe a
find p xs = 
    if null v
        then Nothing
        else Just (head v)
    where v = filter p xs

如果要使用

,则使用模式匹配

但是,如果我们意外地写了下面的内容,会发生什么呢?

代码语言:javascript
运行
复制
find :: (a -> Bool) -> [a] -> Maybe a
find p xs = 
    if null v
        then Just (head v)
        else Nothing
    where v = filter p xs

那是个窃听器。我们在空列表上使用head。唉哟。如果我们使用模式匹配,我们可以完全消除这种错误:

代码语言:javascript
运行
复制
find :: (a -> Bool) -> [a] -> Maybe a
find p xs = 
    case filter p xs of
        (x:_) -> Just x
        _     -> Nothing

知道你的标准库

函数find实际上存在。它是由Data.List出口的。我们很容易用Hoogle找到

使用集合作为最后一个参数

下面是一些使用集合作为参数的函数:

代码语言:javascript
运行
复制
foldl  :: (a -> b -> a) -> a -> [b] -> a
foldr  :: (a -> b -> b) -> b -> [a] -> b
filter :: (a -> Bool)   ->      [a] -> Maybe a
map    :: (a -> b)      ->      [a] -> [b]
delete :: Eq a => a     ->      [a] -> [a]
lookup :: Eq a => a     ->  [(a,b)] -> Maybe b

所有这些函数都使用list作为最后一个参数,因为它允许运行。对于getVideosBy*,我们也应该这样做:

代码语言:javascript
运行
复制
import Data.List (find, isInfixOf)

-- | not used yet
getVideoByIndex :: Integer -> [Video] -> Maybe Video
getVideoByIndex i = find (\v -> index v == i)

-- | not used yet
getVideoByName :: String -> [Video] -> Maybe Video
getVideoByName s = find (\v -> (map toLower s) `isInfixOf` (map toLower $ takeBaseName $ path v))

进一步评论

我不打算将上面的注释应用到代码的其余部分,这只是一个练习。确保检查Prelude中的函数,例如,可以将getVideos编写为

代码语言:javascript
运行
复制
-- | Creates Video objects with indexes
getVideos :: [FilePath] -> [Video]
getVideos list = zipWith Video [1..] list
-- or
getVideos = zipWith Video [1..]

你的问题

小函数

我有所有这些小功能,它们执行一项特定的任务,并相互调用以实现最终目标。如果一个人对代码不熟悉,就很难阅读它。

那是Haskell的一部分。但是,如您所见,getVideoBy已经在标准库中了。如果您只使用一个函数一次,有时最好是内联它们。

代码语言:javascript
运行
复制
-- | Bundles the videos in a specific directory in a Directory type.
getDirectory :: [Video] -> String -> Directory
getDirectory videos name = Directory name $ filter (\ v -> (bottomFolder $ path v) == name) videos

或者,您可以使用本地绑定来保留名称:

代码语言:javascript
运行
复制
-- | Bundles the videos in a specific directory in a Directory type.
getDirectory :: [Video] -> String -> Directory
getDirectory videos name = Directory name (getVideosInDirectory videos name)
  where
    getVideosInDirectory videos name = filter (\ v -> (bottomFolder $ path v) == name) videos

既然我们有了一个本地绑定,我们甚至不需要提供这些参数:

代码语言:javascript
运行
复制
-- | Bundles the videos in a specific directory in a Directory type.
getDirectory :: [Video] -> String -> Directory
getDirectory videos name = Directory name videosInDirectory
  where
    videosInDirectory = filter (\ v -> (bottomFolder $ path v) == name) videos

如果我们希望保留这两个函数,那么如果我们更改参数顺序(请参阅上面的“使用集合作为最后的参数”),它们将变得更容易应用和读取:

代码语言:javascript
运行
复制
-- | Bundles the videos in a specific directory in a Directory type.
getDirectory :: String -> [Video] -> Directory
getDirectory name videos  = Directory name (getVideosInDirectory name videos)

getVideosInDirectory :: String -> [Video] -> [Video] 
getVideosInDirectory name videos = filter (\ v -> (bottomFolder $ path v) == name) videos

,正如我们在“使用集合作为最后的参数”中所看到的,可以将其简化为

代码语言:javascript
运行
复制
getDirectory :: String -> [Video] -> Directory
getDirectory name = Directory name . getVideosInDirectory name

getVideosInDirectory :: String -> [Video] -> [Video] 
getVideosInDirectory name = filter (\ v -> (bottomFolder $ path v) == name)

unlines . map show

很好,我可以描述一个定制类型在打印时应该如何显示自己。但是因为我处理的是列表,所以我不得不unlines $ map show它,这不是很漂亮。

你可以用

代码语言:javascript
运行
复制
mapM_ print lib

默认的Show类是非常基本的。实际上,ShowRead只有一个要求:任何自动派生两者的类型都有read (show x) == x。如果您想提供漂亮的格式设置,请使用自定义类型。

代码语言:javascript
运行
复制
class Pretty a where
    pretty :: a -> String

能给你更多的控制权。或者,加一个newtype在列表的周围,例如。

代码语言:javascript
运行
复制
newtype WithNewlines t a = WithNewlines { unWithNewLines :: t a }

instance (Show a, Foldable t) => Show (WithNewlines t a) where
  show = unlines . concatMap (pure . show) . unWithNewLines

然后使用

代码语言:javascript
运行
复制
putStrLn $ WithNewLines lib

但这也或多或少是神秘的。

票数 2
EN

Code Review用户

发布于 2018-08-05 23:16:34

我认为有些尴尬是因为在构建文件列表时,getRecursiveContents丢弃了目录结构,然后代码试图部分地重构它,以便打印列表。

另一种方法是使用来自Data.Tree容器,并尝试在整个程序的大部分过程中保持树结构,直到生成最终的清单。

例如,下面是getRecursiveContents的一个变体,它保留了目录结构(partitionM额外的可以简化这段代码):

代码语言:javascript
运行
复制
-- (directory name, files in directory)
getRecursiveContents' :: FilePath -> IO (Tree (FilePath,[FilePath]))
getRecursiveContents' = Data.Tree.unfoldTreeM $ \folder -> do
    names <- listDirectory folder
    -- using partitionM would simplify this a lot, but the function is not in base
    let separate name next =
            do (fs,ds) <- next
               exists <- doesDirectoryExist (folder  name)
               pure $ if exists then (fs, name:ds)
                                else (name:fs, ds)
    (fs,ds) <- foldr separate (pure ([],[])) names
    --
    pure ((folder, fs), map (folder ) ds)

我们只能使用以下方式保存视频:

代码语言:javascript
运行
复制
 keepVideos :: Tree (a,[FilePath]) -> Tree (a,[FilePath])
 keepVideos = fmap (fmap (filter isVideoFile)) -- tree, tuple

嵌套fmap在树和元组中操作,它们都是函子。元组的fmap工作在第二个元素之上。

我们还可以在树上对文件编号,例如使用State在所有列表中线程一个计数器:

代码语言:javascript
运行
复制
numberFiles :: Tree (a,[b]) -> Tree (a,[(Int,b)])
numberFiles tree =
    let tag b = do n <- get
                   modify succ
                   pure (n,b)
     in evalState (traverse (traverse (traverse tag)) tree) 0 -- tree, tuple, list

嵌套的traverses就像嵌套的fmaps,现在只有三个,因为我们也在遍历列表。元组的traverse工作在第二个元素之上。

为了生成最终的列表,我们可以使用来自Data.Foldable的函数来处理节点列表(Trees是Foldable)。这应该很容易,因为我们有每个节点的文件夹名和文件列表。树也可以用更“结构化”的方式使用foldTree,但这里可能不需要这样做。

票数 3
EN
页面原文内容由Code Review提供。腾讯云小微IT领域专用引擎提供翻译支持
原文链接:

https://codereview.stackexchange.com/questions/201029

复制
相关文章

相似问题

领券
问题归档专栏文章快讯文章归档关键词归档开发者手册归档开发者手册 Section 归档