This namespace contains typed wrapper macros, type aliases and functions for type checking Clojure code. check-ns is the interface for checking namespaces, cf for checking individual forms.
Usage: (AVec t)
A persistent vector returned from clojure.core/vector (and others)Source
Usage: (BlockingDeref t)
A Clojure blocking derefable (see clojure.core/deref).Source
Usage: (CountRange Integer)
(CountRange Integer Integer)
A type representing a range of counts for a collectionSource
Usage: (Difference type type type*)
Difference represents a difference of types.
(Difference t s) is the same as type t with type s removed.
eg. (Difference (U Int Long) Int) => Long
(Difference (U Num nil) nil) => Num
Source
Usage: EmptyCount
The type of all things with count 0. Use as part of an intersection. eg. See EmptySeqable.Source
Usage: (EmptySeqable t)
A type that can be used to create a sequence of member type x with count 0.Source
Usage: (ExactCount Integer)
A type representing a precise count for a collectionSource
Usage: (Future t)
A Clojure future (see clojure.core/{future-call,future}).
Source
Usage: (Get type type)
(Get type type type)
A type representing a get operationSource
Usage: (HMap :mandatory {Constant Type*} :optional {Constant Type*} :absent-keys #{Constant*} :complete? Boolean)
(quote {Constant Type*})
HMap is a type for heterogeneous maps.Source
Usage: (HSeq [fixed*] :filter-sets [FS*] :objects [obj*])
(HSeq [fixed* rest *] :filter-sets [FS*] :objects [obj*])
(HSeq [fixed* drest ... bound] :filter-sets [FS*] :objects [obj*])
HSeq is a type for heterogeneous seqsSource
Usage: (HSequential [fixed*] :filter-sets [FS*] :objects [obj*])
(HSequential [fixed* rest *] :filter-sets [FS*] :objects [obj*])
(HSequential [fixed* drest ... bound] :filter-sets [FS*] :objects [obj*])
HSequential is a type for heterogeneous sequential collectionsSource
Usage: (HSet #{fixed*} :complete? Boolean)
HSet is a type for heterogeneous sets.
Takes a set of simple values. By default
:complete? is true.
eg. (HSet #{:a :b :c} :complete? true)
Source
Usage: (HVec [fixed*] :filter-sets [FS*] :objects [obj*])
(HVec [fixed* type *] :filter-sets [FS*] :objects [obj*])
(HVec [fixed* type ... bound] :filter-sets [FS*] :objects [obj*])
(quote [fixed*])
(quote [fixed* type *])
(quote [fixed* type ... bound])
HVec is a type for heterogeneous vectors. It extends clojure.core.typed/Vec and is a subtype of clojure.core.typed/HSequential.Source
Usage: (IFn ArityVec+)
[fixed* -> ret :filters {:then fl, :else fl} :object {:id Foo, :path Bar}]
[fixed* rest * -> ret :filters {:then fl, :else fl} :object {:id Foo, :path Bar}]
[fixed* drest ... bound -> ret :filters {:then fl, :else fl} :object {:id Foo, :path Bar}]
An ordered intersection type of function arities.Source
Usage: (NilableNonEmptyASeq t)
The result of clojure.core/seq.Source
Usage: (NilableNonEmptySeq t)
A persistent sequence of member type x with count greater than 0, or nil.Source
Usage: (NonEmptyASeq t)
A sequential non-empty seq retured from clojure.core/seqSource
Usage: (NonEmptyAVec t)
A persistent vector returned from clojure.core/vector (and others) and count greater than 0.Source
Usage: (NonEmptyColl t)
A persistent collection with member type x and count greater than 0.Source
Usage: NonEmptyCount
The type of all things with count greater than 0. Use as part of an intersection. eg. See NonEmptySeqSource
Usage: (NonEmptySeq t)
A persistent sequence of member type x with count greater than 0.Source
Usage: (NonEmptySeqable t)
A type that can be used to create a sequence of member type x with count greater than 0.Source
Usage: (NonEmptyVec t)
A persistent vector with member type x and count greater than 0.Source
Usage: Nothing
Nothing is the bottom type that inhabits no types except itself.Source
Usage: (Pred type)
A predicate for the given type. eg. Type for integer?: (Pred Int)Source
Usage: (Promise t)
A Clojure promise (see clojure.core/{promise,deliver}).
Source
Usage: (Seqable t)
A type that can be used to create a sequence of member type x.Source
Usage: (SequentialSeq t)
A Clojure sequential sequence. Seq's aren't always Sequential.Source
Usage: (SequentialSeqable t)
A sequential, seqable collection. Seq's aren't always Sequential.Source
Usage: (Value Constant)
(quote Constant)
A singleton type for a constant value.Source
Usage: (ann varsym typesyn)
Annotate varsym with type. If unqualified, qualify in the current namespace.
If varsym has metadata {:no-check true}, ignore definitions of varsym
while type checking.
If annotating vars in namespaces other than the current one, a fully
qualified symbol must be provided. Note that namespace aliases are not
recognised: the *full* namespace must be given in the first part of the symbol.
eg. ; annotate the var foo in this namespace
(ann foo [Number -> Number])
; annotate a var in another namespace
(ann another.ns/bar [-> nil])
; don't check this var
(ann ^:no-check foobar [Integer -> String])
Source
Usage: (ann-datatype dname [field :- type*] opts*)
(ann-datatype binder dname [field :- type*] opts*)
Annotate datatype Class name dname with expected fields.
If unqualified, qualify in the current namespace.
Takes an optional type variable binder before the name.
Fields must be specified in the same order as presented
in deftype, with exactly the same field names.
Also annotates datatype factories and constructors.
Binder is a vector of specs. Each spec is a vector
with the variable name as the first entry, followed by
keyword arguments:
- :variance (mandatory)
The declared variance of the type variable. Possible
values are :covariant, :contravariant and :invariant.
- :< (optional)
The upper type bound of the type variable. Defaults to
Any, or the most general type of the same rank as the
lower bound.
- :> (optional)
The lower type bound of the type variable. Defaults to
Nothing, or the least general type of the same rank as the
upper bound.
eg. ; a datatype in the current namespace
(ann-datatype MyDatatype [a :- Number,
b :- Long])
; a datatype in another namespace
(ann-datatype another.ns.TheirDatatype
[str :- String,
vec :- (Vec Number)])
; a datatype, polymorphic in a
(ann-datatype [[a :variance :covariant]]
MyPolyDatatype
[str :- String,
vec :- (Vec Number)
ply :- (Set a)])
Source
Usage: (ann-form form ty)
Annotate a form with an expected type.
Usage: (ann-interface vbnd varsym & methods)
(ann-interface varsym & methods)
Annotate a possibly polymorphic interface (created with definterface) with method types.
Note: Unlike ann-protocol, omit the target ('this') argument in the method signatures.
eg. (ann-interface IFoo
bar
(Fn [-> Any]
[Number Symbol -> Any])
baz
[Number -> Number])
(definterface IFoo
(bar [] [n s])
(baz [n]))
; polymorphic protocol
; x is scoped in the methods
(ann-protocol [[x :variance :covariant]]
IFooPoly
bar
(Fn [-> Any]
[Number Symbol -> Any])
baz
[Number -> Number])
(definterface IFooPoly
(bar [] [n s])
(baz [n]))
Source
Usage: (ann-many t & vs)
Annotate several vars with type t.
eg. (ann-many FakeSearch
web1 web2 image1 image2 video1 video2)
Source
Usage: (ann-precord dname vbnd fields & {ancests :unchecked-ancestors, rplc :replace, :as opt})
Annotate record Class name dname with a polymorphic binder and expected fields. If unqualified, qualify in the current namespace.Source
Usage: (ann-protocol vbnd varsym & methods)
(ann-protocol varsym & methods)
Annotate a possibly polymorphic protocol var with method types.
eg. (ann-protocol IFoo
bar
(Fn [IFoo -> Any]
[IFoo Number Symbol -> Any])
baz
[IFoo Number -> Number])
(defprotocol> IFoo
(bar [this] [this n s])
(baz [this n]))
; polymorphic protocol
; x is scoped in the methods
(ann-protocol [[x :variance :covariant]]
IFooPoly
bar
(Fn [(IFooPoly x) -> Any]
[(IFooPoly x) Number Symbol -> Any])
baz
[(IFooPoly x) Number -> Number])
(defprotocol> IFooPoly
(bar [this] [this n s])
(baz [this n]))
Source
Usage: (ann-record dname [field :- type*] opts*)
(ann-record binder dname [field :- type*] opts*)
Annotate record Class name dname with expected fields.
If unqualified, qualify in the current namespace.
Takes an optional type variable binder before the name.
Fields must be specified in the same order as presented
in defrecord, with exactly the same field names.
Also annotates record factories and constructors.
Binder is a vector of specs. Each spec is a vector
with the variable name as the first entry, followed by
keyword arguments:
- :variance (mandatory)
The declared variance of the type variable. Possible
values are :covariant, :contravariant and :invariant.
- :< (optional)
The upper type bound of the type variable. Defaults to
Any, or the most general type of the same rank as the
lower bound.
- :> (optional)
The lower type bound of the type variable. Defaults to
Nothing, or the least general type of the same rank as the
upper bound.
eg. ; a record in the current namespace
(ann-record MyRecord [a :- Number,
b :- Long])
; a record in another namespace
(ann-record another.ns.TheirRecord
[str :- String,
vec :- (Vec Number)])
; a record, polymorphic in a
(ann-record [[a :variance :covariant]]
MyPolyRecord
[str :- String,
vec :- (Vec Number)
ply :- (Set a)])
Source
Usage: (atom & args)
Like atom, but with optional type annotations.
Same as (atom (ann-form init t) args*)
eg. (atom 1) : (Atom1 (Value 1))
(atom :- Num, 1) : (Atom1 Num)
Usage: (atom> t init & args)
DEPRECATED: use clojure.core.typed/atom
Like atom, but creates an Atom1 of type t.
Same as (atom (ann-form init t) args*)
eg. (atom> Number 1)
(atom> (Vec Any) [])
Deprecated since Gradual Typing version 0.2.58Usage: (cast t x)
(cast t x opt)
Cast a value to a type. Returns a new value that conforms
to the given type, otherwise throws an error with blame.
eg. (cast Int 1)
;=> 1
(cast Int nil)
; Fail, <blame positive ...>
((cast [Int -> Int] identity)
1)
;=> 1
((cast [Int -> Int] identity)
nil)
; Fail, <blame negative ...>
(cast [Int -> Int] nil)
; Fail, <blame positive ...>
(defalias Options
(HMap :optional {:positive (U Sym Str),
:negative (U Sym Str)
:file (U Str nil)
:line (U Int nil)
:column (U Int nil)}))
(IFn [Contract Any -> Any]
[Contract Any Options -> Any]
Options:
- :positive positive blame, (U Sym Str)
- :negative negative blame, (U Sym Str)
- :file file name where contract is checked, (U Str nil)
- :line line number where contract is checked, (U Int nil)
- :column column number where contract is checked, (U Int nil)
Source
Usage: (cf form)
(cf form expected)
Takes a form and an optional expected type and
returns a human-readable inferred type for that form.
Throws an exception if type checking fails.
Do not use cf inside a typed namespace. cf is intended to be
used at the REPL or within a unit test. Note that testing for
truthiness is not sufficient to unit test a call to cf, as nil
and false are valid type syntax.
cf preserves annotations from previous calls to check-ns or cf,
and keeps any new ones collected during a cf. This is useful for
debugging and experimentation. cf may be less strict than check-ns
with type checker warnings.
eg. (cf 1)
;=> Long
(cf #(inc %) [Number -> Number])
;=> [Number -> Number]
Source
Usage: (check-form* form)
(check-form* form expected)
(check-form* form expected type-provided?)
Takes a (quoted) form and optional expected type syntax and type checks the form. If expected is provided, type-provided? must be true.Source
Usage: (check-form-info form & opt)
Type checks a (quoted) form and returns a map of results from type checking the
form.
Options
- :expected Type syntax representing the expected type for this form
type-provided? option must be true to utilise the type.
- :type-provided? If true, use the expected type to check the form.
- :profile Use Timbre to profile the type checker. Timbre must be
added as a dependency. Must use the "slim" JAR.
- :file-mapping If true, return map provides entry :file-mapping, a hash-map
of (Map '{:line Int :column Int :file Str} Str).
- :checked-ast Returns the entire AST for the given form as the :checked-ast entry,
annotated with the static types inferred after checking.
If a fatal error occurs, mapped to nil.
- :no-eval If true, don't evaluate :out-form. Removes :result return value.
It is highly recommended to evaluate :out-form manually.
Default return map
- :ret TCResult inferred for the current form
- :out-form The macroexpanded result of type-checking, if successful.
- :result The evaluated result of :out-form, unless :no-eval is provided.
- :ex If an exception was thrown during evaluation, this key will be present
with the exception as the value.
DEPRECATED
- :delayed-errors A sequence of delayed errors (ex-info instances)
Source
Usage: (check-ns)
(check-ns ns-or-syms & opt)
Type check a namespace/s (a symbol or Namespace, or collection).
If not provided default to current namespace.
Returns a true value if type checking is successful, otherwise
throws an Exception.
Do not use check-ns within a checked namespace.
It is intended to be used at the REPL or within a unit test.
Suggested idiom for clojure.test: (is (check-ns 'your.ns))
check-ns resets annotations collected from
previous check-ns calls or cf. A successful check-ns call will
preserve any type annotations collect during that checking run.
Keyword arguments:
- :collect-only if true, collect type annotations but don't type check code.
Useful for debugging purposes.
- :trace if true, print some basic tracing of the type checker
- :profile Use Timbre to profile the type checker. Timbre must be
added as a dependency. Must use the "slim" JAR.
If providing keyword arguments, the namespace to check must be provided
as the first argument.
Bind clojure.core.typed.util-vars/*verbose-types* to true to print fully qualified types.
Bind clojure.core.typed.util-vars/*verbose-forms* to print full forms in error messages.
eg. (check-ns 'myns.typed)
;=> :ok
; implicitly check current namespace
(check-ns)
;=> :ok
; collect but don't check the current namespace
(check-ns *ns* :collect-only true)
Source
Usage: (check-ns-info)
(check-ns-info ns-or-syms & opt)
Same as check-ns, but returns a map of results from type checking the
namespace.
Options
- :collect-only Don't type check the given namespace/s, but collect the
top level type annotations like ann, ann-record.
- :type-provided? If true, use the expected type to check the form
- :profile Use Timbre to profile the type checker. Timbre must be
added as a dependency. Must use the "slim" JAR.
- :file-mapping If true, return map provides entry :file-mapping, a hash-map
of (Map '{:line Int :column Int :file Str} Str).
Default return map
- :delayed-errors A sequence of delayed errors (ex-info instances)
Source
Usage: (declare-alias-kind sym ty)
Declare a kind for an alias, similar to declare but on the kind level.Source
Usage: (declare-datatypes & syms)
Declare datatypes, similar to declare but on the type level.Source
Usage: (declare-names & syms)
Declare names, similar to declare but on the type level.Source
Usage: (declare-protocols & syms)
Declare protocols, similar to declare but on the type level.Source
Usage: (def name docstring? :- type? expr)
Like clojure.core/def with optional type annotations
NB: in Clojure it is impossible to refer a var called `def` as it is a
special form. Use an alias prefix (eg. `t/def`).
If an annotation is provided, a corresponding `ann` form
is generated, otherwise it expands identically to clojure.core/def
eg. ;same as clojure.core/def
(def vname 1)
;with Number `ann`
(def vname :- Number 1)
;doc
(def vname
"Docstring"
:- Long
1)
Usage: (def-alias sym doc-str t)
(def-alias sym t)
DEPRECATED: use defalias
Define a type alias. Takes an optional doc-string as a second
argument.
Updates the corresponding var with documentation.
eg. (def-alias MyAlias
"Here is my alias"
(U nil String))
Deprecated since Gradual Typing version 0.2.45Usage: (def> name docstring? :- type expr)
DEPRECATED: use clojure.core.typed/def Like def, but with annotations. eg. (def> vname :- Long 1) ;doc (def> vname "Docstring" :- Long 1)Deprecated since Gradual Typing version 0.2.45
Usage: (defalias sym doc-str t)
(defalias sym t)
Define a recursive type alias. Takes an optional doc-string as a second
argument.
Updates the corresponding var with documentation.
eg. (defalias MyAlias
"Here is my alias"
(U nil String))
;; recursive alias
(defalias Expr
(U '{:op ':if :test Expr :then Expr :else Expr}
'{:op ':const :val Any}))
Source
Usage: (defn kw-args? name docstring? attr-map? [param :- type *] :- type exprs*)
(defn kw-args? name docstring? attr-map? ([param :- type *] :- type exprs*) +)
Like defn, but expands to clojure.core.typed/fn. If a polymorphic binder is supplied before the var name, expands to clojure.core.typed/pfn. eg. (defn fname [a :- Number, b :- (U Symbol nil)] :- Integer ...) ;annotate return (defn fname [a :- String] :- String ...) ;multi-arity (defn fname ([a :- String] :- String ...) ([a :- String, b :- Number] :- Long ...)) ;polymorphic function (defn :forall [x y] fname ([a :- x] :- (Coll y) ...) ([a :- Str, b :- y] :- y ...))
Usage: (defn> name docstring? :- type [param :- type *] exprs*)
(defn> name docstring? (:- type [param :- type *] exprs*) +)
DEPRECATED: Use defn Like defn, but with annotations. Annotations are mandatory for parameters and for return type. eg. (defn> fname :- Integer [a :- Number, b :- (U Symbol nil)] ...) ;annotate return (defn> fname :- String [a :- String] ...) ;multi-arity (defn> fname (:- String [a :- String] ...) (:- Long [a :- String, b :- Number] ...))Deprecated since Gradual Typing version 0.2.57
Usage: (defprotocol & body)
Like defprotocol, but with optional type annotations.
Omitted annotations default to Any. The first argument
of a protocol cannot be annotated.
Add a binder before the protocol name to define a polymorphic
protocol. A binder before the method name defines a polymorphic
method, however a method binder must not shadow type variables
introduced by a protocol binder.
Return types for each method arity can be annotated.
Unlike clojure.core/defprotocol, successive methods can
have the same arity. Semantically, providing multiple successive
methods of the same arity is the same as just providing the left-most
method. However the types for these methods will be accumulated into
a Fn type.
eg. ;annotate single method
(defprotocol MyProtocol
(a [this a :- Integer] :- Number))
;polymorphic protocol
(defprotocol [[x :variance :covariant]]
MyProtocol
(a [this a :- Integer] :- Number))
;multiple types for the same method
(defprotocol [[x :variance :covariant]]
MyProtocol
(a [this a :- Integer] :- Integer
[this a :- Long] :- Long
[this a :- Number] :- Number))
;polymorphic method+protocol
(defprotocol [[x :variance :covariant]]
MyProtocol
([y] a [this a :- x, b :- y] :- y))
Usage: (defprotocol> & body)
DEPRECATED: use clojure.core.typed/defprotocol
Like defprotocol, but required for type checking
its macroexpansion.
eg. (defprotocol> MyProtocol
(a [this]))
Deprecated since Gradual Typing version 0.2.45Usage: (doseq seq-exprs & body)
Like clojure.core/doseq with optional annotations.
:let option uses clojure.core.typed/let
eg.
(doseq [a :- (U nil AnyInteger) [1 nil 2 3]
:when a]
(inc a))
Source
Usage: (doseq> seq-exprs & body)
DEPRECATED: use clojure.core.typed/doseq
Like doseq but requires annotation for each loop variable:
[a [1 2]] becomes [a :- Long [1 2]]
eg.
(doseq> [a :- (U nil AnyInteger) [1 nil 2 3]
:when a]
(inc a))
Deprecated since Gradual Typing version 0.2.45Usage: (dotimes bindings & body)
Like clojure.core/dotimes, but with optional annotations.
If annotation for binding is omitted, defaults to Int.
eg. (dotimes [_ 100]
(println "like normal"))
(dotimes [x :- Num, 100.123]
(println "like normal" x))
Source
Usage: (dotimes> bindings & body)
DEPRECATED: Use clojure.core.typed/dotimes
Like dotimes.
eg. (dotimes> [_ 100]
(println "like normal"))
Deprecated since Gradual Typing version 0.2.45Usage: (envs)
Returns a map of type environments, according to the current state of the type checker. Output map: - :vars map from var symbols to their verbosely printed types - :aliases map from alias var symbols (made with defalias) to their verbosely printed types - :special-types a set of Vars that are special to the type checker (like Any, U, I)Source
Usage: (fn name? [param :- type* & param :- type * ?] :- type? exprs*)
(fn name? ([param :- type* & param :- type * ?] :- type? exprs*) +)
Like clojure.core/fn, but with optional annotations.
eg. ;these forms are equivalent
(fn [a] b)
(fn [a :- Any] b)
(fn [a :- Any] :- Any b)
(fn [a] :- Any b)
;annotate return
(fn [a :- String] :- String body)
;named fn
(fn fname [a :- String] :- String body)
;rest parameter
(fn [a :- String & b :- Number *] body)
;dotted rest parameter
(fn [a :- String & b :- Number ... x] body)
;multi-arity
(fn fname
([a :- String] :- String ...)
([a :- String, b :- Number] :- String ...))
; polymorphic binder
(fn :forall [x y z]
fname
([a :- String] :- String ...)
([a :- String, b :- Number] :- String ...))
Usage: (fn> name? :- type? [param :- type* & param :- type * ?] exprs*)
(fn> name? (:- type? [param :- type* & param :- type * ?] exprs*) +)
DEPRECATED: use clojure.core.typed/fn
Like fn, but with annotations. Annotations are mandatory
for parameters, with optional annotations for return type.
If fn is named, return type annotation is mandatory.
Suggested idiom: use commas between parameter annotation triples.
eg. (fn> [a :- Number, b :- (U Symbol nil)] ...)
;annotate return
(fn> :- String [a :- String] ...)
;named fn
(fn> fname :- String [a :- String] ...)
;multi-arity
(fn> fname
(:- String [a :- String] ...)
(:- Long [a :- String, b :- Number] ...))
Deprecated since Gradual Typing version 0.2.45Usage: (for seq-exprs & maybe-ann-body-expr)
Like clojure.core/for with optional type annotations.
All types default to Any.
The :let option uses clojure.core.typed/let.
eg. (for [a :- (U nil Int) [1 nil 2 3]
:when a]
:- Number
(inc a))
Source
Usage: (for> tk ret-ann seq-exprs body-expr)
DEPRECATED: use clojure.core.typed/for
Like for but requires annotation for each loop variable: [a [1 2]] becomes [a :- Long [1 2]]
Also requires annotation for return type.
eg. (for> :- Number
[a :- (U nil AnyInteger) [1 nil 2 3]
:when a]
(inc a))
Deprecated since Gradual Typing version 0.2.45Usage: (inst inst-of & types)
Instantiate a polymorphic type with a number of types. eg. (inst foo-fn t1 t2 t3 ...)Source
Usage: (inst-ctor inst-of & types)
Instantiate a call to a constructor with a number of types.
First argument must be an immediate call to a constructor.
Returns exactly the instantiatee (the first argument).
eg. (inst-ctor (PolyCtor. a b c)
t1 t2 ...)
Source
Usage: (install)
(install features)
Install the :core.typed :lang. Takes an optional set of features
to install, defaults to `:all`, which is equivalent to the set of
all features.
Features:
- :load Installs typed `load` over `clojure.core/load`, which type checks files
on the presence of a {:lang :core.typed} metadata entry in the `ns` form.
The metadata must be inserted in the actual `ns` form saved to disk,
as it is read directly from the file instead of the current Namespace
metadata.
- :eval Installs typed `eval` over `clojure.core/eval`.
If `(= :core.typed (:lang (meta *ns*)))` is true, the form will be implicitly
type checked. The syntax save to disk is ignored however.
eg. (install) ; installs `load` and `eval`
eg. (install :all) ; installs `load` and `eval`
eg. (install #{:eval}) ; installs `eval`
eg. (install #{:load}) ; installs `load`
Source
Usage: (into-array> cljt coll)
(into-array> javat cljt coll)
(into-array> into-array-syn javat cljt coll)
Make a Java array with Java class javat and Typed Clojure type cljt. Resulting array will be of type javat, but elements of coll must be under cljt. cljt should be a subtype of javat (the same or more specific). *Temporary hack* into-array-syn is exactly the syntax to put as the first argument to into-array. Calling resolve on this syntax should give the correct class.Source
Usage: (let [binding :- type? init*] exprs*)
Like clojure.core/let but supports optional type annotations.
eg. (let [a :- Type, b
a2 1.2]
body)
Usage: (letfn> [fn-spec-or-annotation*] expr*)
Like letfn, but each function spec must be annotated.
eg. (letfn> [a :- [Number -> Number]
(a [b] 2)
c :- [Symbol -> nil]
(c [s] nil)]
...)
Source
Usage: (load-if-needed)
Load and initialize all of core.typed if not alreadySource
Usage: (loop [binding :- type? init*] exprs*)
Like clojure.core/loop, and supports optional type annotations.
Arguments default to a generalised type based on the initial value.
eg. (loop [a :- Number 1
b :- (U nil Number) nil]
...)
Usage: (loop> [binding :- type init*] exprs*)
DEPRECATED: use clojure.core.typed/loop
Like loop, except loop variables require annotation.
Suggested idiom: use a comma between the type and the initial
expression.
eg. (loop> [a :- Number, 1
b :- (U nil Number), nil]
...)
Deprecated since Gradual Typing version 0.2.45Usage: (method-type mname)
Given a method symbol, print the core.typed types assigned to it. Intended for use at the REPL.Source
Usage: (nilable-param msym mmap)
Override which parameters in qualified method msym may accept nilable values. If the parameter is a parameterised type or an Array, this also declares the parameterised types and the Array type as nilable. mmap is a map mapping arity parameter number to a set of parameter positions (integers). If the map contains the key :all then this overrides other entries. The key can also be :all, which declares all parameters nilable.Source
Usage: (non-nil-return msym arities)
Override the return type of fully qualified method msym to be non-nil.
Takes a set of relevant arities,
represented by the number of parameters it takes (rest parameter counts as one),
or :all which overrides all arities.
eg. ; must use full class name
(non-nil-return java.lang.Class/getDeclaredMethod :all)
Source
Usage: (override-constructor ctorsym typesyn)
Override all constructors for Class ctorsym with type.Source
Usage: (override-method methodsym typesyn)
Override type for qualified method methodsym.
methodsym identifies the method to override and should be a
namespace-qualified symbol in the form <class>/<method-name>.
The class name needs to be fully qualified.
typesyn uses the same annotation syntax as functions.
Use non-nil-return instead of override-method if you want to
declare that a method can never return nil.
Example:
(override-method java.util.Properties/stringPropertyNames
[-> (java.util.Set String)])
This overrides the return type of method stringPropertyNames
of class java.util.Properties to be (java.util.Set String).
Source
Usage: (pfn> & forms)
Define a polymorphic typed anonymous function. (pfn> name? [binder+] :- type? [[param :- type]* & [param :- type *]?] exprs*) (pfn> name? [binder+] (:- type? [[param :- type]* & [param :- type *]?] exprs*)+)Source
Usage: (pred t)
Generate a flat (runtime) predicate for type that returns true if the
argument is a subtype of the type, otherwise false.
The current type variable and dotted type variable scope is cleared before parsing.
eg. ((pred Number) 1)
;=> true
Source
Usage: (print-env debug-str)
During type checking, print the type environment to *out*, preceeded by literal string debug-str.Source
Usage: (print-filterset debug-string frm)
During type checking, print the filter set attached to form,
preceeded by literal string debug-string.
Returns nil.
eg. (let [s (seq (get-a-seqable))]
(print-filterset "Here now" s))
Source
Usage: (ref & args)
Like ref, but with optional type annotations.
Same as (ref (ann-form init t) args*)
eg. (ref 1) : (Ref1 (Value 1))
(ref :- Num, 1) : (Ref1 Num)
Usage: (ref> t init & args)
DEPRECATED: use clojure.core.typed/ref
Like ref, but creates a Ref1 of type t.
Same as (ref (ann-form init t) args*)
eg. (ref> Number 1)
(ref> (Vec Any) [])
Deprecated since Gradual Typing version 0.2.58Usage: (runtime-infer)
(runtime-infer ns)
Infer and insert annotations for a given namespace.
To instrument your namespace, use the :runtime-infer
feature in your namespace metadata. Note: core.typed
must be installed via `clojure.core.typed/install`.
eg. (ns my-ns
{:lang :core.typed
:core.typed {:features #{:runtime-infer}}}
(:require [clojure.core.typed :as t]))
After your namespace is instrumented, run your tests
and/or exercise the functions in your namespace.
Then call `runtime-infer` to populate the namespace's
corresponding file with these generated annotations.
eg. (runtime-infer) ; infer for *ns*
(runtime-infer 'my-ns) ; infer for my-ns
Source
Usage: (statistics nsyms)
Takes a collection of namespace symbols and returns a map mapping the namespace symbols to a map of dataSource
Usage: (tc-ignore & body)
Ignore forms in body during type checking
Usage: (typed-deps & args)
Declare namespaces which should be checked before the current namespace.
Accepts any number of symbols. Only has effect via check-ns.
eg. (typed-deps clojure.core.typed.holes
myns.types)
Source
Usage: (untyped-var varsym typesyn)
Check a given var has the specified type at runtime.Source
Usage: (var-coverage)
(var-coverage nsyms-or-nsym)
Summarises annotated var coverage statistics to *out* for namespaces nsyms, a collection of symbols or a symbol/namespace. Defaults to the current namespace if no argument provided.Source
Usage: (var> sym)
Like var, but resolves at runtime like ns-resolve and is understood by the type checker. sym must be fully qualified (without aliases). eg. (var> clojure.core/+)Source
Usage: (warn-on-unannotated-vars)
Allow unannotated vars in the current namespace. Emits a warning instead of a type error when checking a def without a corresponding expected type. Disables automatic inference of `def` expressions. eg. (warn-on-unannotated-vars)Source
Usage: (when-let-fail b & body)
Like when-let, but fails if the binding yields a false value.
This namespace contains annotations and helper macros for type checking core.async code. Ensure clojure.core.async is require'd before performing type checking. go use go chan use chan buffer use buffer (similar for other buffer constructors)
Utilities for all implementations of the type checker
Usage: (check-form-cljs form expected expected-provided?)
Check a single form with an optional expected type. Intended to be called from Clojure. For evaluation at the Clojurescript REPL see cf.Source
Usage: (check-ns-info ns-or-syms & opt)
Same as check-ns, but returns a map of results from type checking the
namespace.
Options
- :collect-only Don't type check the given namespace/s, but collect the
top level type annotations like ann, ann-record.
- :type-provided? If true, use the expected type to check the form
- :profile Use Timbre to profile the type checker. Timbre must be
added as a dependency.
- :file-mapping If true, return map provides entry :file-mapping, a hash-map
of (Map '{:line Int :column Int :file Str} Str).
Source
Usage: (add-checks-normal-def check-fn expr expected)
Add runtime checks to a def with an initial value.Source
Usage: (check-def check-fn {:keys [var init env], :as expr} expected)
Check a def. If it is a declare or a defmacro, don't try and check it.Source
Usage: (check-defmacro-or-declare expr expected)
To check a defmacro or declare, just assign it the most general Var type and ignore the body.Source
Usage: (check-normal-def check-fn {:keys [init env], :as expr} & [expected])
Checks a def that isn't a macro definition.Source
Usage: (defmacro-or-declare? {:keys [var], :as expr})
Returns true if this :def AST originally a defmacro or declare.Source
Usage: (check-fni expected mthods {:keys [recur-target-fn validate-expected-fn self-name], :as opt})
Check a vector of :method AST nodes mthods against an expected type that is a possibly-polymorphic function intersection. Returns a vector in the same order as the passed in methods, but each method replaced with a vector of type checked methods.Source
Usage: (expected-for-method {:keys [fixed-arity], :as method} {:keys [dom rest drest kws], :as f})
Takes a :method AST node and a single Function arity type, and returns the Function if the :method node should be checked against the Function, otherwise returns nil.Source
Usage: (check-monitor check {:keys [target], :as expr} expected)
monitor-enter and monitor-exit both take any object and return nilSource
Usage: (add-checks-ann-form check {:keys [statements env], frm :ret, :as expr} expected)
Add runtime checks to an ann-form expression. Propagates its annotation inwards to the inner expression.Source
Usage: (ann-form-annotation {:keys [statements], :as expr})
Return the raw type annotation from the ann-form expression.Source
Usage: (check-ann-form check {:keys [statements env], frm :ret, :as expr} expected)
Type check an ann-form expression. Propagates its annotation inwards to the inner expression.Source
Usage: (parse-annotation tsyn {:keys [env], :as expr})
Parse the raw type annotation tsyn in the context of exprSource
Usage: (check-value {:keys [val], :as expr} expected quoted?)
Given a :const node and an expected type returns a new :const node annotated with its type. quoted? should be true if this :const node is nested inside a :quote node, otherwise should be falseSource
Usage: (unquote-val val)
Convert the syntax representation of a unevaluated value to an actual evaluated value. eg. ['a] is represented as [(quote a)] and evaluates to [a]Source
Usage: (collect-ns* nsym {:keys [ast-for-ns collect-asts collect-ns]})
Collect type annotations and dependency information for namespace symbol nsym, and recursively check declared typed namespace dependencies.Source
A contract system a la racket/contract. Main entry point is the `contract` macro.
Usage: (->Blame positive negative name contract file line column)
Positional factory function for class clojure.core.typed.contract.Blame.Source
Usage: (->CheckedISeq s c b)
Positional factory function for class clojure.core.typed.contract.CheckedISeq.Source
Usage: (->Contract name first-order projection flat?)
Positional factory function for class clojure.core.typed.contract.Contract.Source
Usage: (and-c & cs)
Returns a contract that ensures a value passes each contract `cs`. At most *one* higher-order contract may be passed to `and-c`, and any number of flat contracts. [Contract * -> Contract] eg. (and-c (instance-c Boolean) true-c) ;; (I Boolean true)Source
Usage: (contract c x)
(contract c x b)
Check a contract against a value, with an optional Blame object.
(IFn [Contract Any -> Any]
[Contract Any Blame -> Any])
Source
Usage: (count-range-c lower)
(count-range-c lower upper)
Returns a flat contract that allows values with `count`
greater-or-equal-to lower, and less-or-equal-to upper.
Upper can be nil for positive infinity.
(IFn [Int -> Contract]
[Int (U nil Int) -> Contract])
eg. (count-range-c 0 10)
(count-range-c 0 nil)
Source
Usage: (equiv-c y)
Returns a flat contract that returns true if a value is `=` to y. [Any -> Contract]Source
Usage: (hmap-c & {:keys [mandatory optional absent-keys complete?], :or {absent-keys #{}, mandatory {}, optional {}, complete? false}})
Takes a map of mandatory and optional entry contracts, a set of absent keys, and :complete? true if this is a fully specified map. Intended to work with keyword keys, but should work with any keys looked up via =.Source
Usage: (identical-c y)
Returns a flat contract that returns true if a value is `identical?` to y. [Any -> Contract]Source
Usage: (ifn-c cs c2)
Returns a function contract that checks a function has fixed domain that passes contracts `cs` and return value that passes contact `c2`. [(Vec Contract) Contract -> Contract] eg. (ifn-c [int-c] int-c) ;; [Int -> Int] contractSource
Usage: (make-blame & {:as bls})
Make a new blame object. Keyword arguments: - :message A string message, String - :positive Positive blame party, (U String Symbol) - :negative Negative blame party, (U String Symbol) - :file File that contains contract, (U Str nil) - :line Line where contract occurs, (U Int nil) - :column Column where contract occurs, (U Int nil)Source
Usage: (make-contract & {:keys [name first-order projection flat?], :or {flat? false}})
Make a new contract.
Keyword arguments: (see Contract datatype for more details)
- :name Name of the contract, (U Symbol String)
- :first-order First-order predicate for this contract, [Any -> Any]
- :projection Curried function taking blame and the value to check,
and returns a new checked value, or throws blame.
[Blame -> [Any -> Any]]
- :flat? True if this is a flat contract, Boolean
Source
Usage: (make-flat-contract & args)
Calls `make-contract` but also passes `:flat? true` as the first arguments.Source
Usage: (map->Blame m#)
Factory function for class clojure.core.typed.contract.Blame, taking a map of keywords to field values.Source
Usage: (map->Contract m#)
Factory function for class clojure.core.typed.contract.Contract, taking a map of keywords to field values.Source
Usage: (or-c & cs)
Returns a contract that checks a value passes at least
one of the contracts `cs`.
Any number of flat contracts may be passed to or-c. However,
if more than one higher-order contract is provided, each time
this contract is used, at most *one* may pass its first-order
predicate.
For example, (or-c (ifn-c [int-c] int-c) (ifn-c [] int-c))
cannot be checked against `clojure.core/+` because
the first-order check for both contracts (`ifn?`) passes.
[Contract * -> Contract]
eg. (or-c int-c nil-c) ;; (U Int nil)
(or-c int-c (ifn-c [int-c] int-c)) ;; (U Int [Int -> Int])
Source
Usage: (seqable-c c)
Alpha - subject to change. Returns a contract that checks Seqable things. [Contract -> Contract]Source
Usage: (swap-blame x)
Swap a blame object's blame parties. [Blame -> Blame]Source
Usage: (throw-blame {:keys [message positive negative file line column], :as b})
Throw a blame object [Blame -> Nothing]Source
Usage: (create-env n)
For name n, creates defs for {n}, {n}-kw, add-{n},
and reset-{n}!
Source
This namespace contains easy tools for hole driven developmentSee also: Hole Driven Development
Usage: (->NoisyHole)
Positional factory function for class clojure.core.typed.hole.NoisyHole.Source
Usage: (noisy-hole)
A noisy hole. The type system will complain when (noisy-hole) is used in positions that expect a type more specific than Object or Any. Use (noisy-hole) as a placeholder for code. Throws an exception when evaluted.Source
Usage: (silent-hole)
A silent hole. (silent-hole) passes for any other type when type checking. Use (silent-hole) as a placeholder for code. Throws an exception when evaluted.Source
Extensible languages in Clojure, a la Racket's #lang.
This is a simple library that monkey patches clojure.core/load
to be extensible to different backends.
`monkey-patch-extensible-load` does the actual monkey-patching and
must be called explicitly.
`lang-dispatch` is a map from keywords to alternative `load` functions
(of type [String -> nil]). The corresponding function will be used to
load a file according its :lang metadata entry in the `ns` form.
To add a new implementation, use
(alter-var-root lang-dispatch assoc :new-impl my-load)
eg. A file with a `ns` form
(ns fancy-ns-form
{:lang :new-impl})
will use `my-load` to load the file.
Usage: (default-load1 base-resource-path)
Roughly equivalent to clojure.core/load.Source
Usage: (extensible-eval form)
Evaluates the form data structure (not text!) and returns the result.Source
Usage: (extensible-load & paths)
Loads Clojure code from resources in classpath. A path is interpreted as classpath-relative if it begins with a slash or relative to the root directory for the current namespace otherwise.Added in Gradual Typing version 1.0
Usage: (file-lang res)
Returns the :lang entry in ns form in the given namespace.Source
Usage: (install)
(install features)
A no-argument function that installs extensible `eval` and `load` alternatives that respect :lang ns metadataSource
A map from :lang entries to their corresponding `load` and `eval` alternatives.Source
A no-argument function that installs the extensible `eval` function over clojure.core/eval.Source
A no-argument function that installs the extensible `load` function over clojure.core/load.Source
Usage: (ns-lang ns)
Returns the :lang value in the give Namespace's metadata.Source
Front end for actual implementation in clojure.core.typed.load1. Indirection is necessary to delay loading core.typed as long as possible.
Usage: (install)
(install features)
Install the :core.typed :lang. Takes an optional set of features
to install, defaults to #{:load :eval}.
Features:
- :load Installs typed `load` over `clojure.core/load`
- :eval Installs typed `eval` over `clojure.core/eval`
eg. (install) ; installs `load` and `eval`
eg. (install #{:eval}) ; installs `eval`
eg. (install #{:load}) ; installs `load`
Source
Usage: (install-typed-load)
Extend the :lang dispatch table with the :core.typed languageSource
Usage: (load-typed-file filename)
(load-typed-file filename env)
(load-typed-file filename env opts)
Loads a whole typed namespace, returns nil. Assumes the file is typed.Source
Usage: (monkey-patch-typed-eval)
Install the :core.typed :lang, and monkey patch `eval`Source
Usage: (monkey-patch-typed-load)
Install the :core.typed :lang, and monkey patch `load`Source
Usage: (typed-load1 base-resource-path)
Checks if the given file is typed, and loads it with core.typed if so, otherwise with clojure.core/loadSource
Implementation of clojure.core.typed.load.
Usage: (install)
(install features)
Install the :core.typed :lang. Takes an optional set of features
to install, defaults to #{:load :eval}.
Features:
- :load Installs typed `load` over `clojure.core/load`
- :eval Installs typed `eval` over `clojure.core/eval`
eg. (install) ; installs `load` and `eval`
eg. (install #{:eval}) ; installs `eval`
eg. (install #{:eval}) ; installs `load`
Source
Usage: (install-typed-load)
Extend the :lang dispatch table with the :core.typed languageSource
Usage: (load-typed-file filename)
(load-typed-file filename env)
(load-typed-file filename env opts)
Loads a whole typed namespace, returns nil. Assumes the file is typed.Source
Usage: (monkey-patch-typed-eval)
Install the :core.typed :lang, and monkey patch `eval`Source
Usage: (monkey-patch-typed-load)
Install the :core.typed :lang, and monkey patch `load`Source
Usage: (typed-load1 base-resource-path)
Checks if the given file is typed, and loads it with core.typed if so, otherwise with clojure.core/loadSource
Usage: (atom & args)
Like atom, but with optional type annotations.
Same as (atom (ann-form init t) args*)
eg. (atom 1) : (Atom1 (Value 1))
(atom :- Num, 1) : (Atom1 Num)
Source
Usage: (def name docstring? :- type? expr)
Like clojure.core/def with optional type annotations
NB: in Clojure it is impossible to refer a var called `def` as it is a
special form. Use an alias prefix (eg. `t/def`).
If an annotation is provided, a corresponding `ann` form
is generated, otherwise it expands identically to clojure.core/def
eg. ;same as clojure.core/def
(def vname 1)
;with Number `ann`
(def vname :- Number 1)
;doc
(def vname
"Docstring"
:- Long
1)
Source
Usage: (defn kw-args? name docstring? attr-map? [param :- type *] :- type exprs*)
(defn kw-args? name docstring? attr-map? ([param :- type *] :- type exprs*) +)
Like defn, but expands to clojure.core.typed/fn. If a polymorphic binder is supplied before the var name, expands to clojure.core.typed/pfn. eg. (defn fname [a :- Number, b :- (U Symbol nil)] :- Integer ...) ;annotate return (defn fname [a :- String] :- String ...) ;multi-arity (defn fname ([a :- String] :- String ...) ([a :- String, b :- Number] :- Long ...)) ;polymorphic function (defn :forall [x y] fname ([a :- x] :- (Coll y) ...) ([a :- Str, b :- y] :- y ...))Source
Usage: (defprotocol & body)
Like defprotocol, but with optional type annotations.
Omitted annotations default to Any. The first argument
of a protocol cannot be annotated.
Add a binder before the protocol name to define a polymorphic
protocol. A binder before the method name defines a polymorphic
method, however a method binder must not shadow type variables
introduced by a protocol binder.
Return types for each method arity can be annotated.
Unlike clojure.core/defprotocol, successive methods can
have the same arity. Semantically, providing multiple successive
methods of the same arity is the same as just providing the left-most
method. However the types for these methods will be accumulated into
a Fn type.
eg. ;annotate single method
(defprotocol MyProtocol
(a [this a :- Integer] :- Number))
;polymorphic protocol
(defprotocol [[x :variance :covariant]]
MyProtocol
(a [this a :- Integer] :- Number))
;multiple types for the same method
(defprotocol [[x :variance :covariant]]
MyProtocol
(a [this a :- Integer] :- Integer
[this a :- Long] :- Long
[this a :- Number] :- Number))
;polymorphic method+protocol
(defprotocol [[x :variance :covariant]]
MyProtocol
([y] a [this a :- x, b :- y] :- y))
Source
Usage: (fn name? [param :- type* & param :- type * ?] :- type? exprs*)
(fn name? ([param :- type* & param :- type * ?] :- type? exprs*) +)
Like clojure.core/fn, but with optional annotations.
eg. ;these forms are equivalent
(fn [a] b)
(fn [a :- Any] b)
(fn [a :- Any] :- Any b)
(fn [a] :- Any b)
;annotate return
(fn [a :- String] :- String body)
;named fn
(fn fname [a :- String] :- String body)
;rest parameter
(fn [a :- String & b :- Number *] body)
;dotted rest parameter
(fn [a :- String & b :- Number ... x] body)
;multi-arity
(fn fname
([a :- String] :- String ...)
([a :- String, b :- Number] :- String ...))
; polymorphic binder
(fn :forall [x y z]
fname
([a :- String] :- String ...)
([a :- String, b :- Number] :- String ...))
Source
Usage: (let [binding :- type? init*] exprs*)
Like clojure.core/let but supports optional type annotations.
eg. (let [a :- Type, b
a2 1.2]
body)
Source
Usage: (loop [binding :- type? init*] exprs*)
Like clojure.core/loop, and supports optional type annotations.
Arguments default to a generalised type based on the initial value.
eg. (loop [a :- Number 1
b :- (U nil Number) nil]
...)
Source
Usage: (ref & args)
Like ref, but with optional type annotations.
Same as (ref (ann-form init t) args*)
eg. (ref 1) : (Ref1 (Value 1))
(ref :- Num, 1) : (Ref1 Num)
Source
Usage: (when-let-fail b & body)
Like when-let, but fails if the binding yields a false value.Source
Adds runtime checks where annotations are instead of type checking
Usage: (check expr)
(check expr expected)
Add runtime checks to the output AST, propagating just enough types for immediate ann-form expressions to propagate to fn expected types. Static checking is disabled, outside ill-formed types. Unsafe contracts can be generated, and contract generation cannot fail. Assumes collect-expr is already called on this AST.Source
Usage: (alias-hmap-type env' config t)
Recur up from the leaves of a type and replace HMaps and unions with fresh type aliases. Also registers these type aliases in alias-env. Does not traverse existing type aliases.Source
Usage: (alias-single-HMaps env config)
Traverse the type and alias environments and ensure all HMaps are aliasedSource
Usage: (check expr)
(check expr expected)
Assumes collect-expr is already called on this AST.Source
Usage: (delete-generated-annotations-in-str old)
Delete lines between generate-ann-start and generate-ann-end.Source
Usage: (follow-aliases env config t)
Rename aliases to avoid redundant paths. Also delete unnecessary aliases for simple types. Also inline aliases if they are simple enough.Source
Usage: (follow-all env config)
Squash all aliases referenced by a type environment.Source
Usage: (fv env v)
(fv env v recur?)
(fv env v recur? seen-alias)
Returns the aliases referred in this type, in order of discovery. If recur? is true, also find aliases referred by other aliases found.Source
Usage: (gen-current2)
Turn the currently inferred type environment into type aliases. Also print the alias environment.Source
Usage: (gen-current3)
Turn the currently inferred type environment into type aliases. Also print the alias environment.Source
Usage: (generate-tenv env config {:keys [infer-results equivs], :as is})
Reset and populate global type environment.Source
Usage: (insert-generated-annotations-in-str old ann-str config)
Insert annotations after ns form.Source
Usage: (likely-HMap-dispatch t)
Given a HMap type, returns a vector tuple
of the best guess for the dispatch entry for this HMap.
The first entry contains the keyword key, and the second
contains a set of keys that dispatch to this type.
eg. (likely-HMap-dispatch (prs '{:op ':val}))
;=> [:op #{:val}]
eg. (likely-HMap-dispatch (prs '{:T (U ':intersection :union)}))
;=> [:T #{:intersection :union}]
Source
Usage: (mapply f & args)
Applies a function f to the argument list formed by concatenating everything but the last element of args with the last element of args. This is useful for applying a function that accepts keyword arguments to a map.Source
Usage: (relevant-aliases env)
Returns all referenced aliases from the type environment.Source
Usage: (squash env config t)
Recur down an alias and merge types based on their keysets. Also merge back up if possible.Source
Usage: (squash-horizonally env config)
Join aliases that refer to exactly
one HMap with the same keyset.
If maps are recursively defined, don't
merge them.
eg. {a1 '{:a Int}
a2 '{:a Bool}}
=>
{a1 '{:a (U Int Bool)}
a2 a1}
eg. {a1 '{:a a2}
a2 '{:a (U nil a1)}}
=>
{a1 '{:a a2}
a2 '{:a (U nil a1)}}
Source
Usage: (update-file file f & args)
Reads file as a string, calls f on the string plus any args, then writes out return value of f as the new contents of file. Does not modify file if the content is unchanged.Source
Usage: (var-constraints vsym)
Return the bag of constraints in the current results-atom for the given fully qualified var. eg. (var-constraints 'clojure.core.typed.test.mini-occ/parse-exp)Source
Usage: (walk ast pre post)
Walk the ast applying `pre` when entering the nodes, and `post` when exiting. Both functions must return a valid node since the returned value will replace the node in the AST which was given as input to the function. Short-circuits on reduced.Source
Usage: (statistics nsyms)
Takes a collection of namespace symbols and returns a map mapping the namespace symbols to a map of dataSource
If true, print complete forms in error messages. Bind around a type checking form like cf or check-ns. eg. (binding [*verbose-forms* true] (cf ['deep ['deep ['deep ['deep]]]] Number)) ;=> <full form in error>Source
If true, print fully qualified types in error messages and return values. Bind around a type checking form like cf or check-ns. eg. (binding [*verbose-types* true] (cf 1 Number)) ;=> java.lang.NumberSource