Skip to content

Instantly share code, notes, and snippets.

@LSLeary
LSLeary / Phases.hs
Last active August 2, 2025 07:53 — forked from sjoerdvisscher/Phases.hs
The Phases Applicative (but written as a heap)
{-# LANGUAGE GHC2021, LambdaCase, RoleAnnotations #-}
module Phases (Phases, runPhases, phase) where
-- To maintain the heap invariant according to @Ord k@, the type role of @k@
-- must be nominal, and @Phases@ must be opaque.
type role Phases nominal representational representational
data Phases k f a where
Pure :: a -> Phases k f a
Phase :: k -> (w -> x -> y -> z) -> f w -> Phases k f x -> Phases k f y
{-# LANGUAGE LambdaCase #-}
module Collapse where
-- base
import Data.Functor ((<&>))
import Data.Functor.Classes (Show1)
import Data.Foldable (toList)
import Control.Monad (ap)
@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(..), (>>),