Skip to content

Instantly share code, notes, and snippets.

View eignnx's full-sized avatar

eignnx eignnx

View GitHub Profile
main :-
catch(
( phrase_from_stream(unlimited(parser), user_input) -> true
; format('% parse failure!~n', []) ),
_,
format('% caught exception!~n', [])
),
format('% exiting...~n', []).
unlimited(Goal) -->
unlimited(Goal) -->
call(Goal),
unlimited(Goal).
main :-
test(`asdf:`),
test(`asdf:asdf:asdf:`),
test(`BAD`),
test(`asdf:asdf:asdf:BAD`),
test(`asdBAD`),
:- op(350, yfx, @).
:- set_prolog_flag(occurs_check, error).
:- det(inference/3).
inference(true, bool, _).
inference(false, bool, _).
@eignnx
eignnx / hindley-milner.pl
Last active January 3, 2024 16:03
An implementation of the Hindley-Milner type inference algorithm in SWI-Prolog.
:- op(600, yfx, '@'). % Function application
:- op(450, xfy, '=>'). % Type variable quantification
:- op(1150, fx, mode).
% Defines/validates a typing context.
tcx([]).
tcx([X-Sigma | Tcx]) :-
atom(X),
sigma_type(Sigma),
tcx(Tcx).
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE PatternSynonyms #-}
import Data.Maybe
import Control.Monad.State
import Data.List
data Ty
= Unit -- The unit type.
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
import Debug.Trace ( trace )
type Ident = String
data Value
= Var Ident
| Bool Bool
@eignnx
eignnx / plus-plus-arrow.pl
Last active April 11, 2021 01:15
A Prolog `term_expansion` rule for a modified DCG arrow. It automatically builds syntax trees as it parses.
:- module(cfg_macro, [
op(1200, xfx, ++>)
]).
:- op(1200, xfx, ++>).
/*
The rule:
s ++> np(blah), vp.
translates to:
data Number = singular | plural
data Person = 1st | 2nd | 3rd
data Gender = nonbinary | feminine | masculine | neutral
rule start = english_sentence + "."
rule english_sentence
= pronoun.Number.Person.Gender are.Number.Person.Gender adj
| subj.N1.G1 verb.N1.G1 obj.N2.G2
--OPTION 1 (CURRENT SYNTAX)----
rule whatever1 = "something"
rule whatever2.Thing =
.thing1 -> "something 1"
.thing2 -> "something 2"
rule whatever3.Thing.Thing =
.thing1 {
.thing1 -> "something 1"
50 Ways to Leave Your Lover
Paul Simon
-----------------------------------CHORDS---------------------------------------
Cmaj7 = x35453 (close to barred C)
B7 = x24242 (barred)
D#dim = 23424x (kinda like barred B7, but add middle finger)
D/F# = 200232 (wrap thumb around onto lowest string @ fret #2)
G = 355433