Skip to content

Instantly share code, notes, and snippets.

@olligobber
olligobber / printByte.iota
Last active March 16, 2021 11:03
Prints a byte, encoded as an 8-tuple of booleans, using 2 variables to represent it in hexadecimal
ι(ι(ι(ιι)))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ιι)(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ιι))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ιι))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ιι))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))))))))))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι))(ι(ι(ι(ιι)))(ι(ι(ιι)
@olligobber
olligobber / Functions.hs
Created February 10, 2021 12:41
Generates and exports infinitely many functions (uses all your ram at compile time) with template haskell
{-# LANGUAGE TemplateHaskell #-}
module Functions where
import FunctionsTemplate (generateFunctions)
generateFunctions
-- Normal if statement, requires brackets or associative operators for nesting.
if' :: Bool -> a -> a -> a
if' b x y = if b then x else y
{-
Magic if statement, no brackets needed.
`magicIf` and `magicElseIf` pass on a function, that is either `id` or
`const x` saying what to do when a True or Else case is reached, to the next
`magicElseIf` or `magicElse`.
-}
@olligobber
olligobber / 2Stamp.hs
Last active March 30, 2020 07:11
How many 1c, 7c, or 10c stamps do you need to total a given value
import qualified DP
import Data.Map ((!))
nextSubproblem :: DP.DPCalc Int Int () Int
nextSubproblem = do
this <- DP.thisSubproblem
return (this + 1)
subproblemSolver :: DP.DPCalc Int Int () Int
subproblemSolver = do
@olligobber
olligobber / Rates.hs
Last active January 12, 2020 04:11
Use of Haskell's type checker for calculations of rates
{-# LANGUAGE TypeOperators, ExplicitNamespaces #-}
module Rates (
Rate(..),
(&*),
rev,
(&/),
RatRate,
type (//)
) where
@olligobber
olligobber / primes.bf
Created November 25, 2019 11:37
Outputs all 1 byte primes using only 7 bytes of memory.
SET POS 0 TO 2
++
WHILE POS 0 ISNT 0
[
SET POS 1 TO 2
>++<
SET POS 2 TO POS 0 MINUS POS 1
[->>+>+<<<]>>>[-<<<+>>>]<<[->->+<<]>>[-<<+>>]<<<
WHILE POS 1 ISNT POS 0 (POS 2 ISNT 0)
>>[<<
@olligobber
olligobber / sort.bf
Last active April 9, 2020 08:12
Given a 0-terminated list of bytes, outputs them in increasing order. Uses 2n+4 bytes of memory to sort n bytes of input, using insertion sort.
WHILE INPUT IS NONZERO
,[
MOVE TO LEFT ELEMENT
<<
WHILE LEFT ELEMENT EXISTS
[
ORDER POS 0 AND POS 2 WITH SMALLEST ON RIGHT
USING POS 0 & 1 & 2 & 3 & 5 & 7
WHILE POS 0 ISNT 0
@olligobber
olligobber / order.bf
Last active November 18, 2019 12:39
Given a stream of bytes as input, each pair is ordered so the smallest is output first and the largest is output second. Uses 6 bytes of memory.
LOOP FOREVER
+[-
LOAD FIRST INPUT IN POS 0 & SECOND IN POS 1
,>,<
WHILE POS 0 ISNT 0
[
MOVE TO POS 1 & COPY VALUE TO POS 3 & 4
>[->>+>+>+<<<<]>>>>[-<<<<+>>>>]<<<<
MOVE TO POS 3
>>
@olligobber
olligobber / UnionFind.hs
Last active September 19, 2019 09:13
An implementation of a disjoint set data structure (aka unionfind) in Haskell
{-# LANGUAGE RankNTypes #-}
module UnionFind (
Getter,
Setter,
UnionFind,
UnionFindS,
new,
find,
union,
> let proplist = ((\x -> conj (prop $ 'a':show x) (prop $ 'b':show x)) <$> [0..2])
> putStr . unlines $ fancyRender id <$> proplist
a0 ∧ b0
a1 ∧ b1
a2 ∧ b2
> putStrLn $ fancyRender (either (('t':).show) id) $ disjSmall proplist
(¬t0 ∨ a0) ∧ (¬t0 ∨ b0) ∧ (¬t1 ∨ a1) ∧ (¬t1 ∨ b1) ∧ (¬t2 ∨ a2) ∧ (¬t2 ∨ b2) ∧ (t0 ∨ t1 ∨ t2)
> putStrLn $ fancyRender id $ foldl1 disjBig proplist
(a0 ∨ a1 ∨ a2) ∧ (a0 ∨ a1 ∨ b2) ∧ (a0 ∨ a2 ∨ b1) ∧ (a0 ∨ b1 ∨ b2) ∧ (a1 ∨ a2 ∨ b0) ∧ (a1 ∨ b0 ∨ b2) ∧ (a2 ∨ b0 ∨ b1) ∧ (b0 ∨ b1 ∨ b2)