Skip to content

Instantly share code, notes, and snippets.

@lexi-lambda
lexi-lambda / Matrix.agda
Last active November 17, 2020 02:26
Inductive n-tensor representation proof of concept in Agda
module Matrix where
open import Data.Fin as Fin using (Fin; zero; suc)
open import Data.List as List using (List; []; _∷_; product)
open import Data.Nat as Nat
open import Data.Nat.Properties as Nat
open import Data.Product as Prod
open import Data.Vec as Vec using (Vec; []; _∷_)
open import Level using (Level)
open import Relation.Binary.PropositionalEquality using (_≡_; refl)

With scoped effects, handlers must be a part of the program

It is seductive to imagine that effect handlers in an algebraic effect system are not part of the program itself but metalanguage-level folds over the program tree. And in traditional free-like formulations, this is in fact the case. The Eff monad represents the program tree, which has only two cases:

data Eff effs a where
  Pure :: a -> Eff effs a
  Op :: Op effs a -> (a -> Eff effs b) -> Eff effs b

data Op effs a where
#lang racket/base
; Lock-free FIFO queues, loosely based on “Simple, Fast, and Practical
; Non-Blocking and Blocking Concurrent Queue Algorithms”.
(require racket/contract
racket/future
(only-in racket/unsafe/ops unsafe-struct*-cas!))
(provide queue?
@lexi-lambda
lexi-lambda / find-arrow-packages.rkt
Created April 12, 2020 19:16
A hacky script for scraping packages that use arrow notation from Hackage
#lang racket
(require db/base
db/sqlite3
json
net/url
racket/async-channel
threading)
(define WORKERS 6)

Monads and delimited control are very closely related, so it isn’t too hard to understand them in terms of one another. From a monadic point of view, the big idea is that if you have the computation m >>= f, then f is m’s continuation. It’s the function that is called with m’s result to continue execution after m returns.

If you have a long chain of binds, the continuation is just the composition of all of them. So, for example, if you have

m >>= f >>= g >>= h

then the continuation of m is f >=> g >=> h. Likewise, the continuation of m >>= f is g >=> h.

#lang racket/base
(require (for-syntax racket/base
racket/list
racket/match
syntax/kerncase)
syntax/parse/define)
(define-syntax (argument stx) (raise-syntax-error #f "cannot be used as an expression" stx))
#lang racket/base
(require (for-syntax racket/base
syntax/for-body)
benchmark
plot
racket/format
racket/generator
racket/match
racket/stream)
#lang racket
(require syntax/parse/define "foods.rkt" (for-syntax "foods.rkt"))
(add-delicious-food! "pineapple")
(add-delicious-food! "sushi")
(add-delicious-food! "cheesecake")
(define-simple-macro (add-food-combinations! [fst:string ...]
[snd:string ...])
#:do [(for* ([fst-str (in-list (syntax->datum #'[fst ...]))]
#lang racket/base
;; ---------------------------------------------------------------------------------------------------
;; high-level definition context API
(module intdef racket/base
(require (prefix-in racket: racket/base)
racket/contract
racket/syntax
syntax/apply-transformer
#lang racket
(define/contract (syntax-armed? stx)
(-> syntax? boolean?)
(define (tainted? v)
(and (syntax? v) (syntax-tainted? v)))
(or (syntax-tainted? stx)
(match (syntax-e stx)
[(list* as ... b)
(or (ormap tainted? as) (tainted? b))]