module Catalog where import qualified Data.Text as T import qualified System.Directory as D import qualified System.Posix as P import qualified System.Info as In data SearchDir = SearchDir { dirDepth ::Int, searchDir :: FilePath } deriving (Show) data Action = Action { actionSearchString :: T.Text, ioAction :: IOAction } data IOAction = OneParam (Cataloged -> IO ()) | TwoParam (Cataloged -> Cataloged -> IO ()) data Cataloged = Cataloged { inputType :: InputType, dirPath :: T.Text } deriving (Show) data InputType = Folder | Text | Other deriving (Show, Eq) instance Searchable Action where searchString = actionSearchString instance Searchable Cataloged where searchString = T.toLower . T.pack . reverse . takeWhile (/= '/') . reverse . T.unpack . dirPath instance Show Action where show = T.unpack . searchString instance Searchable T.Text where searchString = id class Searchable s where searchString :: s -> T.Text getCatalog :: IO [Cataloged] getCatalog = do absHomeDir <- D.getHomeDirectory searchCatalogItem SearchDir { dirDepth = 1, searchDir = absHomeDir } -- recursively crawl a directory to the desired depth searchCatalogItem :: SearchDir -> IO [Cataloged] searchCatalogItem (SearchDir depth dir) = do isDir <- P.isDirectory <$> P.getFileStatus dir dir' <- D.makeAbsolute dir let currCatalog = dirToCatalog dir' isDir case (depth, isDir) of (0, _) -> return [currCatalog] (_, False) -> return [currCatalog] (_, True) -> do childPaths <- D.listDirectory dir childCatalogs :: [Cataloged] <- mconcat <$> mapM recSearchCatalog childPaths return $ currCatalog : childCatalogs where recSearchCatalog :: FilePath -> IO [Cataloged] recSearchCatalog x = searchCatalogItem . SearchDir (pred depth) $ (dir ++ "/" ++ x) dirToCatalog :: FilePath -> Bool -> Cataloged dirToCatalog dir isDir = Cataloged { inputType = if isDir then Folder else Other, dirPath = T.pack dir } -- we only match the first one because the action is always the second thing -- that's selected, regardless of how many inputs the action takes -- validAction :: Action -> Cataloged -> Bool -- validAction action = (==) (head . inputs $ action) . inputType getActions :: Cataloged -> [Action] getActions cataloged = [ Action { actionSearchString = "move to trash", ioAction = OneParam $ \cataloged -> P.executeFile "mv" True [T.unpack . dirPath $ cataloged, "~/.Trash"] Nothing }, Action { actionSearchString = "move to", ioAction = TwoParam (\cataloged cataloged' -> P.executeFile "mv" True (map (T.unpack . dirPath) [cataloged, cataloged']) Nothing) } ] ++ case In.os of "darwin" -> darwinActions "linux" -> linuxActions linuxActions :: [Action] linuxActions = [ Action { actionSearchString = "open", ioAction = OneParam $ \cataloged -> P.executeFile "open" True [T.unpack . dirPath $ cataloged] Nothing } ] darwinActions :: [Action] darwinActions = [ Action { actionSearchString = "xfg-open", ioAction = OneParam $ \cataloged -> P.executeFile "open" True [T.unpack . dirPath $ cataloged] Nothing } ]