Skip to content

Commit

Permalink
X.L.LayoutModifier: (wip) Add class InspectLayoutModifier
Browse files Browse the repository at this point in the history
  • Loading branch information
liskin committed Nov 15, 2020
1 parent a06233c commit 77c1821
Showing 1 changed file with 15 additions and 1 deletion.
16 changes: 15 additions & 1 deletion XMonad/Layout/LayoutModifier.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -26,10 +27,15 @@ module XMonad.Layout.LayoutModifier (
-- $usage

-- * The 'LayoutModifier' class
LayoutModifier(..), ModifiedLayout(..)
LayoutModifier(..), ModifiedLayout(..),

-- * The 'InspectLayoutModifier' class
InspectLayoutModifier(..)
) where

import Control.Monad
import Data.Maybe ( fromMaybe )
import Data.Typeable ( cast )

import XMonad
import XMonad.StackSet ( Stack, Workspace (..) )
Expand Down Expand Up @@ -278,3 +284,11 @@ data ModifiedLayout m l a = ModifiedLayout (m a) (l a) deriving ( Read, Show )
-- the above does not parenthesize (m a) and (l a), which is obviously
-- incorrect.

-- | TODO
class InspectLayoutModifier l a where
inspectModifier :: (LayoutModifier m a, Typeable m) => l a -> Maybe (m a)

-- | TODO
instance (InspectLayoutModifier l a, Typeable m, Typeable a)
=> InspectLayoutModifier (ModifiedLayout m l) a where
inspectModifier (ModifiedLayout m l) = fromMaybe (inspectModifier l) (cast m)

0 comments on commit 77c1821

Please sign in to comment.