Skip to content

Instantly share code, notes, and snippets.

View pedrominicz's full-sized avatar

Pedro Minicz pedrominicz

View GitHub Profile
@pedrominicz
pedrominicz / sk.pl
Last active August 9, 2022 11:57
Generate typable SK-combinator calculus terms of a given size
:- ensure_loaded(library(aggregate)).
% Generate typable SK-combinator calculus terms of a given size.
%
% Based on Paul Tarau's paper A Hiking Trip Through the Orders of Magnitude:
% Deriving Efficient Generators for Closed Simply-Typed Lambda Terms and Normal
% Forms.
%
% The paper:
% https://arxiv.org/pdf/1608.03912.pdf
@pedrominicz
pedrominicz / CountSK.hs
Last active August 8, 2022 17:06
Number of SK-combinator calculus terms of a given size
{-# OPTIONS_GHC -Wno-type-defaults #-}
module CountSK where
import Memo
import Data.Foldable
data Term = S | K | App Term Term
@pedrominicz
pedrominicz / gen_boltzmann.pl
Last active August 9, 2022 00:25
Randomly generate simply-typed lambda calculus expressions using Boltzmann samplers
:- ensure_loaded(library(apply)).
:- ensure_loaded(library(random)).
:- set_prolog_flag(optimise, true).
:- set_prolog_flag(optimise_unify, true).
% Randomly generate simply-typed lambda calculus terms using Boltzmann
% samplers.
%
% Based on the paper Random generation of closed simply-typed λ-terms: a
@pedrominicz
pedrominicz / gen.pl
Last active August 9, 2022 12:17
Generate simply-typed lambda calculus expressions of a given size
:- ensure_loaded(library(aggregate)).
:- ensure_loaded(library(lists)).
% Generate simply-typed lambda calculus terms of a given size.
%
% Based on Paul Tarau's paper A Hiking Trip Through the Orders of Magnitude:
% Deriving Efficient Generators for Closed Simply-Typed Lambda Terms and Normal
% Forms.
%
% The paper:
@pedrominicz
pedrominicz / Count.hs
Last active August 8, 2022 16:50
Number of untyped lambda calculus terms of a given size
{-# OPTIONS_GHC -Wno-type-defaults #-}
module Count where
import Memo
import Data.Foldable
-- Based on section 3.1 of the paper Generating Random Lambda Calculus Terms by
-- Jue Wang.
@pedrominicz
pedrominicz / Memo.hs
Created August 4, 2022 14:55
Memoization using `IORef`
module Memo where
import Data.IORef
import System.IO.Unsafe
import qualified Data.Map as M
memoIO :: (Ord a) => (a -> b) -> IO (a -> IO b)
memoIO f = do
v <- newIORef M.empty
return $ \x -> do
@pedrominicz
pedrominicz / recover.lean
Created July 31, 2022 11:21
Good recursors for mutually inductive types
import logic.equiv.basic
universes u v
section
parameters {l r : Type u}
mutual inductive P₁, P₂ (l r : Type u)
with P₁ : Type u
@pedrominicz
pedrominicz / Lex.x
Created July 27, 2022 16:23
Alex: strict text
{
module Lex where
import Data.Bits
import Data.Char
import Data.Word
import Data.Text (Text)
import qualified Data.Text as T
}
@pedrominicz
pedrominicz / Lex.x
Created July 27, 2022 16:12
Extremely simple Alex and Happy example
{
module Lex where
}
%wrapper "basic"
tokens :-
$white+ ;
[^ $white]+ { id }
@pedrominicz
pedrominicz / Lazy.x
Last active July 27, 2022 16:23
Alex: strict bytestring with user state
{
module Lazy where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as B
}
%wrapper "monadUserState-bytestring"
$alpha = [A-Za-z]