Skip to content

Instantly share code, notes, and snippets.

@LSLeary
LSLeary / Cached.hs
Created March 15, 2018 03:02
Optimise any focus-independent layout by caching rectangles?
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module Cached
( Cached
, cached
) where
import XMonad
import qualified XMonad.StackSet as W
import Data.Maybe (fromMaybe)
{-# LANGUAGE TypeApplications #-}
import Control.Applicative (ZipList(..))
import Data.Monoid (Ap(..))
import Data.Maybe (fromMaybe)
import Data.Foldable (traverse_)
every :: Int -> String -> Ap ZipList (Maybe String)
every m s = (Ap . ZipList) (cycle $ Just s : replicate (m - 1) Nothing)
import XMonad
import qualified XMonad.StackSet as W
import Graphics.X11.Xlib.Window (raiseWindow)
import XMonad.Hooks.EwmhDesktops (ewmh)
import Data.Monoid (All(..))
import qualified Data.Map.Strict as M
-- | Separate out propertyNotifyHook from the logHook.
propertyNotifyHook :: X () -> Event -> X All
import XMonad
import XMonad.Actions.PerWorkspaceKeys
import qualified Data.Map.Strict as M
-- | Given config dependent bindings per workspace, produce regular xmonad
-- bindings via @bindOn@. Use like e.g.
--
-- > main = xmonad $ def { keys = perWkspKeys myKeyBinds <+> keys def }
@LSLeary
LSLeary / 0-FiniteLinearOrder.hs
Last active August 18, 2018 02:21
Guaranteeing at the type level uniqueness of members and length of a list-like data-type for safe specification of finite Linear Orders.
{-# LANGUAGE GADTs, TypeFamilies, TypeOperators #-}
{-# LANGUAGE ConstraintKinds, DataKinds, PolyKinds #-}
module FiniteLinearOrder (
FullFiniteLinearOrder (..),
FiniteLinearOrder (..),
Nat (..),
) where
@LSLeary
LSLeary / Grab.hs
Created September 12, 2018 02:20
PR WIP: Modal keybindings for xmonad
{-# LANGUAGE LambdaCase #-}
--------------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.Grab
-- Description : TODO
-- Copyright : (c) 2018 L. S. Leary -- TODO this is kinda wrong...
-- License : BSD3-style (see LICENSE)
--
import XMonad
import XMonad.Util.Types
import qualified XMonad.StackSet as W
import qualified Data.Map.Strict as M
import Control.Monad (when)
-- | Shift a @RationalRect@ to an edge of the screen.
toScreenEdge :: Direction2D -> W.RationalRect -> W.RationalRect
@LSLeary
LSLeary / Strange.hs
Last active December 15, 2018 07:47
{-# LANGUAGE RankNTypes, GADTs, EmptyCase, LambdaCase #-}
module Strange where
-- import Data.Char (ord)
-- Tested with GHC 8.4.3, 8.6.3.
-- I discovered this behaviour while writing church-style ADTs, and thought I'd
-- see if I could write GADTs the same way.
{-# LANGUAGE LambdaCase, DeriveFunctor #-}
module SemiFree where
import Data.Bifunctor
import Data.Semigroup (Endo(..))
-- | Semigroups where some elements reduce in combination, while others only combine
-- symbolically (denoted by @Nothing@)
--
{-# LANGUAGE TypeOperators, PatternSynonyms, ExplicitNamespaces #-}
{-# LANGUAGE LambdaCase, BlockArguments #-}
module Select
( type (-?)(Fun, Const, Lazy, unLazy), ($?)
, Selective(..)
, select, branch, whenS, ifS, whileS, fromMaybeS
, (<||>), (<&&>), anyS, allS
, Monad(..)
) where