Copyright | (c) 2021 Tony Zorman |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Tony Zorman <soliditsallgood@mailbox.org> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Utility functions and re-exports for a more ergonomic developing experience. Users themselves will not find much use here.
Synopsis
- module Data.Traversable
- module Data.Monoid
- module Data.Maybe
- module Data.List
- module Data.Functor
- module Data.Function
- module Data.Foldable
- module Data.Char
- module Data.Bool
- module Control.Monad
- module Control.Applicative
- fi :: (Integral a, Num b) => a -> b
- chunksOf :: Int -> [a] -> [[a]]
- (.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b
- (!?) :: [a] -> Int -> Maybe a
- data NonEmpty a = a :| [a]
- notEmpty :: HasCallStack => [a] -> NonEmpty a
- safeGetWindowAttributes :: Window -> X (Maybe WindowAttributes)
- mkAbsolutePath :: MonadIO m => FilePath -> m FilePath
- keyToString :: (KeyMask, KeySym) -> String
- keymaskToString :: KeyMask -> KeyMask -> String
- cleanKeyMask :: X (KeyMask -> KeyMask)
- regularKeys :: [(String, KeySym)]
- allSpecialKeys :: [(String, KeySym)]
- specialKeys :: [(String, KeySym)]
- multimediaKeys :: [(String, KeySym)]
- functionKeys :: [(String, KeySym)]
- type WindowScreen = Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
Documentation
module Data.Traversable
module Data.Monoid
module Data.Maybe
module Data.List
module Data.Functor
module Data.Function
module Data.Foldable
module Data.Char
module Data.Bool
module Control.Monad
module Control.Applicative
chunksOf :: Int -> [a] -> [[a]] Source #
Given a maximum length, splits a list into sublists
>>>
chunksOf 5 (take 30 $ repeat 'a')
["aaaaa","aaaaa","aaaaa","aaaaa","aaaaa","aaaaa"]
(.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b Source #
Multivariable composition.
f .: g ≡ (f .) . g ≡ \c d -> f (g c d)
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
a :| [a] infixr 5 |
Instances
MonadFix NonEmpty | Since: base-4.9.0.0 |
Defined in Control.Monad.Fix | |
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Eq1 NonEmpty | Since: base-4.10.0.0 |
Ord1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Read1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Show1 NonEmpty | Since: base-4.10.0.0 |
Traversable NonEmpty | Since: base-4.9.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Functor NonEmpty | Since: base-4.9.0.0 |
Monad NonEmpty | Since: base-4.9.0.0 |
NFData1 NonEmpty | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
IsList (NonEmpty a) | Since: base-4.9.0.0 |
Generic (NonEmpty a) | |
Read a => Read (NonEmpty a) | Since: base-4.11.0.0 |
Show a => Show (NonEmpty a) | Since: base-4.11.0.0 |
NFData a => NFData (NonEmpty a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
Ord a => Ord (NonEmpty a) | Since: base-4.9.0.0 |
Generic1 NonEmpty | |
type Item (NonEmpty a) | |
type Rep (NonEmpty a) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |
type Rep1 NonEmpty | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) |
notEmpty :: HasCallStack => [a] -> NonEmpty a Source #
fromList
with a better error message. Useful to
silence GHC's Pattern match(es) are non-exhaustive warning in places where
the programmer knows it's always non-empty, but it's infeasible to express
that in the type system.
safeGetWindowAttributes :: Window -> X (Maybe WindowAttributes) Source #
A safe version of getWindowAttributes
.
mkAbsolutePath :: MonadIO m => FilePath -> m FilePath Source #
(Naïvely) turn a relative path into an absolute one.
- If the path starts with
/
, do nothing. - If it starts with
~/
, replace that with the actual home - directory.
- If it starts with
$
, read the name of an environment - variable and replace it with the contents of that.
- Otherwise, prepend the home directory and
/
to the path.
Keys
Convert a modifier mask into a useful string.
cleanKeyMask :: X (KeyMask -> KeyMask) Source #
Strip numlock, capslock, mouse buttons and XKB group from a KeyMask
,
leaving only modifier keys like Shift, Control, Super, Hyper in the mask
(hence the "Key" in "cleanKeyMask").
Core's cleanMask
only strips the first two because key events from
passive grabs (key bindings) are stripped of mouse buttons and XKB group by
the X server already for compatibility reasons. For more info, see:
https://www.x.org/releases/X11R7.7/doc/kbproto/xkbproto.html#Delivering_a_Key_or_Button_Event_to_a_Client
regularKeys :: [(String, KeySym)] Source #
A list of "regular" (extended ASCII) keys.
allSpecialKeys :: [(String, KeySym)] Source #
A list of all special key names and their associated KeySyms.
specialKeys :: [(String, KeySym)] Source #
A list of special key names and their corresponding KeySyms.
multimediaKeys :: [(String, KeySym)] Source #
List of multimedia keys. If Xlib does not know about some keysym
it's omitted from the list (stringToKeysym
returns noSymbol
in
this case).
functionKeys :: [(String, KeySym)] Source #
A list pairing function key descriptor strings (e.g. "F2"
)
with the associated KeySyms.
type WindowScreen = Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail Source #
The specialized Screen
derived from WindowSet
.