aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/LayoutBuilderP.hs
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2011-06-09 07:18:58 +0200
committerAdam Vogt <vogt.adam@gmail.com>2011-06-09 07:18:58 +0200
commit79f42d9dd4b28df0dd0fef7c03b6dc2938fef4a9 (patch)
tree5effa0220f9771e36a26f16d18b259e661ccad43 /XMonad/Layout/LayoutBuilderP.hs
parent45c6b115e6609c905c0578a785a53784820da71d (diff)
downloadXMonadContrib-79f42d9dd4b28df0dd0fef7c03b6dc2938fef4a9.tar.gz
XMonadContrib-79f42d9dd4b28df0dd0fef7c03b6dc2938fef4a9.tar.xz
XMonadContrib-79f42d9dd4b28df0dd0fef7c03b6dc2938fef4a9.zip
Use a phantom type instead of undefined in L.LayoutBuilderP
Ignore-this: f9009c339ac20245ca0b1dc8154b673f This better expresses the idea that the argument to alwaysTrue is just there to select an instance. Another option could be to do use a fundep, which seems to be compatible with the two instances so far. class Predicate p w | p -> w darcs-hash:20110609051858-1499c-ea3f8f433a510fea3c6fcc79b77098d14afe163f.gz
Diffstat (limited to 'XMonad/Layout/LayoutBuilderP.hs')
-rw-r--r--XMonad/Layout/LayoutBuilderP.hs11
1 files changed, 7 insertions, 4 deletions
diff --git a/XMonad/Layout/LayoutBuilderP.hs b/XMonad/Layout/LayoutBuilderP.hs
index 6ff48d0..aee6c6a 100644
--- a/XMonad/Layout/LayoutBuilderP.hs
+++ b/XMonad/Layout/LayoutBuilderP.hs
@@ -20,7 +20,7 @@ module XMonad.Layout.LayoutBuilderP (
B.relBox, B.absBox,
-- * Overloading ways to select windows
-- $selectWin
- Predicate (..),
+ Predicate (..), Proxy(..),
) where
import Control.Monad
@@ -42,13 +42,16 @@ import qualified XMonad.Layout.LayoutBuilder as B
-- | Type class for predicates. This enables us to manage not only Windows,
-- but any objects, for which instance Predicate is defined.
--- We assume that for all w checkPredicate (alwaysTrue undefined) == return True.
--
-- Another instance exists in XMonad.Util.WindowPropertiesRE in xmonad-extras
class Predicate p w where
- alwaysTrue :: w -> p -- ^ A predicate that is always True. First argument is dummy, we always set it to undefined
+ alwaysTrue :: Proxy w -> p -- ^ A predicate that is always True.
checkPredicate :: p -> w -> X Bool -- ^ Check if given object (window or smth else) matches that predicate
+-- | Contains no actual data, but is needed to help select the correct instance
+-- of 'Predicate'
+data Proxy a = Proxy
+
-- | Data type for our layout.
data LayoutP p l1 l2 a =
LayoutP (Maybe a) (Maybe a) p B.SubBox (Maybe B.SubBox) (l1 a) (Maybe (l2 a))
@@ -71,7 +74,7 @@ layoutAll :: forall l1 p a. (Read a, Eq a, LayoutClass l1 a, Predicate p a) =>
-> l1 a -- ^ The layout to use in the specified area
-> LayoutP p l1 Full a -- ^ The resulting layout
layoutAll box sub =
- let a = alwaysTrue (undefined :: a)
+ let a = alwaysTrue (Proxy :: Proxy a)
in LayoutP Nothing Nothing a box Nothing sub Nothing
instance (LayoutClass l1 w, LayoutClass l2 w, Predicate p w, Show w, Read w, Eq w, Typeable w, Show p) =>