{- - Exports a number of functions for selecting from a list - using a remote control as the input and a LIRC display. - 'selectByList' allows the using to scroll through a list - of values. - 'selector' uses a more sophisticated predictive text method. -} module Hmpf.Control ( selectByList , songMonitor , selector ) where import Hmpf.MPDSession import Hmpf.Tree import Hmpf.LIRC import Hmpf.LCDProc import Hmpf.Keys import Hmpf.ApplicationTypes import Data.Maybe (isNothing,fromJust) import Control.Concurrent import Hmpf.Monitor import qualified Hmpf.Util as U eol = (toEnum 0) :: Char selector :: [String] -> Session (Maybe String) selector xs = do let lst = map ( ++ [eol,eol] ) xs select . nextChoice . mkTree build $ lst selectByList :: [String] -> Session (Maybe Int) --selectByList :: [String] -> Session (Maybe String) selectByList = sl 0 where sl i lst = do selectList lst i k <- lirc case k of VolUp -> sl next lst VolDown -> sl previous lst Enter -> (return . Just $ i ) -- Enter -> (return . Just . ( !! i ) $ lst) Esc -> (return Nothing) _ -> sl i lst where next = (i+1) `mod` l previous = (l + i - 1) `mod` l l = length lst select :: Tree Char -> Session (Maybe String) select tree | isRoot tree = return Nothing select tree | isLeaf tree = do let selected = reverse . tail . tail . path $ tree general selected "==========================" lift ( putStr ">>" ) lift (putStrLn selected ) k <- lirc case k of Esc -> select (previousChoice tree) Enter -> (return . Just $ selected) _ -> select tree select tree | otherwise = do let selected = reverse . tail . path $ tree choices = map ( fromEOL . fromJust . val) . branches . up $ tree i = index tree l = (length . branches . up $ tree ) next = ( i + 1 ) `mod` l previous = ( l + i - 1 ) `mod` l fromEOL = \c -> case c == eol of True -> '^' False -> c lift ( putStrLn selected ) let (left,right) = splitAt i choices lift ( putStr left ) lift ( putStr $ '[':(head right):"]" ) lift ( putStrLn . tail $ right ) alphabet selected choices i k <- lirc case k of Esc -> select (previousChoice tree) Enter -> select (nextChoice tree) VolUp -> select . ( !! next ) . branches . up $ tree VolDown -> select . ( !! previous ) . branches . up $ tree MultiMon -> do let lst = subset . up $ tree result <- selectByList lst let val = do i <- result return ( lst !! i ) case val of Nothing -> select tree x -> return x _ -> select tree nextChoice :: Tree a -> Tree a nextChoice tree | isLeaf tree = tree nextChoice tree | (length . branches $ tree) == 1 = nextChoice . head . branches $ tree | otherwise = head . branches $ tree previousChoice :: Tree a -> Tree a previousChoice = pc . up where pc tree | isRoot tree = tree pc tree | (length . branches . up $ tree) < 2 = previousChoice tree pc tree | otherwise = tree -- Generate a list of possible entries from this point in the tree subset :: Tree a -> [[a]] subset tr = case branches tr of [] -> [ reverse . tail . tail . path $ tr ] xs -> concat . map subset $ xs -- Update the music screen continuously songMonitor :: Session () songMonitor = do st <- status case (state st) of "play" -> do Just sng <- currentsong music (artist sng) (title sng) (maybe 0 id (elapsed $ st) ) (maybe 0 id (duration $ st) ) ((+1) . maybe 0 id . song $ st) (maybe 1 id (playlistlength $ st) ) "pause" -> return () "stop" -> do t <- lift U.time musicBanner "" (" " ++ t) return () lift . threadDelay $ 300000 songMonitor