Skip to content

Instantly share code, notes, and snippets.

module Cube where
import Data.Functor.Const (Const(..))
import Data.Functor.Product (Product(..))
import Data.Functor.Sum (Sum(..))
type (&&) = Product
type (||) = Sum
@LSLeary
LSLeary / watchfile
Last active September 6, 2024 04:52
A reasonable approximation of ghcid for arbitrary files and interpreters, with nice scrolling and searching via less. Only needs inotifywait on the $PATH.
#! /usr/bin/env sh
# Example usage:
# $ watchfile Test.idr idris2 --check
# $ watchfile test.sh shellcheck
# $ watchfile Main.hs -- cabal test
file=$1; shift
tmp="/tmp/watch.$(basename "$file")"
@LSLeary
LSLeary / Incremental.hs
Last active August 20, 2024 18:42
A thread-safe IC implementation supporting both eager parallel propagation and lazy demand driven evaluation.
{-# LANGUAGE DerivingVia, BlockArguments, LambdaCase #-}
module Control.Concurrent.Incremental (
Adaptive, adaptively,
static, dynamic,
ICVar, newICVar, newICVarIO,
demand, propagate,
compute, await,
@LSLeary
LSLeary / Strutless.hs
Last active January 25, 2023 05:05
Strut-avoiding scratchpads?
module Strutless where
import XMonad
import XMonad.StackSet (RationalRect)
import qualified XMonad.StackSet as W
import Data.Set (Set)
import XMonad.Util.Types (Direction2D)
import XMonad.Util.Rectangle (toRatio)
import XMonad.Util.NamedScratchpad (customFloating)
@LSLeary
LSLeary / write-pr
Last active December 20, 2022 04:00
Write good commit messages, then let a script write your PR for you—or at least the bulk of it.
#! /usr/bin/env sh
# Configuration: where PRs are written
prdir=$HOME/PRs
# Argument: the git rev or ref upon which the PR is based
base=$1
repo=$(basename "$(git rev-parse --show-toplevel)")
@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