Add Foldable, Functor, and Traversable instances for Stack

`Functor` is provided by DeriveFunctor.
`Foldable` uses `integrate` (`Stack`'s `toList`).
`Traversable` uses the `Reverse` Applicative to traverse the `up` list in
reverse order.
This commit is contained in:
Keith 2021-01-27 19:55:01 -05:00 committed by Tomas Janousek
parent 5cdf428f55
commit 2c91ea1621
2 changed files with 16 additions and 1 deletions

View File

@ -1,4 +1,5 @@
{-# LANGUAGE PatternGuards #-} {-# LANGUAGE PatternGuards #-}
{-# LANGUAGE DeriveFunctor #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -52,6 +53,8 @@ module XMonad.StackSet (
) where ) where
import Prelude hiding (filter) import Prelude hiding (filter)
import Control.Applicative.Backwards (Backwards (Backwards, forwards))
import Data.Foldable (foldr, toList)
import Data.Maybe (listToMaybe,isJust,fromMaybe) import Data.Maybe (listToMaybe,isJust,fromMaybe)
import qualified Data.List as L (deleteBy,find,splitAt,filter,nub) import qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
import Data.List ( (\\) ) import Data.List ( (\\) )
@ -175,8 +178,19 @@ data RationalRect = RationalRect !Rational !Rational !Rational !Rational
data Stack a = Stack { focus :: !a -- focused thing in this set data Stack a = Stack { focus :: !a -- focused thing in this set
, up :: [a] -- clowns to the left , up :: [a] -- clowns to the left
, down :: [a] } -- jokers to the right , down :: [a] } -- jokers to the right
deriving (Show, Read, Eq) deriving (Show, Read, Eq, Functor)
instance Foldable Stack where
toList = integrate
foldr f z = foldr f z . toList
instance Traversable Stack where
traverse f s =
flip Stack
-- 'Backwards' applies the Applicative in reverse order.
<$> forwards (traverse (Backwards . f) (up s))
<*> f (focus s)
<*> traverse f (down s)
-- | this function indicates to catch that an error is expected -- | this function indicates to catch that an error is expected
abort :: String -> a abort :: String -> a

View File

@ -81,6 +81,7 @@ library
, mtl , mtl
, process , process
, setlocale , setlocale
, transformers >= 0.3
, unix , unix
, utf8-string >= 0.3 && < 1.1 , utf8-string >= 0.3 && < 1.1
ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind