Skip to content

Instantly share code, notes, and snippets.

@sjoerdvisscher
sjoerdvisscher / Parallel.hs
Last active February 19, 2025 16:54
Par Means Parallel: Multiplicative Linear Logic Proofs as Concurrent Functional Programs
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE QualifiedDo #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
module Parallel where
import Control.Concurrent (forkIO)
@sjoerdvisscher
sjoerdvisscher / IndexedOptic.hs
Last active February 4, 2025 15:32
Indexed Optics as in section 2 of https://arxiv.org/pdf/2112.11145
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE GADTs #-}
module IndexedOptic where
import Data.Kind (Type)
type f ~> g = forall i. f i -> g i
@sjoerdvisscher
sjoerdvisscher / Cofreer.hs
Last active May 3, 2024 10:49
Cofree j-relative comonad
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Cofreer where
import Data.Kind (Type)
@sjoerdvisscher
sjoerdvisscher / FeedbackMonad.hs
Last active February 22, 2024 13:36
From Lenses to Composable Continuations, and what lies between (Bob Atkey)
-- https://www.youtube.com/watch?v=YpklMn5yNA0
{-# LANGUAGE RankNTypes, QuantifiedConstraints #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE GADTs #-}
import Prelude (id, (.), ($), Functor(..), (<$>), fst)
import Data.Functor.Identity (Identity(..))
import Data.Void
import Data.Bifunctor (second)
class Feedback m where
@sjoerdvisscher
sjoerdvisscher / diffLinTypes.hs
Last active November 11, 2023 22:45
Deriving differentiation with linear generics
-- https://twitter.com/paf31/status/1362207106703630338
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
@sjoerdvisscher
sjoerdvisscher / Comonoid.hs
Last active October 15, 2023 09:50
A dual of Applicative
-- https://github.com/viercc/functor-monad/tree/main/day-comonoid
{-# LANGUAGE GHC2021 #-}
import Data.Functor.Day
import Control.Comonad
data Multi f a where
MZ :: a -> Multi f a
MS :: Multi f (b -> a) -> f b -> Multi f a
fromMulti :: Applicative f => Multi f a -> f a
@sjoerdvisscher
sjoerdvisscher / KindCat.hs
Last active October 23, 2023 20:11
Profunctor-based category theory
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
@sjoerdvisscher
sjoerdvisscher / Univ.hs
Last active January 14, 2025 14:27
Universal properties with plain Control.Category
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
import Prelude hiding (id, (.))
import Control.Category
import Data.Functor.Coyoneda
import Data.Bifunctor (first)
newtype Object f g = Object { runObject :: forall a. f a -> g (Object f g, a) }
newtype Obj f g = Obj { runObj :: forall a. f a -> Coyoneda g (Obj f g, a) }
to :: Object f g -> Obj f g
@sjoerdvisscher
sjoerdvisscher / FixSquares.hs
Last active August 9, 2023 15:39
Folds and unfolds using squares
-- Using https://hackage.haskell.org/package/squares
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}