aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
authorDaniel Schoepe <daniel.schoepe@gmail.com>2009-09-19 21:17:17 +0200
committerDaniel Schoepe <daniel.schoepe@gmail.com>2009-09-19 21:17:17 +0200
commitc1a6ed7be8b090cea63a70fa86ee614d011d0f63 (patch)
tree2611d41215616daba97a239330d85a00123f44e6 /XMonad/Util
parent3bd3fd1d4bd1af1ffe306307a80387c82d304664 (diff)
downloadXMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.tar.gz
XMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.tar.xz
XMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.zip
Factor out direction types and put them in X.U.Types
Ignore-this: b2255ec2754fcdf797b1ce2c082642ba This patch factors out commonly used direction types like data Direction darcs-hash:20090919191717-7f603-09c283e51a0b886d260008676d71e3daf31f4394.gz
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/Types.hs30
1 files changed, 30 insertions, 0 deletions
diff --git a/XMonad/Util/Types.hs b/XMonad/Util/Types.hs
new file mode 100644
index 0000000..48ffd54
--- /dev/null
+++ b/XMonad/Util/Types.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Util.Types
+-- Copyright : (c) Daniel Schoepe (2009)
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Daniel Schoepe <daniel.schoepe@gmail.com>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Miscellaneous commonly used types.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Util.Types (Direction1D(..)
+ ,Direction2D(..)
+ ) where
+
+import Data.Typeable (Typeable)
+
+-- | One-dimensional directions:
+data Direction1D = Next | Prev deriving (Eq,Read,Show,Typeable)
+
+-- | Two-dimensional directions:
+data Direction2D = U -- ^ Up
+ | D -- ^ Down
+ | R -- ^ Right
+ | L -- ^ Left
+ deriving (Eq,Read,Show,Ord,Bounded,Typeable)