Skip to content

Instantly share code, notes, and snippets.

@miguel-negrao
Created May 17, 2016 13:04
Show Gist options
  • Save miguel-negrao/78c748fd7cac946e1c3011a8c1073838 to your computer and use it in GitHub Desktop.
Save miguel-negrao/78c748fd7cac946e1c3011a8c1073838 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
import Turtle hiding (x, options)
import qualified Control.Foldl as Fold
import qualified Data.List as List
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
dmenu = inproc "dmenu" ["-i","-l","50"]
playTrack path = void $ proc "audacious" ["-e", path] empty
maybeDo :: Maybe (IO ()) -> IO ()
maybeDo = fromMaybe (return ())
contents :: Turtle.FilePath -> IO [Text]
contents path = fold (input path) Fold.list
updateList :: Turtle.FilePath -> Text -> IO ()
updateList path line = do
txt <- contents path
output path $ select $ line : filter (/= line) txt
menuExec :: [(T.Text,IO ())] -> IO ()
menuExec options = do
r <- fold (dmenu $ select (fmap fst options)) Fold.head
let action = do
rr <- r
List.lookup rr options
donothing = return () :: IO ()
fromMaybe donothing action
openMusicDir :: Turtle.FilePath -> Turtle.FilePath -> IO ()
openMusicDir baseFolder listFilename = do
mselectedTrack <- fold (dmenu $ input (baseFolder </> listFilename)) Fold.head
maybeDo $ do
selectedTrack <- mselectedTrack
return $ do
updateList (baseFolder </> "music_history.txt") selectedTrack
playTrack selectedTrack
runActionWithAvailableMusicDisk action = do
let path_a = "/media/miguel/musica/MUSIC"
a <- testdir path_a
if a then action path_a else do
let path_b = "/media/miguel/backup/Musica/MUSIC"
b <- testdir path_b
when b $ action path_b
openMusicWithList :: Turtle.FilePath -> IO ()
openMusicWithList p = do
let path_a = "/media/miguel/musica/MUSIC"
a <- testdir path_a
if a then openMusicDir path_a p else do
let path_b = "/media/miguel/backup/Musica/MUSIC"
b <- testdir path_b
when b $ openMusicDir path_b p
lsdir :: Turtle.FilePath -> Shell Turtle.FilePath
lsdir path = do
child <- ls path
True <- testdir child
return child
travelFilesystemWithDmenu :: Turtle.FilePath -> (Turtle.Text -> IO ()) -> IO ()
travelFilesystemWithDmenu path action = do
let dmenuForDir path = dmenu $ format fp <$> lsdir path
selectedPath <- fold (dmenuForDir path) Fold.head
case selectedPath of
Just x -> do
print x
xs <- fold (lsdir (fromText x)) Fold.list
case xs of
_:_ -> travelFilesystemWithDmenu (fromText x) action
_ -> action x
_ -> return ()
musicByDirectory :: IO ()
musicByDirectory = runActionWithAvailableMusicDisk (\x -> travelFilesystemWithDmenu x playTrack)
normalMusic :: IO ()
normalMusic = openMusicWithList "list.txt"
previouslyPlayed :: IO ()
previouslyPlayed = openMusicWithList "music_history.txt"
byAdditionDate :: IO ()
byAdditionDate = openMusicWithList "list_by_addition_date.txt"
musicOptions :: [ (T.Text, IO ())]
musicOptions = [
("music", normalMusic),
("music by directory",musicByDirectory),
("previously played", previouslyPlayed),
ple ("by date of addition", byAdditionDate)]
main :: IO ()
main = menuExec musicOptions
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment