aboutsummaryrefslogtreecommitdiffstats
path: root/Invisible.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-09-28 21:01:07 +0200
committerAndrea Rossato <andrea.rossato@unibz.it>2007-09-28 21:01:07 +0200
commit1efc8d4cf8bd16498607693c6f9589f11c1c97d3 (patch)
tree2b55397aba0f862bf280ce71cfb4b2296b2c14d9 /Invisible.hs
parentbf67ffe8b42cbc8167f6f680231f82a9b2b9fbec (diff)
downloadXMonadContrib-1efc8d4cf8bd16498607693c6f9589f11c1c97d3.tar.gz
XMonadContrib-1efc8d4cf8bd16498607693c6f9589f11c1c97d3.tar.xz
XMonadContrib-1efc8d4cf8bd16498607693c6f9589f11c1c97d3.zip
Added Invisible to store layout state
Invisible is a data type to store information that will be lost when restarting XMonad (the idea came from David Roundy) darcs-hash:20070928190107-32816-ce095723ac5deb5cde50eab871416e3edee1e875.gz
Diffstat (limited to 'Invisible.hs')
-rw-r--r--Invisible.hs42
1 files changed, 42 insertions, 0 deletions
diff --git a/Invisible.hs b/Invisible.hs
new file mode 100644
index 0000000..5d040f7
--- /dev/null
+++ b/Invisible.hs
@@ -0,0 +1,42 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonadContrib.Invisible
+-- Copyright : (c) 2007 Andrea Rossato, David Roundy
+-- License : BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer : andrea.rossato@unibz.it, droundy@darcs.net
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A data type to store the layout state
+--
+-----------------------------------------------------------------------------
+
+module XMonadContrib.Invisible (
+ -- * Usage:
+ -- $usage
+ Invisible (..)
+ , whenIJust
+ ) where
+
+-- $usage
+-- A data type to store the layout state
+
+data Invisible m a = I (m a)
+
+instance (Functor m, Monad m) => Read (Invisible m a) where
+ readsPrec _ s = [(fail "Read Invisible", s)]
+
+instance Monad m => Show (Invisible m a) where
+ show _ = ""
+
+instance (Functor m, Monad m) => Monad (Invisible m) where
+ return a = I (return a)
+ m >>= f = m >>= f
+
+instance (Functor m, Monad m) => Functor (Invisible m) where
+ fmap f (I x) = I (fmap f x)
+
+whenIJust :: (Monad m) => Invisible Maybe a -> (a -> m ()) -> m ()
+whenIJust (I (Just x)) f = f x
+whenIJust (I Nothing) _ = return ()