xmonad-contrib-0.15: Third party extensions for xmonad

Copyright(c) Daniel Schoepe 2009
LicenseBSD3-style (see LICENSE)
Maintainerdaniel.schoepe@gmail.com
Stabilityunstable
Portabilitynot portable
Safe HaskellNone
LanguageHaskell98

XMonad.Util.ExtensibleState

Contents

Description

Module for storing custom mutable state in xmonad.

Synopsis

Usage

To utilize this feature in a contrib module, create a data type and make it an instance of ExtensionClass. You can then use the functions from this module for storing and retrieving your data:

{-# LANGUAGE DeriveDataTypeable #-}
import qualified XMonad.Util.ExtensibleState as XS

data ListStorage = ListStorage [Integer] deriving Typeable
instance ExtensionClass ListStorage where
  initialValue = ListStorage []

.. XS.put (ListStorage [23,42])

To retrieve the stored value call:

.. XS.get

If the type can't be inferred from the usage of the retrieved data, you have to add an explicit type signature:

.. XS.get :: X ListStorage

To make your data persistent between restarts, the data type needs to be an instance of Read and Show and the instance declaration has to be changed:

data ListStorage = ListStorage [Integer] deriving (Typeable,Read,Show)

instance ExtensionClass ListStorage where
  initialValue = ListStorage []
  extensionType = PersistentExtension

One should take care that the string representation of the chosen type is unique among the stored values, otherwise it will be overwritten. Normally these string representations contain fully qualified module names when automatically deriving Typeable, so name collisions should not be a problem in most cases. A module should not try to store common datatypes(e.g. a list of Integers) without a custom data type as a wrapper to avoid collisions with other modules trying to store the same data type without a wrapper.

put :: (ExtensionClass a, XLike m) => a -> m () Source #

Add a value to the extensible state field. A previously stored value with the same type will be overwritten. (More precisely: A value whose string representation of its type is equal to the new one's)

modify :: (ExtensionClass a, XLike m) => (a -> a) -> m () Source #

Apply a function to a stored value of the matching type or the initial value if there is none.

remove :: (ExtensionClass a, XLike m) => a -> m () Source #

Remove the value from the extensible state field that has the same type as the supplied argument

get :: (ExtensionClass a, XLike m) => m a Source #

Try to retrieve a value of the requested type, return an initial value if there is no such value.

gets :: (ExtensionClass a, XLike m) => (a -> b) -> m b Source #

modified :: (ExtensionClass a, Eq a, XLike m) => (a -> a) -> m Bool Source #