summaryrefslogtreecommitdiffhomepage
path: root/src
diff options
context:
space:
mode:
authorjao <jao@gnu.org>2019-12-05 01:15:56 +0000
committerjao <jao@gnu.org>2019-12-05 01:16:27 +0000
commit413dde1f9a12da0449cd4356f3ff7566cd812ec9 (patch)
tree29f3e15efb97dc0608f44de2eb1b1e62459fec8c /src
parentd8cda91a46f486c0fb9b095f4936029268121ccb (diff)
downloadxmobar-config-413dde1f9a12da0449cd4356f3ff7566cd812ec9.tar.gz
xmobar-config-413dde1f9a12da0449cd4356f3ff7566cd812ec9.tar.bz2
GMPDP, an example of a plugin reading json
Diffstat (limited to 'src')
-rw-r--r--src/lib/GMPDP.hs96
1 files changed, 96 insertions, 0 deletions
diff --git a/src/lib/GMPDP.hs b/src/lib/GMPDP.hs
new file mode 100644
index 0000000..370e360
--- /dev/null
+++ b/src/lib/GMPDP.hs
@@ -0,0 +1,96 @@
+{-# LANGUAGE OverloadedStrings, DeriveGeneric #-}
+
+-- https://www.schoolofhaskell.com/school/starting-with-haskell/libraries-and-frameworks/text-manipulation/json
+
+module GMPDP where
+
+import Data.Aeson
+import Data.Text
+import Control.Applicative
+import Control.Monad
+import qualified Data.ByteString.Lazy as B
+import Network.HTTP.Conduit (simpleHttp)
+import GHC.Generics
+
+import Xmobar
+
+import Control.Monad (when)
+import Control.Concurrent.STM
+import Control.Exception (SomeException (..), handle, evaluate)
+
+import System.INotify (Event(..), EventVariety(..), initINotify, addWatch)
+
+import qualified Data.ByteString.Char8 as BS (ByteString, pack)
+
+
+-- | Type of each JSON entry in record syntax.
+data Song =
+ Song { title :: !String
+ , artist :: !String
+ , album :: !String
+ } deriving (Eq,Show,Generic)
+
+data PlayTime =
+ PlayTime { current :: !Int
+ , total :: !Int
+ } deriving (Eq,Show,Generic)
+
+data GMPDPStatus =
+ GMPDPStatus { song :: Song
+ , time :: PlayTime
+ } deriving (Eq,Show,Generic)
+
+-- Instances to convert our type to/from JSON.
+
+instance FromJSON Song
+instance FromJSON PlayTime
+instance FromJSON GMPDPStatus
+
+-- | Location of the local copy, in case you have it,
+-- of the JSON file.
+jsonFile :: FilePath
+jsonFile = "/home/jao/.config/Google Play Music Desktop Player/json_store/playback.json"
+
+getJSON :: IO B.ByteString
+getJSON = B.readFile jsonFile
+
+getGMPDPStatus :: IO (Maybe GMPDPStatus)
+getGMPDPStatus = do
+ s <- (eitherDecode <$> getJSON) :: IO (Either String GMPDPStatus)
+ case s of
+ Left _ -> return Nothing
+ Right r -> return $ Just r
+
+data GMPDP = GMPDP String deriving (Show,Read,Generic)
+
+handleNotification :: TVar (Maybe GMPDPStatus) -> Event -> IO ()
+handleNotification v _ =
+ getGMPDPStatus >>= \s -> atomically $ writeTVar v s
+
+formatStatus Nothing = ""
+formatStatus (Just s) =
+ fmtt (current $ time s) ++ "/" ++ fmtt (total $ time s) ++
+ " " ++ (title $ song s) ++ " <fc=sienna4>" ++ (album $ song s) ++ "</fc>" ++
+ " " ++ (artist $ song s)
+ where fmtt ms = let s = ms `div` 1000
+ sr x = if x < 10 then "0" ++ show x else show x
+ in sr (s `div` 60) ++ ":" ++ sr (s `mod` 60)
+
+changeLoop :: Eq a => STM a -> (a -> IO ()) -> IO ()
+changeLoop s f = atomically s >>= go
+ where
+ go old = do
+ f old
+ go =<< atomically (do
+ new <- s
+ guard (new /= old)
+ return new)
+
+instance Exec GMPDP where
+ alias (GMPDP a) = a
+ start (GMPDP _) cb = do
+ i <- initINotify
+ s <- getGMPDPStatus
+ v <- newTVarIO s
+ addWatch i [CloseWrite] (BS.pack jsonFile) (handleNotification v)
+ changeLoop (readTVar v) $ \s -> cb (formatStatus s)