Skip to content

Instantly share code, notes, and snippets.

@LSLeary
LSLeary / Graded.hs
Last active November 8, 2024 04:36 — forked from axman6/Tracked Exceptions.hs
Checked exceptions implemented by grading IO with the set of exceptions an action may throw.
{-# LANGUAGE DataKinds, TypeFamilies, UndecidableInstances, RoleAnnotations
, QuantifiedConstraints, RebindableSyntax, BlockArguments
, RequiredTypeArguments
#-}
module Graded (
GradedAppl(..), (<*>), (<*), (*>),
GradedAlt(..),
GradedMonad(..), (>>),
@LSLeary
LSLeary / 0-InlineFix.hs
Last active October 3, 2024 22:51
Unrolling recursive functions at static arguments using church numerals
{-# LANGUAGE BlockArguments #-}
module InlineFix (
Rec,
inlineFix,
Church, (|&), _0, _1, _2, _3, _4, _5, _6, _7, _8, _9,
) where
import GHC.Exts (inline)
import Data.Function (fix)
@LSLeary
LSLeary / LeibnizC.hs
Created September 23, 2024 08:06
Leibniz equality as a quantified constraint with safe reification and reflection
{-# LANGUAGE QuantifiedConstraints
, UndecidableInstances
, AllowAmbiguousTypes
#-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
module LeibnizC where
import Leibniz
@LSLeary
LSLeary / Pool.hs
Created August 19, 2024 13:17
Transparently hand off jobs to a pool of workers.
{-# LANGUAGE DerivingVia, LambdaCase, BlockArguments #-}
module Pool (
Pool,
runPool,
schedule,
withRunInIO,
) where
-- base
@LSLeary
LSLeary / Sum.hs
Last active August 12, 2024 10:29
An implementation of anonymous sums (AKA variants) with O(1) access, without resorting to Typeable or unsafeCoerce.
{-# LANGUAGE LambdaCase, GADTs #-}
module Sum where
import Data.Type.Equality ((:~:)(..))
import Data.Functor ((<&>))
type f ~> g = forall x. f x -> g x
@LSLeary
LSLeary / Transform.hs
Last active July 23, 2023 04:58
Deriving semidirect products for transformation monoids
{-# LANGUAGE DerivingVia, PatternSynonyms #-}
{-# LANGUAGE UndecidableInstances, MonoLocalBinds #-}
module Transform where
import Data.Functor ((<&>))
import Data.Monoid (Sum(..), Product(..), Ap(..))
test1a :: Transformable p s => Transform p s
@LSLeary
LSLeary / Local.hs
Created July 17, 2023 13:36
A "local" quasiquoter, such that [local|<name>|] = Current.Module.<name>.
module Local (local) where
import Data.Char (isUpper)
import Data.Functor ((<&>))
import Language.Haskell.TH.Syntax
( Q, Exp(VarE, ConE), Type(ConT)
, Module(..), Name(..), OccName(..), NameFlavour(NameQ)
)
import Language.Haskell.TH.Lib (thisModule)
@LSLeary
LSLeary / Triangles.hs
Created July 5, 2023 21:35
Fancy if-then-else with triangles!
module Triangles ((<|), (|>)) where
(<|) :: a -> Bool -> Maybe a
a <| True = Just a
_ <| False = Nothing
infix 2 <|
(|>) :: Maybe a -> a -> a
Just a |> _ = a
Nothing |> a = a
@LSLeary
LSLeary / Fresh.hs
Created June 21, 2023 14:06
Generate fresh Typeable types.
module Fresh
( Fresh, runFresh, withFresh
) where
import Data.Typeable
import Control.Monad.State (StateT, evalStateT, get, put)
import Control.Monad.Trans (MonadTrans)
@LSLeary
LSLeary / Sub.hs
Last active June 9, 2023 21:58
Parametrickery: Subtyping & Monotonicity
{-# LANGUAGE DataKinds #-}
module Sub where
data Sub = S Sub
data Three (s :: Sub) a b c where
One :: a -> Three s a b c
Two :: b -> Three (S s ) a b c