about summary refs log tree commit diff
path: root/src/XMonad/Custom/Layout.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/XMonad/Custom/Layout.hs')
-rw-r--r--src/XMonad/Custom/Layout.hs23
1 files changed, 19 insertions, 4 deletions
diff --git a/src/XMonad/Custom/Layout.hs b/src/XMonad/Custom/Layout.hs
index 8f14926..0ad0de2 100644
--- a/src/XMonad/Custom/Layout.hs
+++ b/src/XMonad/Custom/Layout.hs
@@ -1,10 +1,25 @@
 {-# LANGUAGE DeriveDataTypeable    #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE TypeSynonymInstances  #-}
+{-# OPTIONS_GHC -Wno-missing-signatures #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Custom.Layout
+-- Copyright   :  (c) azahi 2018
+-- License     :  BSD3-style (see LICENSE)
+--
+-- Maintainer  :  azahi@teknik.io
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- Custom target for layouts, sublayouts and layout transformers.
+--
+------------------------------------------------------------------------
 
 module XMonad.Custom.Layout
     ( layoutHook'
-    , Transformers (..)
+    , CustomTransformers (..)
     ) where
 
 import           XMonad
@@ -36,10 +51,10 @@ applyGaps = gaps [ (U, gapBase)
                  , (L, gapBase)
                  ]
 
-data Transformers = GAPS
-                  deriving (Read, Show, Eq, Typeable)
+data CustomTransformers = GAPS
+                        deriving (Read, Show, Eq, Typeable)
 
-instance Transformer Transformers Window where
+instance Transformer CustomTransformers Window where
     transform GAPS x k = k (avoidStruts $ applyGaps $ applySpacing x) (const x)
 
 layoutHook' = fullscreenFloat

Consider giving Nix/NixOS a try! <3