Skip to content

Instantly share code, notes, and snippets.

@LSLeary
LSLeary / Rec.hs
Last active October 3, 2024 22:51
Almost obnoxious levels of duality in fixed-points.
{-# LANGUAGE QuantifiedConstraints, BlockArguments, LambdaCase #-}
module Rec where
import Data.Functor.Product (Product(..))
import Data.Functor.Sum (Sum(..))
import Data.Kind (Type, Constraint)
import Control.Arrow ((&&&), (|||))
@LSLeary
LSLeary / Zip.hs
Created October 18, 2022 03:36
Zippy Heterogeneous Lists
{-# LANGUAGE DataKinds, GADTs #-}
module Zip where
import Data.Kind (Type)
data Zippy :: (k1 -> k2 -> Type) -> [k1] -> [k2] -> Type where
Nil :: Zippy f '[] '[]
(:~) :: f x y -> Zippy f xs ys -> Zippy f (x:xs) (y:ys)
@LSLeary
LSLeary / Internal.hs
Created September 24, 2022 08:45
Quadrant: my overly complex, generally self-indulgent, and entirely unpolished layout.
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables, PatternSynonyms, MultiWayIf, RankNTypes #-}
{-# LANGUAGE MonoLocalBinds #-}
--------------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.Quadrant.Internal
-- Description : The internals and core interface of the Quadrant layout.
-- Copyright : (c) 2018 L. S. Leary
-- License : BSD3-style (see LICENSE)
@LSLeary
LSLeary / Roles.hs
Created August 31, 2022 21:32
GHC type role inference and checking has the big stupid.
{-# LANGUAGE RoleAnnotations, DerivingVia #-}
module Roles where
import Control.Monad.Reader (MonadReader, ReaderT(..))
-- | In the case of:
--
-- > newtype ReaderT r m a = ReaderT (r -> m a)
@LSLeary
LSLeary / ThenRefocusAfter.hs
Last active August 5, 2022 12:53
Modify an action to integrate it with RefocusLast.
module ThenRefocusAfter where
import XMonad
import XMonad.Hooks.RefocusLast (refocusWhen)
import XMonad.Util.NamedScratchpad
(NamedScratchpads, query, namedScratchpadAction)
import qualified XMonad.StackSet as W
thenRefocusAfter :: Query Bool -> X a -> X a
p `thenRefocusAfter` act = do
@LSLeary
LSLeary / ConditionalBindings.hs
Last active October 4, 2022 01:27
Conditional key bindings for xmonad. WIP.
{-# LANGUAGE StandaloneDeriving, DeriveFunctor, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
--------------------------------------------------------------------------------
-- Module : XMonad.Actions.ConditionalBindings
-- Description : A framework for producing conditional key bindings.
-- Copyright : (c) 2018 L. S. Leary
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : L. S. Leary
@LSLeary
LSLeary / Y.hs
Last active August 20, 2025 09:05
{-# LANGUAGE BlockArguments #-}
module Y where
newtype Y a = Y { ($$) :: Y a -> a }
{-# NOINLINE y #-}
y :: (a -> a) -> Y a
y f = Y \x -> f (x $$ x)
{-# 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
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 / 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)
--