blob: f387158a7c75f2c40aa6440e858213571b2856a1 (
plain) (
blame)
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
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.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 XMonad.Util.Invisible (
-- * Usage:
-- $usage
Invisible (..)
, whenIJust
, fromIMaybe
) where
-- $usage
-- A wrapper data type to store layout state that shouldn't be persisted across
-- restarts. A common wrapped type to use is @Maybe a@.
-- Invisible derives trivial definitions for Read and Show, so the wrapped data
-- type need not do so.
newtype Invisible m a = I (m a) deriving (Monad, Functor)
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 _ = ""
whenIJust :: (Monad m) => Invisible Maybe a -> (a -> m ()) -> m ()
whenIJust (I (Just x)) f = f x
whenIJust (I Nothing) _ = return ()
fromIMaybe :: a -> Invisible Maybe a -> a
fromIMaybe _ (I (Just x)) = x
fromIMaybe a (I Nothing) = a
|