summaryrefslogtreecommitdiffstats
path: root/lib/Storage.hs
blob: 7f68b15e3a8f4b9977e9967422a2b7136d391366 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
{-# LANGUAGE DeriveDataTypeable, ExistentialQuantification, TypeSynonymInstances, MultiParamTypeClasses, FlexibleInstances, PatternGuards #-}

module Storage ( StoreData
               , Storage
               , storage
               , getStoreData
               , setStoreData
               , updateStoreData
               ) where

import XMonad
import qualified XMonad.StackSet as W
import XMonad.Layout.LayoutModifier (LayoutModifier(..), ModifiedLayout(..))

import Control.Applicative ((<$>))
import Control.Monad

import Data.IORef
import Data.Maybe
import Data.Typeable


class (Typeable d, Show d, Read d) => StoreData d


data (StoreData d) => StorageMessage d = GetStoreData (IORef (Maybe d)) | SetStoreData d
                                     deriving Typeable
instance (StoreData d) => Message (StorageMessage d)


data (StoreData d) => Storage d a = Storage d deriving (Show, Read)

instance (StoreData d) => LayoutModifier (Storage d) a where
  modifierDescription _ = "Storage"
    
  handleMess (Storage d) m
    | Just (GetStoreData ref) <- fromMessage m = do
      io $ writeIORef ref $ Just d
      return $ Nothing

    | Just (SetStoreData d') <- fromMessage m = do
      return $ Just $ Storage d'

  handleMess _ _ = return Nothing


storage :: (LayoutClass l a, StoreData d) => d -> l a -> ModifiedLayout (Storage d) l a
storage def = ModifiedLayout $ Storage def


sendMessage' :: Message a => a -> X ()
sendMessage' a = W.workspace . W.current <$> gets windowset >>= sendMessageWithNoRefresh a


getStoreData :: StoreData d => X (Maybe d)
getStoreData = do
  ref <- io . newIORef $ Nothing
  sendMessage' $ GetStoreData ref
  io . readIORef $ ref


setStoreData :: StoreData d => d -> X ()
setStoreData = broadcastMessage . SetStoreData

updateStoreData :: StoreData d => (d -> d) -> X ()
updateStoreData f = do
  d <- getStoreData
  when (isJust d) $ setStoreData . f $ fromJust d