Skip to content

Instantly share code, notes, and snippets.

@miguel-negrao
Created May 19, 2016 12:56
Show Gist options
  • Save miguel-negrao/bf3c623a0b11314dd0329b459ff3a8aa to your computer and use it in GitHub Desktop.
Save miguel-negrao/bf3c623a0b11314dd0329b459ff3a8aa to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
import Turtle hiding (x)
import Prelude hiding (FilePath)
import qualified Control.Foldl as Fold
import Data.List (sortBy)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO (writeFile)
dirIsLeaf :: FilePath -> IO Bool
dirIsLeaf dir = do
let x = do
path <- ls dir
mfilter id $ liftIO $ testdir path
xs <- fold x Fold.list
case xs of
[] -> return True
_ -> return False
lsLeafDirs :: FilePath -> Shell Text
lsLeafDirs dir = do
path <- lstree dir
isDir <- liftIO $ testdir path
if isDir then
do
isDirLeaf <- liftIO $ dirIsLeaf path
if isDirLeaf then return (format fp path) else mzero
else mzero
lsLeafDirsWithTime :: FilePath -> Shell (UTCTime, Text)
lsLeafDirsWithTime dir = do
path <- lstree dir
isDir <- liftIO $ testdir path
if isDir then
do
isDirLeaf <- liftIO $ dirIsLeaf path
if isDirLeaf then
do
timemod <- datefile path
return (timemod, format fp path)
else mzero
else mzero
main :: IO ()
main = do
dir <- pwd
withTime <- fold (lsLeafDirsWithTime dir) Fold.list
let simple = snd <$> withTime
let sorted = fmap snd.sortBy (\a b -> compare (fst b) (fst a)) $ withTime
TIO.writeFile (T.unpack $ format fp (dir </> "list.txt")) $ T.unlines simple
TIO.writeFile (T.unpack $ format fp (dir </> "list_by_addition_date.txt")) $ T.unlines sorted
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment