
Created split packages: cur, cur-lib, cur-test, cur-doc, similar to other Racket packages, e.g., redex. * Moved tests out of core and into cur-test * Moved docs into cur-doc * Moved cur implementation and libraries into cur-lib * Added cur meta-pacakge that installs all of the above
14 lines
340 B
Racket
14 lines
340 B
Racket
#lang s-exp "../cur.rkt"
|
|
(require "sugar.rkt")
|
|
(provide Maybe none some some/i)
|
|
|
|
(data Maybe : (forall (A : Type) Type)
|
|
(none : (forall (A : Type) (Maybe A)))
|
|
(some : (forall* (A : Type) (a : A) (Maybe A))))
|
|
|
|
(define-syntax (some/i syn)
|
|
(syntax-case syn ()
|
|
[(_ a)
|
|
(let ([a-ty (type-infer/syn #'a)])
|
|
#`(some #,a-ty a))]))
|