Skip to content

Instantly share code, notes, and snippets.

@rntz
rntz / fix-eval-eager.ml
Last active December 7, 2024 20:58
Eager, lazy, & small-step "correct" fixed points
type var = string
type term = Var of var
| Lam of var * term
| App of term * term
| Fix of var * term (* only used for functions *)
| Lit of int
type value = Int of int
| Fun of (value -> value)
@rntz
rntz / mapgen.hs
Created November 13, 2024 03:04
generating maps
import System.Environment (getArgs)
import Control.Monad (guard, forM_)
import System.Random (RandomGen)
import qualified System.Random as Random
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
@rntz
rntz / sudoku.hs
Last active December 13, 2024 14:33
sudoku generation in Haskell
module Main where
import Data.List (minimumBy)
import Data.Ord (comparing)
import Data.Maybe (fromJust)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
-- Unknown: a list of ((x,y), options) for each cell (x,y).
type Unknown = [((Int, Int), [Int])]
@rntz
rntz / sudoku.py
Last active September 11, 2024 06:45
sudoku generator
import copy, random
n = 9
values = list(range(n))
def to_matrix(d):
return [[d[(x,y)] for y in range(n)] for x in range(n)]
def sudoku():
known = dict()
unknown = {(x,y): set(values)
@rntz
rntz / not-sudoku.py
Created September 11, 2024 06:09
not a sudoku solver
import copy, random
n = 4
values = list(range(n))
def to_matrix(d):
return [[d[(x,y)] for y in range(n)] for x in range(n)]
def sudoku():
known = dict()
unknown = {(x,y): set(values)
@rntz
rntz / GuardedKanren.hs
Created September 3, 2024 23:14
minikanren search strategy in Haskell
-- see https://gist.github.com/rntz/c2996e06301d9ae95ee0c7a9b43f5e0d for comparison
module GuardedKanren where
import Control.Monad (liftM2, guard)
import Control.Applicative
data Stream a = Nil | Cons a (Stream a) | Later (Stream a)
deriving (Show)
instance Functor Stream where
@rntz
rntz / GuardedKanren.agda
Last active September 4, 2024 14:49
implementation of muKanren's search strategy in Agda with --guarded
{-# OPTIONS --guarded #-}
module GuardedKanren where
open import Agda.Primitive using (Level)
private variable
l : Level
A B : Set l
data Bool : Set where true false : Bool
if_then_else_ : ∀{A : Set} → Bool → A → A → A
@rntz
rntz / datakanren.rkt
Last active August 26, 2024 21:05
DataKanren, a combination of datalog and microkanren
#lang racket
(require racket/hash) ;; hash-union
;; UNIFICATION VAR
;; symbol beginning with ?
(define (var? x) (and (symbol? x) (string-prefix? (symbol->string x) "?")))
(define/contract (var x) (-> symbol? var?)
(string->symbol (format "?~a" x)))
(define/contract (var-name x) (-> var? symbol?)
@rntz
rntz / kanrig.rkt
Last active August 26, 2024 18:17
microkanren with semirings
#lang racket
(struct rig (zero? sum product) #:prefab)
(define the-rig (make-parameter #f))
(define (the-rig-zero? x) ((rig-zero? (the-rig)) x))
(define (the-rig-sum args) ((rig-sum (the-rig)) args))
(define (the-rig-product args) ((rig-product (the-rig)) args))
(define (the-rig-+ . args) (the-rig-sum args))
(define (the-rig-* . args) (the-rig-product args))
(define (the-rig-zero) (the-rig-+))
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}
module IncrementalStreams where
import Prelude hiding (init)
import Data.Foldable (toList)
import qualified Data.Set as Set
import Data.Set (Set)
import qualified Data.Map as Map
import Data.Map (Map)