=> See INSTALL.md
for new directory installation instructions!
=> Tested on OSX & Linux with Clang++ & G++, and should work on Windows (adheres C++17 standard)
- Launch REPL:
$ heist
- Interpret Script:
$ heist <script-filename> <argv1> <argv2> ...
- Embed Heist in C++: See
EMBED.md
! - Extend Heist with Primitives: See
EXTEND.md
!
- Tail-Call Optimization
- Unhygienic & Reader Macros
- OOP Support
- Multi-Arity Pattern-Matching
- Infix-Operator Support
- First-Class Hash-Maps
- Opt-In Dynamic Scoping
- Opt-In Continuations
- Native Even Streams
- Generic Algorithms
- Expanded String Library
- String I/O
- And More!
- Heist Properties
- Heist Command-Line Flags
- Heist Primitive Data Types
- Heist Numerics
- Heist Macro System, Procedures vs. Macros
- Heist Commenting
- CPS: Continuation Passing Style
- Heist Special Forms
- Quote, Quasiquote
- Lambda, Fn
- Define, Set!, Defn
- Defined?, Delete!
- Begin
- If, And, Or
- Cond, Case
- Let, Let*, Letrec, Letrec*
- Do, While, For
- Delay, Scons, Stream
- Vector-Literal, Hmap-Literal
- Define-Reader-Alias
- Core-Syntax, Define-Syntax, Let-Syntax, Letrec-Syntax
- Syntax-Rules, Syntax-Hash
- Scm->Cps, Cps-Quote, Using-Cps?
- Curry, -<>
- Defclass, New
- Define-Coroutine
- Define-Module
- Define-Overload
- Infix!, Infixr!, Unfix!
- Heist Primitive Variables
- Heist Primitive Procedures
- Help
- Build System Information
- Numeric Primitives
- Equality Predicates
- Character Procedures
- String Procedures
- List/Pair Procedures
- Vector Procedures
- Hash-Map Procedures
- Generic Sequence Procedures
- OOP Reflection Primitives
- Coroutine Handling Primitives
- Stream Primitives
- Delay Predicate & Force
- Type Predicates
- Type Coercion
- Copying
- Eval & Apply
- Compose, Bind, & Id
- Output Procedures
- Formatted Output Procedures
- Input Procedures
- Filesystem Procedures
- Port Procedures
- System Interface Procedures
- Interpreter Invariants Manipulation
- Control Flow Procedures
- Call/cc
- Gensym & Symbol-Append
- Syntax Procedures
- JSON Interop
- CSV Interop
- Universes
- Heist Mathematical Flonum Constants
- Heist Minimalist REPL Example
- Weak & Dynamically Typed
- Properly Tail-Recursive
- Limits non-tail recursion to depth of 1000 by default
- See
set-max-recursion-depth!
primitive to change this
- See
- Embeddable in >= C++17
heist:
symbol prefix is reserved for internal use!
?
suffix denotes a predicate procedure!
suffix denotes a mutative (non-purely-functional) procedure(
,[
, &{
are interchangeable (as are)
,]
, &}
)- Note:
{}
can also force precedence with infix operators!
- Note:
procedure
is said instead offunction
#it
refers to the REPL's last evaluated expression
- Code is data (parentheses construct an Abstract Syntax Tree)
- Function (or "procedure") calls are denoted by parens:
- in C++:
myFunc(0,'a',"hello")
- in Heist Scheme:
(myFunc 0 #\a "hello")
- in C++:
- Nearly every character (except
.
) can be used in a variable name!- Unless, of course, the combination could be interpreted as a
primitive data type (ie1000
is an invalid variable name) - Hence can do things like name a factorial function
!
as if it were a primitive! - This excludes
.
though, given it denotes property access for objects
- Unless, of course, the combination could be interpreted as a
- Lisp 1: variables & procedures share a single namespace
core-syntax
is evaluated first & MUST be matched (unlike runtime macros fromdefine-syntax
)- Runtime macros & variables are in different namespaces
- Hence if a runtime macro's pattern doesn't match, it gets treated as an attempted procedure call
- Interpret Script:
<script-filename> <optional-argv-1> ...
- Compile Script:
-c <script-filename> <optional-compiled-filename>
- Load Script:
-l <script-filename>
- Infix Operators:
-infix
- With CPS Evaluation:
-cps
- Disable ANSI Colors:
-nansi
- Case Insensitivity:
-ci
- Dynamic Call Trace:
-dynamic-call-trace
- Trace Call Args:
-trace-args
- Stack Trace Size:
-trace-limit <non-negative-integer>
- Interpreter Version:
--version
- Show These Options:
--help
Compilation replaces interpreter's reader, hence:
- Reader-modifying operations must be done in a seperate file and loaded with
-l
!- These include
infix!
,infixr!
,unfix!
,define-reader-syntax
, &define-reader-alias
! - IE:
$ heist -l reader_modifications.scm -c file_to_compile.scm
- These include
Wraps scheme code in a scm->cps
block automatically, hence:
- Reader-modifying operations must be done in a seperate file and loaded with
-l
!- These include
infix!
,infixr!
,unfix!
,define-reader-syntax
, &define-reader-alias
! - IE:
$ heist -cps -l reader_modifications.scm file_to_interpret.scm
- These include
- Affects the REPL, scripts, and
-c
!- Use with the REPL wraps every expression in a unique
scm->cps
block!
- Use with the REPL wraps every expression in a unique
Order | Operators | Assoc | Effects |
---|---|---|---|
10 | : |
Right | functional composition |
9 | ** |
Right | expt |
8 | * / % // mod |
Left | *, /, remainder, quotient, modulo |
7 | + - |
Left | addition, subtraction |
6 | :: @ |
Right | cons, append |
5 | > < >= <= |
Left | gt, lt, gte, lte |
4 | == != |
Left | eq, neq |
3 | && |
Left | and |
2 | || |
Left | or |
1 | -> |
Left | lambda |
0 | = <- **= *= /= %= //= mod= += -= |
Right | define, set!, set! ** * / % // mod + - |
- Symbol (quoted syntax label,
'hello
) - Number (see numerics section)
- Pair (quoted expression
'(1 2 3)
, list(list 1 2 3)
, or cons(cons 1 (cons 2 (cons 3 '())))
) - String (wrapped by
""
, usesASCII
encoding!) - Char (have the
#\
prefix,#\h #\e #\l #\l #\o
) (usesASCII
encoding!)- Also Supports Named Chars and Hex Chars:
#\space
,#\tab
,#\newline
,#\vtab
,#\page
,#\return
#\alarm
,#\backspace
,#\nul
,#\esc
,#\delete
#\x0
->#\xff
- Also Supports Named Chars and Hex Chars:
- Boolean (true or false,
#t
or#f
) - Vector (quoted literal
'#(1 2 3)
, or primitive(vector 1 2 3)
) - Hash-Map (quoted literal
'$(a 1 b 2)
, or primitive(hmap 'a 1 'b 2)
) - Input Port, Output Port (see port primitives)
- Syntax-Rules Object (see
syntax-rules
special form) - Delayed Data (see
delay
special form) - Procedure (via primitives or the
lambda
/fn
special forms) - Object (see
defclass
) - Class-Prototype (see
defclass
) - Void Datum
(void)
- Undefined Datum
(undefined)
- Exact/Ratnum (rational number)
- Arbitrary precision numerator & denominator (automatically reduced to simplest form!)
- Special Case: denominator of
1
creates a BigInt-1/2 ; stays as a fraction! 3 ; ratnum w/ denom of 1 = bigint 4/2 ; gets simplified to bigint 2
- Inexact/Flonum (floating-point number)
- Base-10 may use scientific notation!
- Precision is bound by
fl-precision
- Special Case:
0.0
gets simplified to0
(Zero is Exact)1.0 3.5e10 ; scientific notation -4E12 ; also scientific notation
- Special Constants:
- Positive Infinity:
+inf.0
- Negative Infinity:
-inf.0
- NaN:
+nan.0
,-nan.0
- Both
+nan.0
&-nan.0
resolve to the same NaN object!
- Both
- Positive Infinity:
- Complex Numbers:
- Both the real and imaginary components will match in exactness
- Supports
+inf.0
or-inf.0
components (+nan.0
is unique & never complex!) - Special Case: imaginary value of
0
becomes a real (non-complex) number!3/4+1/2i 3/4+0.5i ; becomes 0.75+0.5i to match exactness -i ; valid complex number! -44+0i ; becomes -44
- Radix:
- Binary:
#b
, Octal:#o
, Hexadecimal:#x
, Decimal:#d
(enabled by default) - Nary 2-36:
#2r
-#36r
#b-101 ; -5 #b10/11 ; 2/3 #b1010.11 ; 10.75 #o77 ; 63 #xC0DE ; 49374 #xc0de ; 49374 #30rHeistScheme ; 10326335991592274 #2r-101/10 ; -5/2
- Binary:
- Exactness:
- Inexact:
#i
, Exact:#e
#i3 ; 3.0 #i1/2 ; 0.5 #e3.5 ; 7/2 #e1.0 ; 1 #e#b101.1 ; Exact & Binary! => 11/2 #i#2r101 ; Inexact & Binary! => 5.0
- Inexact:
One of Scheme's most powerful features is its flexible run-time macro system!
For those in the know:
- While R5RS+ Scheme supports hygienic macros, R4RS (Heist Scheme's base) makes this optional.
- Unhygienic macros were selected after experimenting with CL, Clojure, & Scheme, finding:
- Hygiene's pros are easier to emulate w/o it than non-hygiene's pros are to emulate with hygiene
- Forsaking hygiene enables more extensive control when meta-programming
Macros are identical to procedures, except for 3 key features:
- They expand into new code that will be run in the current scope, rather than
processing a computation in a new scope (that of their definition, as with procedures)- Built-in
syntax-hash
mechanism makes avoiding namespace conflicts trivial! - Macro argument names are automatically hashed to become unique symbols!
- Built-in
- They do not evaluate their arguments (unlike procedures)
- Hence macros can accept, and expand into, arbitrary code and data patterns!
- They do NOT have a recursive expansion limit (as does procedural non-tail-recursion)
- Hence recursive expansions MAY cause a segmentation fault if they infinitely expand
- NOTE: Such is an indication of a USER error however, and NOT an interpreter error!
- Hence recursive expansions MAY cause a segmentation fault if they infinitely expand
Either a syntax-rules
object, or an unary callable:
- Syntax-rules objects have the expression matched against a pattern, then expanded into a template
- Callables are passed the macro expression as a quoted datum, and must return an evaluable datum
- Note: transformers defined in cps contexts have
id
bound as their continuation!
- Note: transformers defined in cps contexts have
- Single-line comment:
;
- Multi-line comment: Open:
#|
, Close:|#
A style of programming which explicitly handles control flow via "continuations",
where a "continuation" represents the rest of the work to be done in a program.
Programming with and manipulating continuations can yield certain advantages,
most notably the ability to implement many control flow operations in terms
of continuations (including threads, coroutines, try-catch, arbitrary returns, goto, etc.)
Unfortunately, explicitly programming with continuations is rarely desirable and hardly enjoyable.
Fortunately, there are ways to convert any program into CPS, and Scheme as a language has this
transformation baked in by default.
The power of continuations in Scheme may be leveraged through the primitive call/cc
procedure:
taking an unary procedure as its argument, call/cc
(or call-with-current-continuation
) passes
the current continuation as an argument to the function it received.
Check out this blog post on implementing Coroutines, Exceptions, Generators, and more using call/cc
!
And yet, continuations pose certain penalties incurred by the transformation process, and as such
some believe they should be removed from the Scheme standard altogether.
Heist Scheme, in an effort to reconcile these perspectives, offers "opt-in" CPS tranformations by
using the intrinsic scm->cps
macro to transform code blocks into CPS & the -cps
cmd-line flag to
transform entire programs at the user's behest.
As such, Heist programs may get the efficiency of not using continuations by default, then activate CPS
transformations for their benefits as needed. However, this means that primitives such as call/cc
may only be validly used in the scope of a scm->cps
block or when using the -cps
cmd-line flag.
Other primitives of this nature include:
load
alternative inscm->cps
blocks:cps-load
eval
alternative inscm->cps
blocks:cps-eval
compile
alternative inscm->cps
blocks:cps-compile
- Proper List:
(quote (<obj1> <obj2> ...))
=>(list '<obj1> '<obj2> (quote ...))
- Dotted List:
(quote (<obj1> ... <objN> . <objN+1>))
=>(append '(<obj1> ... <objN>) <objN+1>)
- Empty List:
(quote ())
=>'()
(unique value, ONLY one returning#t
fornull?
primitive!) - Vector:
(quote #(<obj1> <obj2> ...))
=>(vector '<obj1> '<obj2> (quote ...))
- Hash-Map:
(quote $(<key> <val> ...))
=>(hmap '<key> '<val> (quote ...))
- Syntax:
(quote <syntax>)
=><syntax-as-symbol>
- Else:
(quote <any-other-obj>)
=><any-other-obj>
'12 ; => 12
'hello ; => hello
'(1 2 3) ; => (list 1 2 3)
'#(hello there) ; => (vector 'hello 'there)
'$(a 1 b 2) ; => (hmap 'a 1 'b 2)
''double ; => (quote (quote double)) => (list 'quote 'double)
'(define a 12) ; => (list 'define 'a '12) ; quoted code becomes a list of data!
`<obj> => (quasiquote <obj>)
,<obj> => (unquote <obj>)
,@<obj> => (unquote-splicing <obj>)
- Note:
quasiquote
is actually a macro directly defined in Heist Scheme!
Quoting a Datum (exactly like quote
, with 2 key exceptions):
unquote
ing data undoes the quotation done byquasiquote
unquote-splicing
=unquote
and "unwraps" parenthesis- Hence result of
unquote-splicing
must eval to acyclic list
- Hence result of
(define a 12)
`(a a a) ; => (list 'a 'a 'a)
`(a ,a a) ; => (list 'a 12 'a)
(define b '(1 2 3))
`(b b b) ; => (list 'b 'b 'b)
`(,b ,b ,b) ; => (list (list 1 2 3) (list 1 2 3) (list 1 2 3))
`(,@b ,@b ,@b) ; => (list 1 2 3 1 2 3 1 2 3)
(define c (cons 3 4))
`(1 2 ,c) ; => '(1 2 (3 . 4))
`(1 ,c 2) ; => '(1 (3 . 4) 2)
`(1 2 ,@c) ; => '(1 2 3 . 4)
`(1 ,@c 2) ; => ERROR! CANT APPEND 2 TO DOTTED LIST '(1 3 . 4)
- Note: Pass a variadic number of args (0+) by using
.
as such:- Note: Variadic arg-list name must always be the last arg!
(lambda (. va-args-list) <body> ...) ; OK (lambda (a b . va-args-list) <body> ...) ; OK (lambda (a b . va-args-list c) <body> ...) ; ERROR: Variadic Arg Name Isn't Last!
- Note: Variadic arg-list name must always be the last arg!
- Note: Assign default values to arguments by using
()
:- Note: Mandatory parameters must precede optional ones!
(lambda (a (b 1) (c 2)) <body> ...) ; OK, b & c have default values! (lambda (a (b 1) . va-args-list) <body> ...) ; OK, has both optionals & variadics! (lambda ((b 1) a . va-args-list) <body> ...) ; ERROR: a MUST precede optional b! (lambda (a b . (va-args-list 1)) <body> ...) ; ERROR: variadics CAN'T have defaults!
- Note: Mandatory parameters must precede optional ones!
- Use
%n
to refer to then
th argument (1-indexed so%1
is the 1st arg) - Use
%%
to refer to a variadic arg (hencelist
is equivalent to\%%
)
- Note: Pass a variadic number of args (0+) by using
.
(likelambda
!) - Note: Pattern-match against containers by using literal syntax!
- Like
syntax-rules
, write more restrictive patterns first! - Boolean literals match based on truthiness rather than type!
- Match against symbol literals by using
quote
!
- Like
(define list-map
(fn ((f ()) '()) ; match against nil
((f (x . xs)) (cons (f x) (list-map f xs))))) ; match & unpack pair
(define factorial
(fn ((n) (factorial n 1))
((0 p) p) ; 0 is more restrictive than 'n', so place 1st!
((n p) (factorial (- n 1) (* n p)))))
(define bad-bool-match
(fn ((#t) "true")
((1) "one"))) ; NEVER TRIGGERED: 1 is "truthy" & hence matches #t!
(define gud-bool-match
(fn ((1) "one") ; place more restrictive 1 literal first!
((#t) "true")))
(bad-bool-match 1) ; "true"
(bad-bool-match #t) ; "true"
(gud-bool-match 1) ; "one"
(gud-bool-match #t) ; "true"
;; Define a Variable
(define <var-name> <value>)
;; Define a Procedure
(define (<procedure-name> <arg1> <arg2> ...) <body> ...)
;; Alias "define" via "def"
(def life-universe-everything 42)
- Becomes
(obj.add-property! (quote <name>) <new-value>)
if<var-name>
=<obj.name>
(define (<procedure-name> <arg> ...) <body> ...)
;; Becomes =>
(define <procedure-name> (lambda (<arg> ...) <body> ...))
(define ((compose f g) x) (f (g x)))
;; Becomes =>
(define (compose f g) (lambda (x) (f (g x))))
- Becomes
(obj.set-property! (quote <name>) <new-value>)
if<var-name>
=<obj.name>
Use: Determine if a Symbol is define
d!
- Given an object property-access symbol, returns whether the property exists!
- Use
runtime-syntax?
,core-syntax?
, &reader-syntax?
to check for macros! - WARNING: This is NOT the inverse of the
undefined?
primitive!undefined?
checks values,defined?
checks the environment!
(defined? a) ; #f ; <a> was never registered in the environment!
(undefined? a) ; ERROR: <undefined?> operates on values, and <a> has none in the environment!
(define a 12)
(defined? a) ; #t
(set! a (undefined))
(defined? a) ; #t ; "(undefined)" is a valid value type assigned to <a> in the environment!
(undefined? a) ; #t ; <undefined?> checks values!
Use: Unbind a Symbol if define
d!
- Given an object property-access symbol, removes the property from the object!
- If property is in object's prototype, next access re-caches a copy in the object!
(define a 12)
(display a) ; 12
(delete! a) ; unbind <a>
(display a) ; ERROR => UNBOUND a
(defclass C () (val 12))
(define c (C))
(define c.val2 13) ; dynamically add <val2> member to <c>
(set! c.val 14) ; update <c.val> value
(display c.val) ; 14
(display c.val2) ; 13
(delete! c.val)
(delete! c.val2)
(display c) ; #<object>
(display c.val) ; 12 [re-cached in <c> from prototype <C>]
(display c.val2) ; ERROR => <.val2> NOT A PROPERTY OF <c>
- Helps fit multiple expressions somewhere only expecting 1 (see
if
)
- Note: Use
begin
for multiple<consequent>
and/or<alternative>
expressions
- Note:
and
is actually a macro directly defined in Heist Scheme!
Derivation Using if
:
(and <exp1> <exp2> <exp3> <exp4>)
;; Becomes =>
(if <exp1> (if <exp2> (if <exp3> <exp4> #f) #f) #f)
- Note:
or
is actually a macro directly defined in Heist Scheme!
Derivation Using if
:
(or <exp1> <exp2> <exp3> <exp4>)
;; Becomes =>
(let ((or-result <exp1>)) ; Bind result to prevent 2x eval from condition & result
(if or-result
or-result
(let ((or-result <exp2>))
(if or-result
or-result
(let ((or-result <exp3>))
(if or-result
or-result
<exp4>))))))
- Note:
cond
is actually a macro directly defined in Heist Scheme!
- Using
else
as the condition of the last clause is equivalent to using#t
as the condition - Use
=>
to apply the result of the condition to a callable
Derivation Using if
:
(cond (<condition1> <exp1> ...)
(<condition2> <exp2> ...)
(<condition3> => <callable>)
(else <exp4> ...))
;; Becomes =>
(if <condition1>
(begin <exp1> ...)
(if <condition2>
(begin <exp2> ...)
(let ((cond-result <condition3>))
(if cond-result
(<callable> cond-result)
(begin <exp4> ...)))))
- Note:
case
is actually a macro directly defined in Heist Scheme!
(case <key> <clause1> ... <clauseN>)
; <clause> = ((<match1> ... <matchN>) <exp1> ... <expN>)
- Using
else
as the condition of the last clause is equivalent to using#t
as the condition
Derivation Using cond
:
(case <key>
((<val1> ...) <exp1> ...)
((<val2> <key> <val3> ...) <exp2> ...)
((<val4> ...) => <callable>)
(else <exp3> ...))
;; Becomes =>
(cond ((memv <key> (list <val1> ...)) <exp1> ...) ; See the <memv> primitive!
((memv <key> (list <val2> <key> <val3> ...)) <exp2> ...)
((memv <key> (list <val4> ...)) => <callable>)
(else <exp3> ...))
- Note:
let
is actually a macro directly defined in Heist Scheme!
- Nameless:
(let (<arg-binding1> ... <arg-bindingN>) <body> ...)
- Named:
(let <name> (<arg-binding1> ... <arg-bindingN>) <body> ...)
Derivations Using lambda
:
;; -:- NAMELESS -:-
(let ((<name> <value>) ...)
<body> ...)
;; Becomes =>
((lambda (<name> ...) <body> ...)
<value> ...)
;; -:- NAMED -:-
(let <procedure-name> ((<name> <value>) ...)
<body> ...)
;; Becomes =>
(let ()
(define <procedure-name>
(lambda (<name> ...) <body> ...))
(<procedure-name> <value> ...))
- Note:
let*
is actually a macro directly defined in Heist Scheme!
<arg-binding>
=(<name> <value>)
Derivation Using let
:
(let* ((<name1> <value1>)
(<name2> <value2>)
(<name3> <value3>))
<body> ...)
;; Becomes =>
(let ((<name1> <value1>))
(let ((<name2> <value2>))
(let ((<name3> <value3>))
<body> ...)))
- Note:
letrec
is actually a macro directly defined in Heist Scheme!
<arg-binding>
=(<name> <value>)
Derivation Using let
:
(letrec ((<name> <value>) ...)
<body> ...)
;; Becomes =>
(let ((<name> #f) ...)
(set! <name> <value>) ...
<body> ...)
- Note:
letrec*
is actually a macro directly defined in Heist Scheme!
<arg-binding>
=(<name> <value>)
Derivation Using letrec
:
(letrec* ((<name1> <value1>)
(<name2> <value2>)
(<name3> <value3>))
<body> ...)
;; Becomes =>
(letrec ((<name1> <value1>))
(letrec ((<name2> <value2>))
(letrec ((<name3> <value3>))
<body> ...)))
- Note:
do
is actually a macro directly defined in Heist Scheme!
(do ((<var> <initial-val> <update>) ...)
(<break-test> <return-exp1> <return-exp2> ...) ; returns are optional (<void> by default)!
<body> ...)
Derivation Using letrec
:
(do ((<var> <initial-val> <update>) ...)
(<break-test> <return-exp1> <return-exp2> ...)
<body> ...)
;; Becomes =>
(letrec ((<INTERNAL-RESERVED-NAME>
(lambda (<var> ...)
(if <break-test>
(begin <return-exp1> <return-exp2> ...)
(begin
<body> ...
(set! <var> <update>) ...
(<INTERNAL-RESERVED-NAME> <var> ...))))))
(<INTERNAL-RESERVED-NAME> <initial-val> ...))
- Warning: degrades to
do
in cps contexts! - Use
*condition*
as an alias for the current condition! - Uses a true C++
while
under the hood (no recursion overhead)!
(while (<test> <return-exp1> <return-exp2> ...) ; returns are optional (<void> by default)!
<body> ...)
(define x 0)
(while ((< x 10))
(set! x (+ x 1))
(if (= x 5)
(set! *condition* #f))) ; set condition to false w/o modifying "x"!
(display x) ; 5
(define x 0)
(while ((< x 10)) (set! x (+ x 1)))
(display x) ; 10 (as expected)
- Note:
for
is actually a macro directly defined in Heist Scheme! - Identical interface as
do
but expands to awhile
!
(for ((<var> <initial-val> <update>) ...)
(<break-test> <return-exp1> <return-exp2> ...) ; returns are optional (<void> by default)!
<body> ...)
Derivation Using while
:
(for ((<var> <initial-val> <update>) ...)
(<break-test> <return-exp1> <return-exp2> ...)
<body> ...)
;; Becomes =>
(let ()
(define <var> <initial-val>) ...
(while ((not <break-test>) <return-exp1> <return-exp2> ...)
<body> ...
(set! <var> <update>) ...))
- Force the promise to run its expression via the
force
primitive! - Delayed expressions have
id
bound as their topmost continuation in CPS!
Possible Derivation Using lambda
:
- In practice, Heist actually supports native "delayed expressions" distinct from thunks!
(delay <exp>)
(force <promise>)
;; Becomes =>
(let ((already-run? #f) (result #f)) ; Memoized promises!
(lambda ()
(if already-run?
result
(begin
(set! already-run? #t)
(set! result <exp>)
result))))
(<promise>)
- Stream pairs are regular pairs with delayed
car
andcdr
! - Allows for infinite lists (see
scar
&scdr
primitives for manipulation)! - Note:
scons
is actually a macro directly defined in Heist Scheme!
Derivation Using delay
:
(scons <obj1> <obj2>)
;; Becomes =>
(cons (delay <obj1>) (delay <obj2>))
stream
is toscons
aslist
is tocons
!- Note:
stream
is actually a macro directly defined in Heist Scheme!
Derivation Using scons
:
(stream <obj1> <obj2> <obj3>)
;; Becomes =>
(scons <obj1> (scons <obj2> (scons <obj3> '())))
;; Generate all powers of 2!
(define (pows-of n (count 0))
(scons (expt n count)
(pows-of n (+ count 1))))
(define 2-pow
(let ((s (pows-of 2)))
(lambda ()
(define hd (scar s))
(set! s (scdr s))
hd)))
(do ((x 0 (+ x 1)))
((> x 24))
(display (2-pow)) ; 1 2 4 8 16 32 64 128 256 512 1024 ... 16777216
(newline))
;; Generate all Fibonacci numbers!
(define fibs (scons 0 (scons 1 (stream-map + fibs (scdr fibs)))))
(display (stream->list fibs 25)) ; (0 1 1 2 3 5 8 13 21 34 55 89 ... 46368)
;; Generate all primes!
(define (ints-from n)
(scons n (ints-from (+ n 1))))
(define (sieve ints)
(scons (scar ints)
(sieve (stream-filter \(not-zero? (remainder %1 (scar ints))) (scdr ints)))))
(define primes (sieve (ints-from 2)))
(display (stream->list primes 25)) ; (2 3 5 7 11 13 17 19 23 29 ... 97)
- Hence, like
#
,vector-literal
must be quoted to form a vector object!
'#(<obj1> <obj2> <obj3> ...)
;; Becomes =>
'(vector-literal <obj1> <obj2> <obj3> ...)
;; Becomes =>
(vector '<obj1> '<obj2> '<obj3> '...)
- Hence, like
$
,hmap-literal
must be quoted to form a hash-map object! - Keys ::=
symbol
|string
|number
|character
|boolean
'$(<key1> <val1> <key2> <val2> ...)
;; Becomes =>
'(hmap-literal <key1> <val1> <key2> <val2> ...)
;; Becomes =>
(hmap '<key1> '<val1> '<key2> '<val2> '...)
- Check for aliases via the
reader-alias?
primitive! - Get all current aliases via the
reader-alias-list
primitive!
(define-reader-alias <alias-symbol> <name-symbol>)
(define-reader-alias <alias-symbol-to-delete>)
(define-reader-alias a b)
(define-reader-alias b +)
(b 1 2 3) ; 6
(a 1 2 3) ; ERROR: VARIABLE b IS UNBOUND !!!
- Note: Run-Time macros are expanded at run-time, ie each time they're invoked!
- See
core-syntax
for an analysis-time macro alternative!
- See
- Note:
let-syntax
&letrec-syntax
are actually macros directly defined in Heist Scheme! - Note: See the Syntax Transformers section for more info on syntax transformers!
(define-syntax <label> <syntax-transformer>)
(let-syntax ((<label> <syntax-transformer>) ...) <body> ...)
(letrec-syntax ((<label> <syntax-transformer>) ...) <body> ...)
Derivation Using let
:
(let-syntax ((<label> <syntax-transformer>) ...) <body> ...)
(letrec-syntax ((<label> <syntax-transformer>) ...) <body> ...)
;; Both Become (letrec style macro evaluation is default) =>
(let ()
(define-syntax <label> <syntax-transformer>) ...
<body> ...)
(syntax-rules (<key> ...) <syntax-clause1> <syntax-clause2> ...))
<syntax-clause>
=(<pattern> <template>)
<pattern>
=(<any-symbol> <expression-to-match-against>)
<template>
=<expression-to-expand-into>
- Note: Literals &
<key>
s in patterns must be matched exactly to expand! - Note:
...
andsyntax-hash
are always reserved<key>
names! - Note: Use
*dot*
to alias the current(dot)
in expansions!
Heist Scheme's Powerful Macro System Enables Matching & Constructing Arbitrarily Complex Expressions!
- For Patterns:
<obj> ...
Matches 1 or more entities(<contents>) ...
Matches 1 or more expressions that match<contents>
- Note: Variadic Matches must accompany variadic expansions in the
<template>
!
- Note: Variadic Matches must accompany variadic expansions in the
- Examples:
a ... ; Matches 1+ arbitrary objects (a b) ... ; Matches 1+ pairs ((a b) (c d)) ... ; Matches 1+ pairs of pairs ((a ...) ...) ; Matches 1+ expressions of 1+ arbitrary objects
- For Templates:
<obj> ...
Expands 1 or more entities(<contents>) ...
Constructs 1 or more expressions with<contents>
- Note: Variadic Expansions must accompany variadic matches in the
<pattern>
! - Examples:
a ... ; Expands 1+ arbitrary objects (a b) ... ; Constructs 1+ pairs of variadic matches <a> & <b> ((a b) (c d)) ... ; Constructs 1+ pairs of pairs of variadic matches <a>, <b>, <c>, & <d> ((a ...) ...) ; Constructs 1+ expressions of 1+ variadic matches <a>
- Writing macros that expand to other macro definitions using
...
can cause
issues, however this can be mediated by escaping nested...
via\...
- Example:
(core-syntax define-inlined (syntax-rules () ((_ (name) b ...) (core-syntax name (syntax-rules () ((_) ((lambda () b ...)))))) ((_ (name a ...) b ...) (core-syntax name (syntax-rules () ((_ arg \...) ; escape the ... to be un-escaped upon expansion ((lambda (a ...) b ...) arg \...)))))))
- ONLY valid in
syntax-rules
templates! - Expander replaces
syntax-hash
expression, and every instance of<symbol>
,
with a hashed version of<symbol>
unique to the expansion instance!- Similar to
gensym
but specialized forsyntax-rules
!
- Similar to
;; Note the name conflict in the following:
;; The <a> gets expanded to <b>, but the expansion then reads that <b> as 10
;; due to the rebinding of <b> by <let>, thus the result is 20 and not 15
(define-syntax my-macro
(syntax-rules ()
((_ a)
(let ((b 10))
(+ a b))))) ; expands to (+ b b) => (+ 10 10)
(define b 5)
(write (my-macro b)) ; 20
;; We can resolve this by binding our <b> in the macro to a UNIQUE identifier.
;; We COULD solve this using <gensym>:
(define-syntax my-macro
(syntax-rules ()
((_ a)
(eval
`(let ((,(gensym) 10)) ; form the expression by splicing in a unique symbol,
(+ a ,(gensym 1))))))) ; then evaluate the expression in the local environment
(define b 5)
(write (my-macro b)) ; 15
;; HOWEVER, this is a tad verbose for our purposes. Enter <syntax-hash>:
;; a FAST alternative to <gensym> specialized ONLY for <syntax-rules> expansions!
;; => NOTE: we can use the "`@" reader macro to be even more concise!
(define-syntax my-macro
(syntax-rules ()
((_ a)
(let ((`@b 10)) ; `@b => (syntax-hash b) & binds <hashed-b> to 10
(+ a b))))) ; expands to (+ b <hashed-b>) => (+ 5 10)
(define b 5)
(write (my-macro b)) ; 15
- Note: See the Syntax Transformers section for more info on syntax transformers!
- Interpreter's
eval
seperates expression analysis (declaration) & execution (invocation):define-syntax
macros, bound to any environment, dynamically expand at run-time- Hence run-time macros in a
lambda
body are re-expanded upon every invocation!
- Hence run-time macros in a
core-syntax
macros, only bound to the global environment, expand at analysis-time
- BEST PRACTICE: use
core-syntax
in the GLOBAL SCOPE to avoid the below! - Heist reads, analyzes, and runs each expression individually
- Hence reading
(define (f) ...)
below means the entire expr is analyzed at once,
but themy-macro
core-syntax defn is only registered at run-time!- Hence
(my-macro 12)
is analyzed beforemy-macro
is defn'd as core-syntax!- Thus
(my-macro 12)
must be expanded at run-time instead of analysis-time!
- Thus
- However
(my-macro 13)
does expand at analysis-time, since(f)
triggered
my-macro
to be bound as core-syntax prior analyzing the(define (g) ...)
expr!
- Hence
(define (f)
(core-syntax my-macro ; BINDS my-macro TO THE GLOBAL ENV AS CORE-SYNTAX AT RUNTIME
(syntax-rules ()
((_ a) (* a 2))))
(my-macro 12)) ; EXPANDS AT RUNTIME SINCE my-macro ISN'T CORE-SYNTAX YET!
(f) ; RUN f TO REGISTER my-macro AS core-syntax IN THE GLOBAL ENV
(define (g) (my-macro 13)) ; EXPANDS AT ANALYSIS TIME
- Hence returns an unary procedure, accepting the "topmost" continuation!
- Enables use of
call/cc
,cps-eval
, &cps-load
primitives! - Automatically wraps entire program (& passed
id
) if-cps
cmd-line flag used! - Enables opt-in continuations for their benefits w/o their overhead when unused!
- Optimizes the cps transformation as well for reasonable speed!
- In general,
scm->cps
code at-O3
optimization runs as fast as its non-cps version would at-O0
- With CPS, avoid runtime-macros/eval/load expanding to a
define
in the current envrionment!- Lazy expansion breaks this functionality (may expand to localized bindings though!)
- May use analysis-time macros expanding to
define
s though (hencedefn
etc. are fine)!
- CPS procedures applied in non-CPS contexts have
id
bound as their continuation!
- Experimentally, go wild!
- For practical code, leave
scm->cps
to be used by libraries, & prefer specialized solutions
rather than homebrewed alternatives.- I.E. use
define-coroutine
and thejump!
/catch-jump
idiom rather than spinning
up your own versions via continuations.
- I.E. use
Coroutine Example Using call/cc
:
((scm->cps
(define (make-queue) (cons '() '()))
(define (enqueue! queue obj)
(let ((lobj (list obj)))
(if (null? (car queue))
(begin
(set-car! queue lobj)
(set-cdr! queue lobj))
(begin
(set-cdr! (cdr queue) lobj)
(set-cdr! queue lobj)))
(car queue)))
(define (dequeue! queue)
(let ((obj (caar queue)))
(set-car! queue (cdar queue))
obj))
;;;; coroutine
(define process-queue (make-queue))
(define (coroutine thunk)
(enqueue! process-queue thunk))
(define (start)
((dequeue! process-queue)))
(define (pause)
(call/cc
(lambda (k)
(coroutine (lambda () (k #f)))
(start))))
;;;; example prints alternating ints & chars
(coroutine (lambda ()
(let loop ((i 0))
(if (< i 26)
(begin
(display (+ 1 i)) ; print #
(display " ")
(pause) ; pause coroutine to print a char
(loop (+ 1 i)))))))
(coroutine (lambda ()
(let loop ((i 0))
(if (< i 26)
(begin
(display (integer->char (+ i 65))) ; print char
(display " ")
(pause) ; pause coroutine to print a #
(loop (+ 1 i)))))))
(newline)
(start)) id)
1 A 2 B 3 C 4 D 5 E 6 F 7 G 8 H 9 I 10 J 11 K 12 L 13 M 14 N 15 O 16 P 17 Q 18 R 19 S 20 T 21 U 22 V 23 W 24 X 25 Y 26 Z
- Identical to
quote
after transforming given code into CPS!
- Applications may have a peculiar tag in front of them, with non-cps arguments
- This is b/c Heist only knows if an application is a macro or callable at run-time!
- For callables, cps-transformation precedes execution!
- For macros, execution precedes cps-transformation (& re-execution)!
- Note:
curry
is actually a macro directly defined in Heist Scheme! - Enables trivial means to bind arguments to values (especially helps w/ lambda calculus)
- Note: it is undefined behavior to have a variadic
curry
lambda using.
!
(define K (curry (a b) a))
; The following invocations are identical!
((K 1) 2) ; Traditional LISP curried call works! ; => 1
(K 1 2) ; Nicer invocation interface also works! ; => 1
(define Id (curry (a) a))
(define KI (K Id)) ; Binds "Id" as the first arg to "K"!
((KI 1) 2) ; "Id" is selected, then 2 is passed to "Id"! ; => 2
(KI 1 2) ; => 2
- Note:
-<>
is actually a macro directly defined in Heist Scheme! - Note: Common Lisp's "Diamond Wand" inspired by Clojure's threading macros!
(display
(-<> (* 2 3)
(+ <> <>)
(* <> <>))) ; 144
Derivation Using lambda
:
(-<> (* 2 3)
(+ <> <>)
(* <> <>))
;; Becomes =>
((lambda (<>) (* <> <>))
((lambda (<>) (+ <> <>))
(* 2 3)))
Defclass
creates a class prototype (think JavaScript) from which Objects are made!
(defclass <class-name> (<optional-inherited-prototype>) <member-or-method-instances>)
=> <member-or-method-instance> ::= (<member-name> <default-value>)
| (<method-name> <procedure-value>)
| ((<method-name> <arg1> <arg2> ...) <body> ...)
|
| ((<class-name> <arg> ...) <body> ...) ; constructor
| (<class-name> ((<arg> ...) <body> ...) ...) ; fn constructor
|
| ((eq? <obj>) <body> ...) ; overload eq?
| ((eqv? <obj>) <body> ...) ; overload eqv?
| ((equal? <obj>) <body> ...) ; overload equal?
| ((self= <obj>) <body> ...) ; overload all the above
|
| ((write) <body> ...) ; overload write
| ((display) <body> ...) ; overload display
| ((pprint) <body> ...) ; overload pretty-print
| ((self->string) <body> ...) ; overload all the above
|
| ((self->type) <body> ...) ; overload typeof
|
| ((self->copy) <body> ...) ; overload copy
|
| ((self->procedure <arg> ...) <body> ...) ; overload application
- User-defined
<class-name>
ctor is optional, if undefined will be generated - Default values from class-prototypes are
deep-copied
to objects upon construction - Can dynamically add properties to prototypes, which all existing objects also get access to!
- Class Object Predicate
(<class-name>? <obj>)
is generated by default - Object member/method property setter method is generated by default:
(<object>.set-property! <property-name-symbol> <new-value>)
- This method is automatically invoked when using
set!
on an object property!(set! obj.name val)
=>(obj.set-property! (quote name) val)
- Object dynamic member/method property registration method is generated by default:
(<object>.add-property! <property-name-symbol> <default-value>)
- If member/method exists: sets value, else: adds it as a new property
- This method is automatically invoked when using
define
on an object property!(define obj.name val)
=>(obj.add-property! (quote name) val)
self
refers to the current invoking object (designed for use in methods).prototype
member returns the class prototype of the object.super
member returns object's underlying inherited object (returns#f
if dne)- The
.super
property can only beset!
to object or#f
values!- If
set!
to an object, the object must have the same.prototype
as the original.super
value!
- If
- The
By default, "super objects" in an inheritance chain will only be created by using their class' default
constructor. However, user-defined constructors of the super class may still be used to initialize super
objects via the super
special form (only works in class methods).
Suppose you had a "Square" class that inherits the "Rectangle" class:
(defclass Rectangle ()
((Rectangle (width 0) (height 0))
(define self.width width)
(define self.height height))
((area)
(* self.width self.height))
((perimeter)
(* 2 (+ self.width self.height))))
(defclass Square (Rectangle)
((Square (len 0))
(super len len))) ; invoke the user-defined ctor to create the super "Rectangle" object
- Equality:
self=
method will attempt to be invoked on objects foreq?
,eqv?
,equal?
- Printing:
self->string
method will attempt to be invoked on objects fordisplay
,write
,pprint
- Typeof:
self->type
method will attempt to be invoked on objects fortypeof
- Method should accept 0 arguments, and by convention return a symbol!
- Copying:
self->copy
method will attempt to be invoked on objects forcopy
- Method should accept 0 arguments, and by convention return a new object!
- Unlike the above methods,
self->copy
is NOT inherited by default!
- The
self->procedure
method will automatically be called on any object applied as a procedure!- Think
operator()()
in C++! - Check out the primitive
functor?
predicate! - Convert functors to procedures via the
functor->procedure
primitive!
- Think
- Similar to C++'s
this
,self
is implicitly passed as a method argument upon invocation - Unlike C++, object members must be referenced via
self.<member>
in methods- Enables methods to also reference external variables with members' names
- Passed by reference (as are strings, pairs, vectors, and hash-maps)
- May be deep-copied via
copy
& shallow-copied viashallow-copy
- May be deep-copied via
- Traditional OOP Access, Member:
person.name
, Method:(person.greet <friend's name>)
(defclass node ()
(left '())
(right '())
(val 0)
((leaf?)
(and (null? self.left) (null? self.right))))
(define root (node))
(set! root.left (node))
(set! root.left.val 42)
(display root.val) ; 0
(newline)
(display root.left.val) ; 42
(newline)
(display (root.leaf?)) ; #f
(newline)
(display (root.left.leaf?)) ; #t
- Overloads
equal?
for structural equality against other anonymous objects! - Note:
new
is actually a macro directly defined in Heist Scheme!
- Note:
define-coroutine
is actually a macro directly defined in Heist Scheme!
- Re-invoking
(<co-name>)
will return a newcoroutine
object instance! - Hence
<co-name>
should not be called recursively internally, rather use
the named-let construct in order to perform recursive operations!
- Creation: Either from invoking
(<co-name>)
oryield
in a coroutine - 2 Properties,
.value
member &.next
method:.value
: yielded value (#f
if object isn't from ayield
).next
: either starts or continues the coroutine's execution
(yield <value>)
: yield a value from the coroutine via a new coroutine object!(yield)
is equivalent to(yield #f)
, designed for use withcycle-coroutines!
- Nesting
define-coroutine
instances (or use inscm->cps
) is undefined behavior! - Using
jump!
orcatch-jump
indefine-coroutine
is undefined behavior (used byyield
)! - The
id
procedure is returned if no expressions exist after the lastyield
! - Like
scm->cps
, avoid runtime-macros/eval/load expanding to adefine
in the current environment!
;; Having 2 coroutines alternate until one completes (similar to the scm->cps example)!
(define-coroutine (print-ints)
(let loop ((count 0))
(display count)
(display #\space)
(yield)
(if (< count 25)
(loop (+ count 1)))))
(define-coroutine (print-chars)
(let loop ((count 0))
(display (integer->char (+ 65 count)))
(display #\space)
(yield)
(if (< count 25)
(loop (+ count 1)))))
(cycle-coroutines! (print-ints) (print-chars)) ; 0 A 1 B 2 C ... 25 Z
;; Create a generator thunk to iterate over all powers of 2!
(define-coroutine (all-pows-of-2)
(let loop ((count 0))
(yield (expt 2 count))
(loop (+ count 1))))
(define 2-pow (coroutine->generator (all-pows-of-2)))
(display (2-pow)) ; 1
(display (2-pow)) ; 2
(display (2-pow)) ; 4
(display (2-pow)) ; 8
;; Step through a coroutine using coroutine objects!
(define-coroutine (example)
(yield 1)
(yield 2)
(yield 3)
4)
(define cobj (example))
(set! cobj (cobj.next)) ; launch coroutine
(display cobj.value) ; 1
(set! cobj (cobj.next))
(display cobj.value) ; 2
(set! cobj (cobj.next))
(display cobj.value) ; 3
(set! cobj (cobj.next)) ; last iteration returns the final value!
(display cobj) ; 4
- Note:
define-module
is actually a macro directly defined in Heist Scheme! - Note: Expose variables/macros by defining them outside of the module body!
;; ANONYMOUS MODULE: procedures are directly exposed
(define-module (greet set-age! set-name!)
(define name "") ; hidden (variable's in the module)!
(define age 0) ; hidden (variable's in the module)!
(define (increment-value is-name? val) ; hidden (procedure not exposed)!
(if is-name? (set! name val) (set! age val)))
(define (set-age! a) (increment-value #f a)) ; exposed procedure!
(define (set-name! n) (increment-value #t n)) ; exposed procedure!
(define (greet) ; exposed procedure!
(displayf "Hello! My name is %s and I'm %n years old!" name age)))
(set-name! "Jordan")
(set-age! 21)
(greet) ; Hello! My name is Jordan and I'm 21 years old!
;; NAMED MODULE: exposed procedures are members of a "module" object!
(define-module Person (greet set-age! set-name!)
(define name "") ; hidden (variable's in the module)!
(define age 0) ; hidden (variable's in the module)!
(define (increment-value is-name? val) ; hidden (procedure not exposed)!
(if is-name? (set! name val) (set! age val)))
(define (set-age! a) (increment-value #f a)) ; exposed procedure!
(define (set-name! n) (increment-value #t n)) ; exposed procedure!
(define (greet) ; exposed procedure!
(displayf "Hello! My name is %s and I'm %n years old!" name age)))
(Person.set-name! "Jordan")
(Person.set-age! 21)
(Person.greet) ; Hello! My name is Jordan and I'm 21 years old!
- Note:
define-overload
is actually a macro directly defined in Heist Scheme!
- Access the original overloaded procedure version via
*original*
! - Use
else
as a catch-all predicate!
(define-overload <
(string? string<?)
(char? char<?)
(else *original*)) ; use <else> to catch all cases!
(define-overload >
(number? *original*) ; reference original > via *original*
(string? string>?)
(char? char>?))
(define-overload =
(number? *original*)
(else equal?))
(define-overload +
(number? *original*)
(char? string)
(seq? append)
(hmap? hmap-merge))
- Note: use
infix!
for left-associativity &infixr!
for right-associativity! - Note: converted to prefix notation by the reader!
- Inspired by Standard ML!
(infix! <integer-literal> <symbol1> ...)
,(infixr! <integer-literal> <symbol1> ...)
- Define operators
<symbol1> ...
with<integer-literal>
precedence!
- Define operators
(infix! <symbol1> ...)
,(infixr! <symbol1> ...)
- Returns precedence level if
<symbol1> ...
are operators, else returns#f
- Returns precedence level if
- Force precedence via
{}
(like()
's use in most programming languages)! - Escape infix operators from prefix conversion via
#!
prefix (rm'd by reader)! - Prefix/postfix operators are ignored (presumed intentionally placed)!
(define :: cons)
(define @ append)
(infixr! 5 :: @)
(defn qsort
((()) '())
(((x . xs))
(qsort (filter (>= x) xs)) @
x :: (qsort (filter (< x) xs))))
(display (qsort '(1 3 5 7 2 4 6 8))) ; (1 2 3 4 5 6 7 8)
(define ** expt)
(define %% modulo)
(define % remainder)
(define // quotient)
(define != (compose not =))
(infixr! 8 **)
(infix! 7 * / // %% %)
(infix! 6 + -)
(infix! 4 > < >= <= = !=)
(display 10 + 2 ** 5) ; 42
(display {10 + 2} ** 5) ; 248832 ; PRECEDENCE FORCED VIA "{}"
; (display (map + '(1 2) '(3 4)))) ; ERROR, READS: ((+ map '(1 2)) '(4 5))
(display (map #!+ '(1 2) '(3 4))) ; OK: ESCAPED "+" AVOIDS INFIX CONVERSION
- Make sure to escape the operators with the
#!
prefix to prevent reader conversions!
(infixr! 5 compose)
(display (list even? compose length)) ; (#<procedure>)
(unfix! #!compose)
(display (list even? compose length)) ; (#<procedure even?> #<procedure compose> #<procedure length>)
(define :: cons)
(define @ append)
(infixr! 5 :: @)
(unfix! :: @) ; BAD => Reader infix-conversions means this becomes ((:: unfix! @))
(unfix! #!:: #!@) ; GOOD => "#!" reader symbol prefix will prevent operator infix-conversions
-
True & False:
#t
,#f
-
Flonum Precision:
fl-precision
- Bound to
LDBL_DIG
from#include <cfloat>
- Bound to
-
Min & Max Flonum Values:
fl-min
,fl-max
fl-max
bound toLDBL_MAX
from#include <cfloat>
fl-min
bound toLDBL_TRUE_MIN
if exists, elseLDBL_MIN
- Either option from
#include <cfloat>
- Either option from
-
Flonum Epsilon Value:
fl-epsilon
- Bound to
LDBL_EPSILON
from#include <cfloat>
- Represents the smallest
x
so1.0 + x != 1.0
- Bound to
-
The Empty Stream:
stream-null
(equivalent to'()
) -
Min & Max Infix Operator Precedences:
*min-infix-precedence*
,*max-infix-precedence*
- Bound to
LLONG_MIN
&LLONG_MAX
from#include <climits>
- Bound to
-
Optional Environment Arg Flags for
Eval
,Load
,Cps-Eval
,Cps-Load
:- Null Environment, all effects are sandboxed:
*null-environment*
- Local Environment, using local bindings:
*local-environment*
- Global Environment, using global bindings:
*global-environment*
- Null Environment, all effects are sandboxed:
-
Argc & Argv:
*argc*
,*argv*
- Interpreted Scripts: passed at the cmd-line after the script name
- Compiled Script: passed to the executable of the compiled C++ file
-
EXIT_SUCCESS & EXIT_FAILURE:
*exit-success*
,*exit-failure*
- Designed to be used in conjunction with
exit
- Designed to be used in conjunction with
-
General Current Platform Name:
*heist-platform*
- Possible results:
'windows
|'apple
|'linux
|'unix
|'posix
|'unknown
- Possible results:
-
Specific Current Platform Name:
*heist-exact-platform*
- Possible results:
'windows-64
|'windows-32
'apple-ios-simulator
|'apple-ios
|'apple-osx
|'apple
'linux
|'unix
|'posix
'unknown
- Possible results:
-
Get Heist Interpreter Directory:
*heist-dirname*
- String to the Heist-Scheme interpreter's directory
- IE
(map even?)
is equivalent to(lambda (x . xs) (apply map (cons even? (cons x xs))))
- Query a Heist Scheme Feature:
(help <optional-query-string-or-symbol>)
- Nullary invocation (w/o arguments) launches the interactive help menu!
-
License:
(license)
-
Sublime Text Build System:
(sublime-text-build-system)
-
Shell Alias:
(shell-alias)
-
Addition: Add n numbers
(+ <number1> <number2> ...)
-
Subtraction: Subtract n numbers, or negate 1 number
(- <number1> <number2> ...)
(- <number>)
-
Multiplication: Multiply n numbers
(* <number1> <number2> ...)
-
Division: Divide n numbers, or invert 1 number
(/ <number1> <number2> ...)
(/ <number>)
-
Equality Comparisons:
(= <number1> <number2> ...)
(< <real1> <real2> ...)
(> <real1> <real2> ...)
(<= <real1> <real2> ...)
(>= <real1> <real2> ...)
-
Absolute Value:
(abs <real>)
-
Exponentiation: Exponentiate n numbers
(expt <number1> <number2> ...)
- As in math, exponentiation is right associative!
-
Exponentiation Modulo: Raise
<real1>
to the power of<real2>
modulo<real3>
(expt-mod <real1> <real2> <real3>)
-
Maximum: Get the maximum value
(max <real1> <real2> ...)
-
Minimum: Get the minimum value
(min <real1> <real2> ...)
-
Quotient: Get the quotient of
(/ <real1> <real2>)
(quotient <real1> <real2>)
-
Remainder: Get the remainder of
(/ <real1> <real2>)
(remainder <real1> <real2>)
-
Divmod: Get a pair with the quotient and remainder of
<real1>
&<real2>
(divmod <real1> <real2>)
-
Modulo:
(modulo <real1> <real2>)
-
Modulo Flonum: Get a pair with the integral & fractional portions of
<flonum>
(modf <flonum>)
-
Exponent: Get e raised to the power of
<number>
(exp <number>)
-
Logarithm:
(log <number> <optional-base>)
- Defaults to the natural logarithm!
-
Square Root:
(sqrt <number>)
-
Greatest Common Denominator:
(gcd <real1> <real2>)
-
Least Common Multiple:
(lcm <real1> <real2>)
-
nPr:
(npr <real1> <real2>)
-
nCr:
(ncr <real1> <real2>)
-
Extract Number's Numerator:
(numerator <real>)
-
Extract Number's Denominator:
(denominator <real>)
-
Generate a Log Procedure of a Certain Base:
(make-log-base <real>)
-
Psuedo-Random Number Generator: Seeded or unseeded
(random)
,(random <real-seed>)
-
Coerce Inexact to Exact:
(inexact->exact <number>)
-
Coerce Exact to Inexact:
(exact->inexact <number>)
-
Odd Predicate:
(odd? <integer>)
-
Even Predicate:
(even? <integer>)
-
Positive Predicate:
(positive? <real>)
,(not-positive? <real>)
-
Negative Predicate:
(negative? <real>)
,(not-negative? <real>)
-
Zero Predicate:
(zero? <number>)
,(not-zero? <number>)
-
Infinite Predicate:
(infinite? <real>)
-
Finite Predicate:
(finite? <real>)
-
NaN Predicate:
(nan? <real>)
-
Exact Number Predicate:
(exact? <number>)
-
Inexact Number Predicate:
(inexact? <number>)
-
Integer Predicate:
(integer? <number>)
-
Big-Integer Predicate:
(bigint? <number>)
- Equivalent to
(and (exact? <number>) (integer? <number>))
- Equivalent to
-
Round Number Up to Nearest Integer:
(ceiling <real> <optional-real-precision>)
-
Round Number Down to Nearest Integer:
(floor <real> <optional-real-precision>)
-
Round Number Towards Zero:
(truncate <real> <optional-real-precision>)
-
Round Number:
(round <real> <optional-real-precision>)
-
Regular:
(sin <number>)
,(cos <number>)
,(tan <number>)
-
Inverse:
(asin <number>)
,(acos <number>)
,(atan <number>)
,(atan <real1> <real2>)
-
Hyperbolic:
(sinh <number>)
,(cosh <number>)
,(tanh <number>)
-
Inverse Hyperbolic:
(asinh <number>)
,(acosh <number>)
,(atanh <number>)
-
And:
(logand <real1> <real2>)
-
Or:
(logor <real1> <real2>)
-
Xor:
(logxor <real1> <real2>)
-
Not:
(lognot <real>)
-
Logical Shift Left:
(loglsl <real> <shift-amount>)
-
Logical Shift Right:
(loglsr <real> <shift-amount>)
-
Arithmetic Shift Right:
(logasr <real> <shift-amount>)
-
Confirm Nth Bit is 1:
(logbit? <real> <n>)
-
Set Nth Bit to 1:
(logbit1 <real> <n>)
-
Set Nth Bit to 0:
(logbit0 <real> <n>)
-
Complement Nth Bit:
(logbit~ <real> <n>)
- Generate:
(make-rectangular <real-real> <real-imag>)
- Generate from polar values:
(make-polar <real-magnitude> <real-angle>)
- Get real part:
(real-part <number>)
- Get imaginary part:
(imag-part <number>)
- Get polar magnitude:
(magnitude <number>)
- Get polar angle:
(angle <number>)
- Get conjugate:
(conjugate <number>)
-
Shallow Equality (pointer comparisons):
(eq? <obj1> <obj2> ...)
- Generally:
(eq? <item> <item>) ; #t (eq? <item> (shallow-copy <item>)) ; #f (eq? <item> (copy <item>)) ; #f
- Generally:
-
Equivalency (structural comparisons):
(eqv? <obj1> <obj2> ...)
- Compares items in containers using
eq?
- Generally:
(eqv? <item> <item>) ; #t (eqv? <item> (shallow-copy <item>)) ; #t (eqv? <item> (copy <item>)) ; #f
- Compares items in containers using
-
Deep Equality (recursive comparisons):
(equal? <obj1> <obj2> ...)
- Generally:
(equal? <item> <item>) ; #t (equal? <item> (shallow-copy <item>)) ; #t (equal? <item> (copy <item>)) ; #t
- Generally:
-
Boolean Not:
(not <obj>)
-
Alphabetic Predicate:
(char-alphabetic? <char>)
-
Numeric Predicate:
(char-numeric? <char>)
-
Whitespace Predicate:
(char-whitespace? <char>)
-
Uppercase Predicate:
(char-upper-case? <char>)
-
Lowercase Predicate:
(char-lower-case? <char>)
-
Alphanumeric Predicate:
(char-alphanumeric? <char>)
-
Control Predicate:
(char-control? <char>)
-
Printable Predicate:
(char-print? <char>)
-
Graphical Predicate:
(char-graph? <char>)
-
Punctuation Predicate:
(char-punctuation? <char>)
-
Hexadecimal Digit Predicate:
(char-xdigit? <char>)
-
Convert to Uppercase:
(char-upcase <char>)
-
Convert to Lowercase:
(char-downcase <char>)
- Get EOF Character:
(eof)
-
Character Equality:
(char=? <char1> <char2> ...)
(char<? <char1> <char2> ...)
(char>? <char1> <char2> ...)
(char<=? <char1> <char2> ...)
(char>=? <char1> <char2> ...)
-
Case-Insensitive Character Equality:
(char-ci=? <char1> <char2> ...)
(char-ci<? <char1> <char2> ...)
(char-ci>? <char1> <char2> ...)
(char-ci<=? <char1> <char2> ...)
(char-ci>=? <char1> <char2> ...)
-
Construction: Creates a string of length
<size>
(make-string <size> <optional-fill-char>)
- Note:
<optional-fill-char>
defaults to#\?
-
Construction:
(string <char-or-string1> <char-or-string2> ...)
-
Unfold: Form a string by mapping & incrementing seed, until
<break-condition>
is true(string-unfold <break-condition> <map-callable> <successor-callable> <seed>)
- Note: map via
<map-callable>
, increment via<successor-callable>
-
Unfold Right: Form a string by mapping right & incrementing seed, until
<break-condition>
is true(string-unfold-right <break-condition> <map-callable> <successor-callable> <seed>)
- Note: map via
<map-callable>
, increment via<successor-callable>
-
Character Padding Left of String: pads
<length>
characters,<character>
defaults to#\space
(string-pad <string> <length> <optional-character>)
-
Character Padding Right of String: pads
<length>
characters,<character>
defaults to#\space
(string-pad-right <string> <length> <optional-character>)
-
Character Trimming Left of String: trims characters while
<predicate?>
is true(string-trim <string> <optional-predicate?>)
- Note:
<predicate?>
defaults tochar-whitespace?
-
Character Trimming Right of String: trims characters while
<predicate?>
is true(string-trim-right <string> <optional-predicate?>)
- Note:
<predicate?>
defaults tochar-whitespace?
-
Character Trimming Left & Right of String: trims characters while
<predicate?>
is true(string-trim-both <string> <optional-predicate?>)
- Note:
<predicate?>
defaults tochar-whitespace?
-
Replacement: Replace
<string1>
between indices<start-index>
&<end-index>
with<string2>
(string-replace <string1> <string2> <start-index> <end-index>)
- See
regex-replace
®ex-replace-all
for a regex-based alternative!
-
String Contains Substring (From Left): Get index of 1st instance
(string-contains <string> <sub-string>)
- Use
string-contains-ci
for a case-insensitive alternative! - Returns
#f
is<sub-string>
isn't in<string>
!
-
String Contains Substring (From Right): Get index of last instance
(string-contains-right <string> <sub-string>)
- Use
string-contains-right-ci
for a case-insensitive alternative! - Returns
#f
is<sub-string>
isn't in<string>
!
-
Join a List of Strings Into 1 String:
(string-join <string-list> <optional-string-delimiter> <optional-grammar>)
<optional-grammar> = 'infix | 'suffix | 'prefix
- Note:
<optional-string-delimiter>
defaults to""
- Note:
<optional-grammar>
defaults to'infix
-
Split String Into a List of Substrings:
(string-split <target-string> <optional-string-delimiter> <optional-start-index>)
- Note:
<string-delimiter>
defaults to""
- Note:
<optional-start-index>
defaults to0
- Enables splitting with delimiters using regex-significant chars more easily!
- See
regex-split
for a regex-based alternative!
- See
-
Swap String Pointers:
(string-swap! <string1> <string2>)
-
Mutating Push-Back Character to String:
(string-push-back! <string> <char>)
-
Mutating Push-Front Character to String:
(string-push-front! <string> <char>)
-
Mutating Pop-Back Character from String:
(string-pop-back! <string>)
-
Mutating Pop-Front Character from String:
(string-pop-front! <string>)
-
Confirm String is Empty:
(string-empty? <string>)
-
Copy String: Copy
<source-string>
to<target-string>
from<target-start-idx>
(string-copy! <target-string> <target-start-idx> <source-string>)
-
String Equality:
(string=? <string1> <string2> ...)
(string<? <string1> <string2> ...)
(string>? <string1> <string2> ...)
(string<=? <string1> <string2> ...)
(string>=? <string1> <string2> ...)
-
Case-Insensitive String Equality:
(string-ci=? <string1> <string2> ...)
(string-ci<? <string1> <string2> ...)
(string-ci>? <string1> <string2> ...)
(string-ci<=? <string1> <string2> ...)
(string-ci>=? <string1> <string2> ...)
Regex: (uses ECMAScript Syntax)
-
Replace 1st Regex Instance:
(regex-replace <target-string> <regex-string> <replacement-string>)
(regex-replace <target-string> <regex-string> <callable>)
<callable> ::= (lambda (<prefix>, <suffix>, <match1>, ...) <body>)
<callable>
must return a string to replace the match!
-
Replace All Regex Instances:
(regex-replace-all <target-string> <regex-string> <replacement-string>)
(regex-replace-all <target-string> <regex-string> <callable>)
<callable> ::= (lambda (<prefix>, <suffix>, <match1>, ...) <body>)
<callable>
must return a string to replace the match!
-
Get Alist of All Regex Matches:
(regex-match <target-string> <regex-string>)
- Returned alist's sublists have the position & match substring instance!
- If
<regex-string>
has multiple substrings per match, becomes a 2nd order alist!
-
Regex Split String Into a List of Substrings:
(regex-split <target-string> <optional-regex-string> <optional-start-index>)
<optional-regex-string>
defaults to""
to split into char-strings<optional-start-index>
defaults to0
-
Construct Pair:
(cons <obj1> <obj2>)
-
List Access:
car
= first of pair,cdr
= second of pair, & composedcar
&cdr
(car <pair>)
,(cdr <pair>)
(caar <pair>)
,(cadr <pair>)
,(cdar <pair>)
,(cddr <pair>)
(caaar <pair>)
...(cdddr <pair>)
(caaaar <pair>)
...(cddddr <pair>)
-
First/Second Setters:
(set-car! <pair> <obj>)
,(set-cdr! <pair> <obj>)
-
Last Pair In List:
(last-pair <non-empty-list>)
-
Swap 2 Pairs:
(pair-swap! <pair1> <pair2>)
-
Construct List (1):
(make-list <size> <fill-value>)
-
Construct List (2):
(list <obj1> <obj2> ...)
-
Construct Dotted List:
(list* <obj1> <obj2> ...)
-
Construct Circular List:
(circular-list <obj1> <obj2> ...)
-
Generate Numeric List: Generate
<count>
objects, from<start>
& incrementing w/<step>
<optional-start-number>
defaults to0
<optional-step-number>
defaults to1
(iota <count> <optional-start-number> <optional-step-number>)
-
Unfold: Form a list by mapping & incrementing seed, until
<break-condition>
is true- Note: map via
<map-callable>
, increment via<successor-callable>
(unfold <break-condition> <map-callable> <successor-callable> <seed>)
- Note: map via
-
Unfold Right: Form a list by mapping right & incrementing seed, until
<break-condition>
is true- Note: map via
<map-callable>
, increment via<successor-callable>
(unfold-right <break-condition> <map-callable> <successor-callable> <seed>)
- Note: map via
-
Get All Combinations:
(get-all-combinations <list>)
-
Empty List Predicate:
(null? <obj>)
-
List Predicate:
(list? <obj>)
-
Dotted List Predicate:
(list*? <obj>)
-
Circular List Predicate:
(circular-list? <obj>)
-
Associative List Predicate:
(alist? <obj>)
-
(Lists) Get Sublist Beginning w/ an Object If Present (
#f
Otherwise):- Seek using
eq?
:(memq <obj> <list>)
- Seek using
eqv?
:(memv <obj> <list>)
- Seek using
equal?
:(member <obj> <list>)
- Seek using
-
(Associative Lists) Get Pair Beginning w/ a Key If Present (
#f
Otherwise):- Seek using
eq?
:(assq <obj> <alist>)
- Seek using
eqv?
:(assv <obj> <alist>)
- Seek using
equal?
:(assoc <obj> <alist>)
- Seek using
-
Construct Vector (1):
(make-vector <size> <fill-value>)
-
Construct Vector (2):
(vector <obj1> <obj2> ...)
-
Mutating Push-Back Object to Vector:
(vector-push-back! <vector> <obj>)
-
Mutating Push-Front Object to Vector:
(vector-push-front! <vector> <obj>)
-
Mutating Pop-Back Object from Vector:
(vector-pop-back! <vector>)
-
Mutating Pop-Front Object from Vector:
(vector-pop-front! <vector>)
-
Generate Numeric Vector: Generate
<count>
objects, from<start>
& incrementing w/<step>
<optional-start-number>
defaults to0
<optional-step-number>
defaults to1
(vector-iota <count> <optional-start-number> <optional-step-number>)
-
Unfold: Form a vector by mapping & incrementing seed, until
<break-condition>
is true- Note: map via
<map-callable>
, increment via<successor-callable>
(vector-unfold <break-condition> <map-callable> <successor-callable> <seed>)
- Note: map via
-
Unfold Right: Form a vector by mapping right & incrementing seed, until
<break-condition>
is true- Note: map via
<map-callable>
, increment via<successor-callable>
(vector-unfold-right <break-condition> <map-callable> <successor-callable> <seed>)
- Note: map via
-
Grow a Vector: Generate a new vector w/ same elts and new size
(vector-grow <vector> <size>)
-
Empty Vector Predicate:
(vector-empty? <vector>)
-
Copy Vector: Copy
<source-vector>
to<target-vector>
from<target-start-idx>
(vector-copy! <target-vector> <target-start-idx> <source-vector>)
-
Swap Vector Pointers:
(vector-swap! <vector1> <vector2>)
-
Vector Binary Search:
(vector-binary-search <vector> <value> <3-way-comparison>)
- Suppose values a & b:
- a < b:
(<3-way-comparison> a b)
< 0 - a = b:
(<3-way-comparison> a b)
= 0 - a > b:
(<3-way-comparison> a b)
> 0
- a < b:
- Suppose values a & b:
-
Get All Combinations:
(vector-get-all-combinations <vector>)
-
Constructor:
(hmap <key1> <value1> <key2> <value2> ...)
-
Extract Key List:
(hmap-keys <hash-map>)
-
Extract Value List:
(hmap-vals <hash-map>)
-
Determine if Key in Hash-Map:
(hmap-key? <hash-map> <key>)
-
Determine if Viable Key Type:
(hmap-hashable? <obj>)
-
Access Value:
(hmap-ref <hash-map> <key>)
-
Set/Create Association:
(hmap-set! <hash-map> <key> <value>)
-
Delete Association:
(hmap-delete! <hash-map> <key>)
-
Total Entries:
(hmap-length <hash-map>)
-
Empty? Predicate:
(hmap-empty? <hash-map>)
-
Merge Hash-Maps into a New Copy:
(hmap-merge <hash-map-1> <hash-map-2> ...)
- Note: keys of hmaps on the left take precedence over those on the right!
-
Merge
<hash-map-2> ...
into<hash-map-1>
:(hmap-merge! <hash-map-1> <hash-map-2> ...)
- Note: keys of hmaps on the left take precedence over those on the right!
-
Iterate Over Key-Value Pairs:
(hmap-for-each <callable> <hash-map>)
-
Iterate Over Keys:
(hmap-for-each-key <callable> <hash-map>)
-
Iterate Over Values:
(hmap-for-each-val <callable> <hash-map>)
-
Map Callable Over Values Making a New Hash-Map:
(hmap-map <callable> <hash-map>)
-
Mutative Map Callable Over Values:
(hmap-map! <callable> <hash-map>)
-
Generate Empty Variant of Sequence:
(empty <sequence>)
-
Get Sequence Length:
(length <sequence>)
-
Get Sequence Length (
#f
If a Circular List):(length+ <sequence>)
-
Get Reverse of Sequence:
(reverse <sequence>)
-
Mutating Reverse Sequence:
(reverse! <sequence>)
-
Fold: Accumulate sequence from left to right, starting with
<seed>
using<callable>
(fold <callable> <seed> <sequence1> <sequence2> ...)
-
Fold Right: Accumulate sequence from right to left, starting with
<seed>
using<callable>
(fold-right <callable> <seed> <sequence1> <sequence2> ...)
-
Map: Apply
<callable>
to each elt in each sequence, forming a sequence of results(map <callable> <sequence1> <sequence2> ...)
-
Mutating Map: Apply
<callable>
to each elt in each sequence, mapping on the 1st sequence(map! <callable> <sequence1> <sequence2> ...)
-
Filter: Form a sequence of elts from
<sequence>
satisfying<predicate?>
(filter <predicate?> <sequence>)
-
For Each: Apply
<callable>
to each elt of each<sequence>
(for-each <callable> <sequence1> <sequence2> ...)
-
Mutating Copy: Copy
<source-sequence>
to<dest-sequence>
(seq-copy! <dest-sequence> <source-sequence>)
-
Count Elts With a Property:
(count <predicate?> <sequence>)
-
Get Elt at an Index:
(ref <sequence> <index>)
-
Get Subsequence:
(slice <sequence> <start-index> <optional-length>)
<optional-length>
defaults to the end of<sequence>
if not included!- Negative
<optional-length>
denotes offset from the end of the sequence!
-
Set Elt at an Index:
(set-index! <sequence> <index> <obj>)
-
Swap Elts at 2 Indices:
(swap-indices! <sequence> <index> <index>)
-
Fill Sequence:
(fill! <sequence> <fill-value>)
-
Append:
(append <sequence1> ... <sequenceN> <obj>)
-
Remove:
(remove <predicate?> <sequence>)
-
Remove First:
(remove-first <predicate?> <sequence>)
-
Remove Last:
(remove-last <predicate?> <sequence>)
-
Delete an Elt:
(delete <sequence> <index>)
-
Get Last Elt:
(last <sequence>)
-
Get All Except Head:
(tail <sequence>)
-
Get First Elt:
(head <sequence>)
-
Get All Except Last:
(init <sequence>)
-
Compare Elts of Sequences:
(seq= <predicate?> <sequence1> <sequence2> ...)
-
Get 1st Elt After
<predicate?>
is True:(skip <predicate?> <sequence>)
-
Get Last Elt After
<predicate?>
is True:(skip-right <predicate?> <sequence>)
-
Get Index of 1st Elt Satisfying
<predicate?>
:(index <predicate?> <sequence>)
-
Get Index of Last Elt Satisfying
<predicate?>
:(index-right <predicate?> <sequence>)
-
Drop
<length>
Elts From Left:(drop <sequence> <length>)
-
Drop
<length>
Elts From Right:(drop-right <sequence> <length>)
-
Take
<length>
Elts From Left:(take <sequence> <length>)
-
Take
<length>
Elts From Right:(take-right <sequence> <length>)
-
Drop Elts While
<predicate?>
From Left:(drop-while <predicate?> <sequence>)
-
Drop Elts While
<predicate?>
From Right:(drop-right-while <predicate?> <sequence>)
-
Take Elts While
<predicate?>
From Left:(take-while <predicate?> <sequence>)
-
Take Elts While
<predicate?>
From Right:(take-right-while <predicate?> <sequence>)
-
Confirm Any Sequence Satisfies
<predicate?>
:(any <predicate?> <sequence1> <sequence2> ...)
-
Confirm All Sequences Satisfy
<predicate?>
:(every <predicate?> <sequence1> <sequence2> ...)
-
Generic
cons
:cons
for lists, a copyingpush-back
for strings & vectors(conj <obj> <sequence>)
-
Coerce to List:
(seq->list <sequence>)
-
Coerce to Vector:
(seq->vector <sequence>)
-
Coerce to String:
(seq->string <sequence>)
-
Union:
(union <elt=?> <sequence1> <sequence2> ...)
-
Intersection:
(intersection <elt=?> <sequence1> <sequence2> ...)
-
Difference:
(difference <elt=?> <sequence1> <sequence2> ...)
-
Symmetric Difference:
(symmetric-difference <elt=?> <sequence1> <sequence2> ...)
-
Sort:
(sort <predicate?> <sequence>)
-
Mutating Sort:
(sort! <predicate?> <sequence>)
-
Confirm Sequence is Sorted:
(sorted? <predicate?> <sequence>)
-
Merge 2 Sequences Sorted With
<predicate?>
:(merge <predicate?> <sequence1> <sequence2>)
-
Delete Neighboring Duplicates:
(delete-neighbor-dups <elt=?> <sequence>)
-
Mutating Delete Neighboring Duplicates:
(delete-neighbor-dups! <elt=?> <sequence>)
-
Functional Property Access:
(.. <object> <property-symbol-1> ...)
- IE
person.sibling.age
=(.. person 'sibling 'age)
- IE
-
Object Members Hash-Map:
(object-members <object>)
- Returns a
hash-map
of member names & values
- Returns a
-
Object Methods Hash-Map:
(object-methods <object>)
- Returns a
hash-map
of method names & values - Method values already have
<object>
bound asself
!
- Returns a
-
Class Name:
(proto-name <class-prototype>)
-
Prototype Member Names List:
(proto-members <class-prototype>)
-
Prototype Method Names List:
(proto-methods <class-prototype>)
-
Inherited Prototype:
(proto-super <class-prototype>)
-
Dynamically Add New Property:
(proto-add-property! <class-prototype> <property-name-symbol> <value>)
-
Coroutine Object Predicate:
(coroutine? <obj>)
- Coroutine objects can only be made by coroutine instantiations or
yield
- Coroutine objects can only be made by coroutine instantiations or
-
Convert Coroutine Object to a Generator Thunk:
(coroutine->generator <coroutine-object>)
- Invoking the generator will continuously yield the next
yield
ed value - Yields the
'generator-complete
symbol once finished iterating the coroutine!
- Invoking the generator will continuously yield the next
-
Cyclical Coroutine Invocation:
(cycle-coroutines! <coroutine-object-1> ...)
- TAKE HEED: if none of the coroutines ever finish, neither will this procedure!
- Invokes first coroutine until yields, then invokes next, and so on until wraps around
- Returns the first non-coroutine-object received from a
.next
invocation - See the example from the
define-coroutine
section!
-
Get Length of Stream:
(stream-length <stream>)
-
Get Reverse of Stream:
(stream-reverse <stream>)
-
Stream Access:
scar
= first of stream,scdr
= rest of stream, & composedscar
&scdr
(scar <stream>)
,(scdr <stream>)
(scaar <stream>)
,(scadr <stream>)
,(scdar <stream>)
,(scddr <stream>)
(scaaar <stream>)
...(scdddr <stream>)
(scaaaar <stream>)
...(scddddr <stream>)
-
Reference: Get elt at
<index>
in<stream-pair>
(stream-ref <stream-pair> <index>)
-
Append: Join
<streams>
into a new stream(stream-append <stream1> <stream2> ...)
-
Drop: Drop
<n>
elts from<stream>
(stream-drop <stream> <n>)
-
Drop While: Drop elts from
<stream>
while<predicate?>
is true(stream-drop-while <predicate?> <stream>)
-
Take: Take
<n>
elts from<stream>
(stream-take <stream> <n>)
-
Take While: Take elts from
<stream>
while<predicate?>
is true(stream-take-while <predicate?> <stream>)
-
Map: Apply
<callable>
to each elt in each stream, forming a stream of results(stream-map <callable> <stream1> <stream2> ...)
-
Filter: Form a stream of elts from
<stream>
satisfying<predicate?>
(stream-filter <predicate?> <stream>)
-
For Each: Apply
<callable>
to each elt of each<stream>
(stream-for-each <callable> <stream1> <stream2> ...)
-
Unfold: Form a stream by mapping & incrementing seed, until
<break-cond-callable>
is true- Note: map via
<map-callable>
, increment via<suc-callable>
(stream-unfold <break-cond-callable> <map-callable> <suc-callable> <seed>)
- Note: map via
-
Fold: Accumulate stream from left to right, starting with
<seed>
using<callable>
(stream-fold <callable> <seed> <stream>)
-
Fold Right: Accumulate stream from right to left, starting with
<seed>
using<callable>
(stream-fold-right <callable> <seed> <stream>)
-
Numeric Stream: Form a stream starting from
<first>
incrementing by<optional-step>
- Note:
<optional-step>
step is1
by default (stream-from <first> <optional-step>)
- Note:
-
Stream Generation: Form a stream starting from
<seed>
using<suc-callable>
(stream-iterate <suc-callable> <seed>)
-
Zip: Form a stream of lists containing the nth elt of each
<stream>
(stream-zip <stream1> <stream2> ...)
-
Infinite Cycle: Forms an infinite stream of repeating
<objs>
(stream-constant <obj1> <obj2> ...)
-
Interleave: Form a stream by interleaving elts of either
<stream>
(stream-interleave <stream1> <stream2>)
-
Convert Stream to a Generator Thunk:
(stream->generator <stream>)
- Invoking the generator will continuously yield the next value in the stream!
- Yields the
'generator-complete
symbol once finished traversing the stream (if finite)!
-
Delay Predicate:
(delay? <obj>)
-
Force a Delayed Expression:
(force <delayed-expression>)
-
Get Typename Symbol:
(typeof <obj>)
-
Get Pointer Address String:
(pointer-address <obj>)
- Returns
#f
if<obj>
is passed by value!
- Returns
-
Undefined Predicate:
(undefined? <obj>)
- Use
(undefined)
to generate an undefined object!
- Use
-
Void Predicate:
(void? <obj>)
- Use
(void)
to generate a void object!
- Use
-
Empty Sequence Predicate:
(empty? <obj>)
-
Pair Predicate:
(pair? <obj>)
-
Vector Predicate:
(vector? <obj>)
-
Hash-Map Predicate:
(hmap? <obj>)
-
Character Predicate:
(char? <obj>)
-
Number Predicate:
(number? <obj>)
-
Real Predicate:
(real? <obj>)
-
Complex Predicate:
(complex? <obj>)
-
Rational Number Predicate:
(rational? <obj>)
-
String Predicate:
(string? <obj>)
-
Symbol Predicate:
(symbol? <obj>)
-
Boolean Predicate:
(boolean? <obj>)
-
Atom Predicate:
(atom? <obj>)
-
Procedure Predicate:
(procedure? <obj>)
-
Functor Predicate:
(functor? <obj>)
- Functor = object with a
self->procedure
method defined! - Functors may be called as if a function!
- Functor = object with a
-
Callable Predicate:
(callable? <obj>)
- Equivalent to:
(or (procedure? <obj>) (functor? <obj>) (class-prototype? <obj>))
- Equivalent to:
-
Input-Port Predicate:
(input-port? <obj>)
-
Output-Port Predicate:
(output-port? <obj>)
-
Eof-Object Predicate:
(eof-object? <obj>)
-
Stream-Pair Predicate:
(stream-pair? <obj>)
-
Empty-Stream Predicate:
(stream-null? <obj>)
-
Stream Predicate:
(stream? <obj>)
-
Syntax-Rules Object Predicate:
(syntax-rules-object? <obj>)
-
Sequence Predicate:
(seq? <obj>)
-
Object Predicate:
(object? <obj>)
-
Class Prototype Predicate:
(class-prototype? <obj>)
-
Char to Integer:
(char->integer <char>)
-
Integer to Char:
(integer->char <int>)
<int>
must be in range of [0,255]!
-
Number to String:
(number->string <number> <optional-radix> <optional-precision>)
-
String to Number:
(string->number <string> <optional-radix>)
-
String to Symbol:
(string->symbol <string>)
-
Symbol to String:
(symbol->string <symbol>)
-
Vector to List:
(vector->list <vector>)
-
List to Vector:
(list->vector <list>)
-
String to Vector:
(string->vector <string>)
-
Vector to String:
(vector->string <vector>)
-
String to List:
(string->list <string>)
-
List to String:
(list->string <list>)
-
Hash-Map to Alist:
(hmap->alist <hash-map>)
-
Alist to Hash-Map:
(alist->hmap <alist>)
-
Stream to List:
(stream->list <stream> <size>)
- Convert the 1st
<size>
elts of<stream>
into a list!
- Convert the 1st
-
List to Stream:
(list->stream <list>)
-
Object Members to Hmap:
(object->hmap <object>)
-
Object Members to Alist:
(object->alist <object>)
-
Functor to Procedure:
(functor->procedure <functor>)
-
Deep-Copy Datum:
(copy <obj>)
- Deep-copy vectors, strings, proper/dotted/circular lists, hmaps, & objects!
-
Shallow-Copy Datum:
(shallow-copy <obj>)
- Shallow-copy vectors, strings, proper/dotted/circular lists, hmaps, & objects!
- Note that this performs structural allocation w/ shallow content copying
- Hence
copy
andshallow-copy
are effectively identical for strings!
- Hence
-
Eval: Run quoted data as code
(eval <data> <optional-environment>)
- Pass
*null-environment*
toeval
in an empty environment! - Pass
*local-environment*
toeval
in the local environment (default)! - Pass
*global-environment*
toeval
in the global environment!
-
Cps-Eval: Alternative to
eval
forscm->cps
blocks (evals in CPS)!(cps-eval <data> <optional-environment> <continuation>)
- Pass
*null-environment*
tocps-eval
in an empty environment! - Pass
*local-environment*
tocps-eval
in the local environment (default)! - Pass
*global-environment*
tocps-eval
in the global environment!
-
Apply
<callable>
to List of Args:(apply <callable> <argument-list>)
-
Compose N
<callable>
s:(compose <callable-1> ... <callable-N>)
- Aliased as
o
for composition shorthand! - Generates a procedure of N args that applies them to the callable composition!
- Aliased as
-
Bind N args to
<callable>
:(bind <callable> <val-1> ... <val-N>)
- Generates a procedure that when invoked calls the arg-bound
<callable>
! - Example:
((bind map even?) '(1 2 3))
is equivalent to(map even? '(1 2 3))
- Generates a procedure that when invoked calls the arg-bound
-
Identity:
(id <obj>)
-
Pretty-Print (Indents Quoted Data):
(pretty-print <obj> <optional-open-output-port-or-string>)
(pprint <obj> <optional-open-output-port-or-string>)
-
Write (Machine-Readable):
(write <obj> <optional-open-output-port-or-string>)
-
Display (Human-Readable):
(display <obj> <optional-open-output-port-or-string>)
-
Newline:
(newline <optional-open-output-port-or-string>)
-
Write-Char:
(write-char <char> <optional-open-output-port-or-string>)
-
Sprintf: Returns a new, formatted string!
(sprintf <formatted-string> <optional-arg1> <optional-arg2> ...)
-
Formatted-Display:
(displayf <optional-output-port> <formatted-string> <optional-arg1> ...)
-
Formatted-Write:
(writef <optional-output-port> <formatted-string> <optional-arg1> ...)
-
Formatted-Pretty-Print:
(pprintf <optional-output-port> <formatted-string> <optional-arg1> ...)
(pretty-printf <optional-output-port> <formatted-string> <optional-arg1> ...)
=> <formatted-string> is like C's printf with unique formatting patterns:
----------------------------------------------------------------------
%a = display anything
%wa = write anything
%pa = pretty-print anything
----------------------------------------------------------------------
%... = display unpacked sequence
%w... = write unpacked sequence
%p... = pretty-print unpacked sequence
----------------------------------------------------------------------
%n = number
%+n = number (show sign if positive too)
%,n = number with commas (only for bigints)
%En = %en = number (coerced to exact)
%In = %in = number (coerced to inexact)
%#rn = %#Rn = number (in base <#> from 2 to 36)
%#n = number (left-padded with 0s to a width of <#> characters)
%.#n = number (with <#> digits of precision)
-> IE "%+e2r.5n": 5 digits of precision & mk exact in binary w/ sign
-> NOTE: case of 'n' in "%n" denotes case of base >= 11 letters
-> NOTE: 0-padding & precision MUST be of 2 digits or less!
----------------------------------------------------------------------
%$ = display real finite as a dollar value
%,$ = display real finite as a dollar value seperated by commas
----------------------------------------------------------------------
%s = display string
%#s = display string & pad left with # spaces
%-#s = display string & pad right with # spaces
%ws = write string
-> NOTE: padding MUST be of 3 digits or less (ie from -999 to 999)
----------------------------------------------------------------------
%c = display char
%wc = write char
----------------------------------------------------------------------
%b = bool
%wb = write "true" or "false" instead of "#t" or "#f"
----------------------------------------------------------------------
%% = "%" (escapes a "%")
----------------------------------------------------------------------
-
Convert String to ASCII Art:
(string->ascii-art <string>)
-
Convert String to Whitespace Art:
(string->space-art <string>)
-
Reset ANSI Formats:
(fmt:reset)
-
Clear Screen:
(fmt:clear)
-
Bold Text:
(fmt:bold)
-
Underlined Text:
(fmt:line)
-
Reverse Background & Foreground Colors:
(fmt:rev)
-
Black Text:
(fmt:black)
,(fmt:black1)
...(fmt:black8)
-
Red Text:
(fmt:red)
,(fmt:red1)
...(fmt:red8)
-
Green Text:
(fmt:green)
,(fmt:green1)
...(fmt:green8)
-
Yellow Text:
(fmt:yellow)
,(fmt:yellow1)
...(fmt:yellow8)
-
Blue Text:
(fmt:blue)
,(fmt:blue1)
...(fmt:blue8)
-
Magenta Text:
(fmt:magenta)
,(fmt:magenta1)
...(fmt:magenta8)
-
Cyan Text:
(fmt:cyan)
,(fmt:cyan1)
...(fmt:cyan8)
-
White Text:
(fmt:white)
,(fmt:white1)
...(fmt:white8)
-
Black Background:
(fmt:bblack)
,(fmt:bblack1)
...(fmt:bblack8)
-
Red Background:
(fmt:bred)
,(fmt:bred1)
...(fmt:bred8)
-
Green Background:
(fmt:bgreen)
,(fmt:bgreen1)
...(fmt:bgreen8)
-
Yellow Background:
(fmt:byellow)
,(fmt:byellow1)
...(fmt:byellow8)
-
Blue Background:
(fmt:bblue)
,(fmt:bblue1)
...(fmt:bblue8)
-
Magenta Background:
(fmt:bmagenta)
,(fmt:bmagenta1)
...(fmt:bmagenta8)
-
Cyan Background:
(fmt:bcyan)
,(fmt:bcyan1)
...(fmt:bcyan8)
-
White Background:
(fmt:bwhite)
,(fmt:bwhite1)
...(fmt:bwhite8)
-
Read: Get input as a quoted Datum
(read <optional-open-input-port-or-string>)
-
Read Next Expression Into a String:
(read-string <optional-open-input-port-or-string>)
-
Read Next Line of Input Into a String:
(read-line <optional-open-input-port-or-string>)
-
Read Next Character of Input:
(read-char <optional-open-input-port-or-string>)
-
Peek Char:
(peek-char <optional-open-input-port-or-string>)
-
Whether a Character is Ready to be Read:
(char-ready? <optional-open-input-port-or-string>)
-
Slurp Entire Port Contents Into a String:
(slurp-port <optional-open-input-port-or-string>)
-
Slurp Entire File Contents Into a String:
(slurp-file <filename-string>)
-
Read Entire Port Contents as a Data Struct:
(read-port <optional-open-input-port-or-string>)
-
Read Entire File Contents as a Data Struct:
(read-file <filename-string>)
-
Current Working Directory String:
(getcwd)
-
Get Parent Directory String:
(dirname <filepath-string>)
-
Create a New Directory:
(mkdir <new-directory-name-string>)
-
Change Current Working Directory:
(chdir <directory-path-string>)
-
File Predicate:
(file? <filename-string>)
-
Directory Predicate:
(directory? <directory-name-string>)
-
Path Predicate:
(path? <path-string>)
- Equivalent to
(or (file? <path-string>) (directory? <path-string>))
!
- Equivalent to
-
Get Directory Entries List:
(directory-entries <directory-name-string>)
- Returns
#f
if<directory-name-string>
doesn't denote a directory!
- Returns
-
Get Directory Entries List w/o Dot-Files:
(directory-entries* <directory-name-string>)
- Returns
#f
if<directory-name-string>
doesn't denote a directory! - "Dot-file" here refers to any file beginning with "."!
- Returns
-
Delete Path:
(delete-path! <path-string>)
-
Rename Path:
(rename-path! <old-name-string> <new-name-string>)
-
Copy Path:
(copy-path <source-path-string> <destination-path-string>)
-
Get File Size:
(file-size <filename-string>)
- Behavior is platform-dependant when invoked on directories!
-
Get File Extension:
(file-extension <filename-string>)
- Returns
#f
if<filename-string>
doesn't have an extension! - Doesn't include the
.
in its returned extension!
- Returns
-
Confirm File Extension:
(has-file-extension? <filename-string> <extension-string>)
<extension-string>
should NOT include the.
(implicitly added)!
-
Set File Extension:
(set-file-extension! <filename-string> <new-extension-string>)
- Effectively a mutative equivalent to
swap-file-extension
<new-extension-string>
should NOT include the.
(implicitly added)!
- Effectively a mutative equivalent to
-
Swap File Extension:
(swap-file-extension <filename-string> <new-extension-string>)
- Effectively a non-mutative equivalent to
set-file-extension!
<new-extension-string>
should NOT include the.
(implicitly added)!
- Effectively a non-mutative equivalent to
-
Open-Port Predicate:
(open-port? <port>)
-
Closed-Port Predicate:
(closed-port? <port>)
-
Current Input Port:
(current-input-port)
-
Current Output Port:
(current-output-port)
-
Call With Input File:
(call-with-input-file <filename-string> <unary-port-callable>)
-
Call With Output File:
(call-with-output-file <filename-string> <unary-port-callable>)
-
With Input From File:
(with-input-from-file <filename-string> <nullary-callable>)
-
With Output From File:
(with-output-to-file <filename-string> <nullary-callable>)
-
Generate Input Port:
(open-input-file <filename-string>)
-
Generate Output Port:
(open-output-file <filename-string>)
- Only works to create files that don't already exist!
-
Generate Output Append Port:
(open-output-file+ <filename-string>)
- Both creates new files & appends to existing files!
-
Destructively Generate Output Port:
(open-output-file! <filename-string>)
- Equivalent to
(begin (delete-path! <filename-string>) (open-output-file <filename-string>))
- Equivalent to
-
Rewind Port:
(rewind-port! <input-or-output-port>)
-
Seek from Port's Current Position:
(port-seek! <open-port> <integer-offset>)
- Equivalent to C++'s
fseek
usingSEEK_CUR
- Equivalent to C++'s
-
Seek from Start of Port's Stream:
(port-seek-front! <open-port> <integer-offset>)
- Equivalent to C++'s
fseek
usingSEEK_SET
- Equivalent to C++'s
-
Close Port:
(close-port <input-or-output-port>)
-
Load:
(load <filename-string> <optional-environment>)
- Pass
*null-environment*
toload
in an empty environment! - Pass
*local-environment*
toload
in the local environment (default)! - Pass
*global-environment*
toload
in the global environment!
- Pass
-
Cps-Load:
(cps-load <filename-string> <optional-environment> <continuation>)
- Alternative to
load
forscm->cps
blocks (converts file to CPS prior loading)! - Pass
*null-environment*
tocps-load
in an empty environment! - Pass
*local-environment*
tocps-load
in the local environment (default)! - Pass
*global-environment*
tocps-load
in the global environment!
- Alternative to
-
Compile a File:
(compile <filename-string> <optional-compiled-filename>)
- Take into account the compiler's replacement of the reader!
-
Cps-Compile a File:
(cps-compile <filename-string> <optional-compiled-filename>)
- Take into account the compiler's replacement of the reader!
-
System Interface Via Command-Line: Returns
#f
if feature not offered by OS(system <optional-system-call-string>)
-
Get-Environment: Get the system environment variable's value as a string
(getenv <environment-variable-name-string>)
-
Command-Line Args: Get a string with command-line arg descriptions
(command-line)
-
Get Milliseconds Since Epoch:
(ms-since-epoch)
-
Time Callable Execution:
(time <callable> <arg1> ... <argN>)
- Returns a pair:
(cons <time-in-seconds> <callable's-result>)
- Returns a pair:
-
Get Current Date as String:
(current-date <optional-offset> ...)
<optional-offset>
=(<symbolic-unit> <integer-amount>)
<symbolic-unit>
=sec
|min
|hour
|day
|year
-
Disable ANSI Escape Codes:
(set-nansi! <boolean>)
- Check status via
(nansi?)
!
- Check status via
-
Check Case-Insensitivity:
(ci?)
-
Set Pretty-Print Column Length:
(set-pprint-column-width! <positive-integer>)
- Get current width via
(pprint-column-width)
!
- Get current width via
-
Set Recursion Depth Limit:
(set-max-recursion-depth! <positive-integer>)
- Get current max depth via
(max-recursion-depth)
!
- Get current max depth via
-
Set REPL Prompt:
(set-repl-prompt! <string>)
- Get current repl prompt string via
(repl-prompt)
!
- Get current repl prompt string via
-
Dynamic Procedure Trace (Last Resort Debugging):
(set-dynamic-call-trace! <boolean>)
- Check status via
(dynamic-call-trace?)
!
- Check status via
-
Trace Procedure Call Arguments Too:
(set-trace-args! <boolean>)
- Check status via
(trace-args?)
!
- Check status via
-
Set Dot Symbol For Pair Literals & Variadics:
(set-dot! <symbol>)
- Defaults to
.
! - Get current dot via
(dot)
! - Returns the last symbol that served this role!
- Alias the current dot in syntax via
*dot*
!
- Defaults to
-
Register Values as Falsey:
(set-falsey! <obj> ...)
- Note that
#t
can NEVER be set as falsey! - By default, only
#f
is falsey in Heist Scheme. - Falsey values are identified internally via
equal?
. - Falsey values are deep-copied via
copy
internally to the set of falsey values.
Thus:(define l '(1 2 3)) (set-falsey! l) (if l 1 0) ; 0 (set-car! l 0) (if l 1 0) ; 1
- Note that
-
Register Values as Truthy:
(set-truthy! <obj> ...)
- Note that
#f
can NEVER be set as truthy! - Effectively removes
<obj> ...
from the set of falsey values. - By default, everything EXCEPT
#f
is truthy in Heist Scheme.
- Note that
-
Get Falsey Values List:
(falsey-values)
-
Exit:
(exit <optional-integer-exit-code>)
- Note:
<optional-integer-exit-code>
defaults to*exit-success*
- Note: Unlike C++'s
std::exit
, thisexit
calls all destructors prior exiting! - If triggered while embedded in C++ (
interop.hpp
), eval'd code
returns either*exit-success*
or*exit-failure*
as a SYMBOL! - If triggered in
*null-environment*
, evaluation of the given code ends immediately!
- Note:
-
Trigger Error:
(error <errorful-obj-symbol> <error-string> <optional-errorful-objs>)
-
Trigger Syntax Error:
(syntax-error <errorful-obj-symbol> <error-string> <optional-errorful-objs>)
-
Call With Current Environment:
(call/ce <callable> <arg1> ... <argN>)
(call-with-current-environment <callable> <arg1> ... <argN>)
-
Convert Callable to Use Dynamic Scope:
(lexical-scope->dynamic-scope <callable>)
-
Convert Callable to Use Lexical Scope:
(dynamic-scope->lexical-scope <callable>)
- Callables use lexical scope by default!
-
Confirm Callable Uses Dynamic Scope:
(dynamic-scope? <callable>)
-
Confirm Callable Uses Lexical Scope:
(lexical-scope? <callable>)
-
Jump/Throw Value:
(jump! <optional-arg>)
<optional-arg>
defaults to(void)
-
Catch Jumped/Thrown Value:
(catch-jump <callable> <arg1> ... <argN>)
-
Trace Procedure Call:
(trace <procedure> <arg1> ... <argN>)
- Call With Current Continuation:
(call/cc <unary-continuation-callable>)
(call-with-current-continuation <unary-continuation-callable>)
- Note: only valid in CPS contexts!
-
Generate a Unique Symbol:
(gensym <optional-instance-#-to-reference>)
(gensym 1)
refers to the symbol generated by the last(gensym)
invocation(gensym 2)
refers to the symbol generated by the 2nd to last(gensym)
invocation- etc.
-
Generate a Seeded Symbol:
(sown-gensym <seed>)
<seed>
= number | symbol | boolean
-
Append Symbols:
(symbol-append <symbol-1> ... <symbol-N>)
- If the series of symbols appended yields a number, returns the number
- IE
(symbol-append '+ 'i)
=>+i
=>0+1i
- IE
- If the series of symbols appended yields a number, returns the number
-
Expand Macros:
(expand <quoted-macro-exp>)
- Expands both analysis-time & run-time macros!
- Does not expand any new macros defined in
<quoted-macro-exp>
! - Use
expand*
to expand while also auto-unwrapping unary begins!
-
Expand Core Macros:
(core-expand <quoted-macro-exp>)
- Only expands analysis-time macros!
- Does not expand any new macros defined in
<quoted-macro-exp>
! - Use
core-expand*
to core-expand while also auto-unwrapping unary begins!
-
Core-Syntax?: Determine if a symbol was defined by
core-syntax
(core-syntax? <symbol>)
-
Runtime-Syntax?: Determine if a symbol was defined by
define-syntax
(runtime-syntax? <symbol>)
-
Reader-Alias?: Determine if a symbol was defined by
define-reader-alias
(reader-alias? <string>)
- Must be a string to avoid conversion by the reader if IS an alias!
-
Reader-Syntax?: Determine if a symbol was defined by
define-reader-syntax
(reader-syntax? <string>)
- Must be a string to avoid expansion by the reader if IS syntax!
-
Define Reader Shorthand Syntax:
(define-reader-syntax <shorthand-string> <optional-longhand-string>)
- Have the reader expand
<shorthand-string>
around objects into<longhand-string>
- Internally,
'
works as if interpreted(define-reader-syntax "'" "quote")
! - Leaving out
<optional-longhand>
rms<shorthand>
reader macro & returns if found! - Defining
:
as a shorthand is invalid (messes with internal reserved symbols)!
- Internally,
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ;; NOTE: Defn's _MUST_ be evaluated before being usable by the reader! ;; Ex 1: (define-reader-syntax "%" "display") %1 ; OK! Above definition was evaluated prior reading this expression! ;; Ex 2: ((lambda () (define-reader-syntax "%" "display"))) %1 ; Also OK! Same reason as Ex 1. ;; Ex 3: ((lambda () (define-reader-syntax "%" "display") %1)) ; ERROR (%1 not defined!): `%1` got read in the same expression as ; `(define-reader-syntax "%" "display")` before the definition was evaluated! ; >>> Hence `%1` didn't get expanded to `(display 1)` by the reader!
-
Get Alist of Reader Syntax Shorthands & Longhands:
(reader-syntax-list)
-
Get Alist of Reader Aliases & Names:
(reader-alias-list)
-
Get Alist of Infix Symbols, Associativity, & Precedence:
(infix-list)
-
Delete Core Syntax:
(delete-core-syntax! <macro-name-symbol> ...)
-
Delete Runtime Syntax:
(delete-runtime-syntax! <macro-name-symbol> ...)
-
Convert JSON String to a Scheme Datum:
(json->scm <string>)
- Note: arrays -> vectors, null ->
'()
, & maps -> alists (of key-value lists)
- Note: arrays -> vectors, null ->
-
Convert Scheme Datum to a JSON String:
(scm->json <obj> <optional-indent-width>)
<obj> ::= <string> | <number> | <'()> ; -> <null> | <alist> ; -> <map> (keys must be string | number | null | bool!) | <vector> ; -> <array> | <boolean>
-
Convert Object Members into JSON String:
(object->json <object> <optional-indent-width>)
-
JSON Datum Predicate:
(json-datum? <obj>)
- Effectively returns whether
(scm->json <obj>)
would throw an error or not
- Effectively returns whether
-
Convert CSV String to a List of Lists:
(csv->list <string> <optional-delimiter-char>)
<optional-delimiter-char>
defaults to#\,
- Since CSV is untyped (unlike JSON), all cells are stringified!
-
Convert CSV String to a Vector of Vectors:
(csv->vector <string> <optional-delimiter-char>)
<optional-delimiter-char>
defaults to#\,
- Since CSV is untyped (unlike JSON), all cells are stringified!
-
Convert List of Lists to a CSV String:
(list->csv <list-of-lists-of-csv-data> <optional-delimiter-char>)
<csv-data>
::=<string>
|<number>
<optional-delimiter-char>
defaults to#\,
-
Convert Vector of Vectors to a CSV String:
(vector->csv <vector-of-vectors-of-csv-data> <optional-delimiter-char>)
<csv-data>
::=<string>
|<number>
<optional-delimiter-char>
defaults to#\,
-
CSV Datum Predicate:
(csv-datum? <obj>)
- Effectively returns whether
vector->csv
orlist->csv
would throw an error or not
- Effectively returns whether
-
Create Universe:
(new-universe)
- Returns a
universe
object, initialized with Heist's default bindings,
which enables evaluation in a persistent sandboxed environment!
- Returns a
-
Universe Predicate:
(universe? <obj>)
-
Method to Evaluate in Universe:
(<universe-object>.eval <datum>)
- Evaluates
<datum>
in the<universe-object>
's sandboxed environment!
- Evaluates
-
Method to Store Data in Universe Buffer:
(<universe-object>.push! <datum>)
-
Method to Remove Data from Universe Buffer:
(<universe-object>.pop!)
-
Method to Clear Universe Buffer:
(<universe-object>.clear!)
-
Method to Execute (then clear!) Universe Buffer:
(<universe-object>.run!)
-
e:
fl-e
-
1/e:
fl-1/e
-
e^2:
fl-e-2
-
π:
fl-pi
-
1/π:
fl-1/pi
-
2π:
fl-2pi
-
π/2:
fl-pi/2
-
π/4:
fl-pi/4
-
π^2:
fl-pi-squared
-
π/180, Radians Per Degree:
fl-rad/deg
-
180/π, Degrees Per Radian:
fl-deg/rad
-
2/π:
fl-2/pi
-
2/√π:
fl-2/sqrt-pi
-
e^(π/4):
fl-e-pi/4
-
log2(e):
fl-log2-e
-
log10(e):
fl-log10-e
-
loge(2):
fl-log-2
-
1/loge(2):
fl-1/log-2
-
loge(3):
fl-log-3
-
loge(π):
fl-log-pi
-
loge(10):
fl-log-10
-
1/loge(10):
fl-1/log-10
-
√2:
fl-sqrt-2
-
√3:
fl-sqrt-3
-
√5:
fl-sqrt-5
-
√10:
fl-sqrt-10
-
1/√2:
fl-1/sqrt-2
-
2^(1/3):
fl-cbrt-2
-
3^(1/3):
fl-cbrt-3
-
2^(1/4):
fl-4thrt-2
-
φ:
fl-phi
-
loge(φ):
fl-log-phi
-
1/loge(φ):
fl-1/log-phi
-
γ (Euler's Constant):
fl-euler
-
e^γ:
fl-e-euler
-
sin(1):
fl-sin-1
-
cos(1):
fl-cos-1
-
Γ(1/2) = √π:
fl-gamma-1/2
-
Γ(1/3):
fl-gamma-1/3
-
Γ(2/3):
fl-gamma-2/3
(define (print data) (pretty-print data) (if (not (void? data)) (newline)))
(let loop ((ignore #f)) (loop (print (eval (read)))))