Skip to content

Instantly share code, notes, and snippets.

@opqdonut
opqdonut / kortti
Created December 17, 2021 11:35
Clojurellinen joulukortti
;;Rauhaisaa joulua ja
;;tulevaa vuotta! Alla
;;pala käsinleivottua
;;clojurekoodia. Nauti!
(reduce reduce reduce[,
[reduce[comp][eval,,,,,
replace]][{\i,,,,,,,,,,
(comment)\ä,,,,,,,,,,,,
assoc\t,,,,,,,,,,,,,,,,
str},,,,,,,,,,,,,,,,,,,
@opqdonut
opqdonut / Day8.hs
Created December 10, 2021 05:55
Advent of Code 2021 Day 8
module Day8 where
import Data.List
parseLine l = (map sort $ take 10 w, map sort $ drop 11 w)
where w = words l
input = map parseLine . lines <$> readFile "input.8"
part1 i =
@opqdonut
opqdonut / Day7.hs
Created December 9, 2021 15:25
Advent of Code 2021 Day 7
module Day7 where
import Data.List
parse :: String -> [Int]
parse s = read ("["++s++"]")
input = parse <$> readFile "input.7"
example = [16,1,2,0,4,2,7,1,2,14]
@opqdonut
opqdonut / Day6.hs
Created December 9, 2021 06:28
Advent of Code 2021, Day 6
module Day6 where
import Debug.Trace
import Data.Array
step = concatMap u
where u 0 = [6,8]
u n = [n-1]
fishnaive init d = length (iterate step [init] !! d)
@opqdonut
opqdonut / Day3.hs
Last active December 3, 2021 05:42
Advent of Code 2021, Day 3
module Day3 where
import Data.Char
import Data.List
import Data.Ord
import Numeric
import Control.Applicative
input = map (map digitToInt) . lines <$> readFile "input.3"
@opqdonut
opqdonut / shift_reset.clj
Last active September 17, 2021 08:43
shift/reset in clojure
(ns shift-reset
(:require [clojure.walk :as walk]
[clojure.test :refer [deftest is]]))
(defmacro shift [& _]
(assert false "Shift outside reset"))
(defn shift? [e]
(and (list? e)
(= 'shift (first e))))
@opqdonut
opqdonut / README.md
Created June 1, 2021 09:07
Monitor puzzle

It's 8AM on a Monday and Joel is trying to get in to the Nitor Office.

Joel has lots of keys in a keychain in his pocket. Each key can have a parent key that it hangs on, and possibly a left or a right child key that hang on it.

Joel gropes around in his pocket for the leftmost key. This can be reached by starting at the top key, and moving to the lefth child key as long as possible. After this Joel pulls the keychain out of his pocket using this key. The rest of the keys dangle under this new

@opqdonut
opqdonut / Matrix.hs
Last active March 10, 2021 15:02
arbitrary-dimensional matrices
module Matrix where
-- We want a datatype that can work like [a], [[a]], [[[a]]] etc.
-- We want the type system to ensure all the values of type a are at the same level, unlike in a rose tree:
import Data.List
data RoseTree a = Single a | Many [RoseTree a]
deriving Show
@opqdonut
opqdonut / longest.sh
Created March 9, 2021 13:42
Finding the longest functions in a clojure codebase
# via awk, assuming everything with a ( in column 0 is a definition:
awk '/^\(/ {print c, f, s; f=FILENAME; s=$0; c=0} {c++} END {print c, FILENAME, s}' **/*.clj **/*.cljs **/*.cljc | sort -rn | head
# or, more accurately via the clj-kondo linter
clj-kondo --config '{:output {:analysis true :format :json}}' --lint src --lint test | jq -r '.analysis ["var-definitions"] | .[] | ((.["end-row"] - .row) | tostring) + " " + .ns + "/" + .name ' | sort -rn | head
;; Spec: split a list into chunks such that the total size of each chunk is limited.
;; Size is measured by a function parameter.
;; Output should be a lazy sequence.
(comment
(partition-by :size 10 [{:size 1} {:size 2} {:size 8} {:size 3} {:size 7}])
;; ==> (({:size 1} {:size 2}) ({:size 8}) ({:size 3} {:size 7}))
)
;; First implementation: reductions seems like a good fit, but requires too much scaffolding
(defn partition-by [measure limit xs]