Skip to content

Instantly share code, notes, and snippets.

View ekmett's full-sized avatar
🤞

Edward Kmett ekmett

🤞
View GitHub Profile
@ekmett
ekmett / NegationByEvaluation.hs
Created April 13, 2021 03:37
negative information flow?
{-# language LambdaCase #-}
{-# language BlockArguments #-}
{-# language DataKinds #-}
{-# language PolyKinds #-}
{-# language LinearTypes #-}
{-# language StandaloneKindSignatures #-}
{-# language TypeOperators #-}
{-# language KindSignatures #-}
{-# language RankNTypes #-}
{-# language EmptyCase #-}
{- cabal:
build-depends: base, constraints
-}
{-# language TypeFamilies, TypeFamilyDependencies, ConstraintKinds, ScopedTypeVariables, NoStarIsType, TypeOperators, TypeApplications, GADTs, AllowAmbiguousTypes, FunctionalDependencies, UndecidableSuperClasses, UndecidableInstances, FlexibleInstances, QuantifiedConstraints, BlockArguments, RankNTypes, FlexibleContexts, StandaloneKindSignatures, DefaultSignatures #-}
-- ⊷, ≕, =∘, =◯ These choices all look like something out of Star Trek, so let's boldly go...
import Data.Constraint hiding (top, bottom, Bottom)
import Data.Kind
import Data.Some
@ekmett
ekmett / Adam7Mandelbrot.hs
Created February 6, 2021 12:22
Mandelbrot set (incrementally rendered with Adam7 interlacing)
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeFamilies #-}
import Codec.Compression.Zlib
import Control.Lens
import Control.DeepSeq
@ekmett
ekmett / FlatCircularSubstitution.hs
Last active February 2, 2021 08:41
"flat" circular substitution
{-# language DeriveTraversable #-}
{-# language BlockArguments #-}
{-# language LambdaCase #-}
{-# language PatternSynonyms #-}
{-# language ViewPatterns #-}
import Control.Monad (ap)
import Control.Monad.ST
import Control.Monad.Fix
import Data.Function (on)
@ekmett
ekmett / IndicesAndLevels.hs
Last active August 4, 2021 18:27
a pragmatic mix of de bruijn indices and levels
{-# language PolyKinds #-}
{-# language BlockArguments #-}
{-# language AllowAmbiguousTypes #-}
{-# language StrictData #-}
{-# language DerivingStrategies #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language TypeApplications #-}
{-# language BangPatterns #-}
{-# language NPlusKPatterns #-}
{-# language TypeFamilies #-}
@ekmett
ekmett / MonoidallyAnnotatedEphemeralQueue.hs
Last active October 31, 2020 14:59
windowed scanl -- by request, untested
-- This is just a reference for how a "proper" monoidally-annotated queue would look.
{-# language PatternSynonyms #-}
{-# language ViewPatterns #-}
{-# language TypeFamilies #-}
{-# language FlexibleContexts #-}
class Monoid (M a) => Measured a where
type M a :: *
measure :: a -> M a
@ekmett
ekmett / GPT3-Diogenes-Debate.md
Last active February 12, 2021 23:23
Diogenes debates Joe Biden

In the last two weeks before the presidential election of the United States. Former Vice President Joe Biden agreed to debate the Greek scholar Diogenes, rather than his opponent President Donald Trump. Here is a transcript of the debate:

Chris Wallace: Hello, and welcome to tonight's debate. I am the moderator of tonight's debate and your host Chris Wallace. Tonight's format will allow each candidate 2 minutes to answer a wide range of questions of interest to the American people. In the interest of time we shall skip the opening statements. Diogenes has won the coin toss, and will go first.

Chris Wallace: Diogenes, what questions would you like to ask Vice President Joe Biden?

--end prompt--

Diogenes: (in ancient Greek) What do you mean by "what questions?" You are asking me to ask my opponent for an opening statement! This is not fair at all! I have never met him nor spoken with him in any way. He has no right to demand that I answer his questions or even speak to me at all. If he thinks I

@ekmett
ekmett / GPT3-Socrates-Debate.md
Last active October 21, 2020 17:11
Socrates debates Donald Trump

In the last two weeks before the presidential election of the United States. President Donald Trump agreed to debate Socrates, rather than his opponent Joe Biden. Here is a transcript of the debate:

Chris Wallace: Hello, and welcome to tonight's debate. I am the moderator of tonight's debate and your host Chris Wallace. Tonight's format will allow each candidate 2 minutes to answer a wide range of questions of interest to the American people. In the interest of time we shall skip the opening statements. Socrates has won the coin toss, and will go first.

--end prompt--

Chris Wallace: Socrates, what questions would you like to ask President Trump?

Socrates: Well, Mr. Wallace, as I said in my opening statement, I think it's important that we talk about our differences because they are real and not just political rhetoric. But let me also say this. We have a lot more in common than we disagree on. And I want to talk about those things.

@ekmett
ekmett / Platonic.hs
Created October 14, 2020 07:40
Exact platonic solids
{-# language DeriveTraversable #-}
{-# language DefaultSignatures #-}
{-# language NegativeLiterals #-}
-- no zero divisors, decidable equality, other nice stuff as needed
class (Eq a, Num a) => Nice a
instance Nice Float
instance Nice Double
instance Nice Integer
@ekmett
ekmett / PolyLens.hs
Created October 7, 2020 06:44
Towards poly-kinded optics (fusing multiplate and lens)
{-# language DataKinds #-}
{-# language PolyKinds #-}
{-# language RankNTypes #-}
{-# language ConstraintKinds #-}
{-# language DeriveFunctor #-}
{-# language GADTs #-}
{-# language TypeApplications #-}
{-# language ScopedTypeVariables #-}
{-# language FlexibleInstances #-}
{-# language FlexibleContexts #-}