How can I elegantly combine resource and exception handling? - clojure

I'm writing a Clojure wrapper for an object-oriented API that heavily involves resource handling. For instance, for the Foo object, I've written three basic functions: foo?, which returns true iff something is a Foo; create-foo, which attempts to obtain the resources to create a Foo, then returns a map containing a return code and (if the construction succeeded) the newly created Foo; and destroy-foo, which takes a Foo and releases its resources. Here are some stubs for those three functions:
(def foo? (comp boolean #{:placeholder}))
(defn create-foo []
(let [result (rand-nth [::success ::bar-too-full ::baz-not-available])]
(merge {::result result}
(when (= ::success result)
{::foo :placeholder}))))
(defn destroy-foo [foo] {:pre [(foo? foo)]} nil)
Obviously, every time create-foo is called and succeeds, destroy-foo must be called with the returned Foo. Here's a simple example that doesn't use any custom macros:
(let [{:keys [::result ::foo]} (create-foo)]
(if (= ::success result)
(try
(println "Got a Foo:")
(prn foo)
(finally
(destroy-foo foo)))
(do
(println "Got an error:")
(prn result))))
There's a lot of boilerplate here: the try-finally-destroy-foo construct must be present to ensure that all Foo resources are released, and the (= ::success result) test must be present to ensure that nothing gets run assuming a Foo when there is no Foo.
Some of that boilerplate can be eliminated by a with-foo macro, similar to the with-open macro in clojure.core:
(defmacro with-foo [bindings & body]
{:pre [(vector? bindings)
(= 2 (count bindings))
(symbol? (bindings 0))]}
`(let ~bindings
(try
~#body
(finally
(destroy-foo ~(bindings 0))))))
While this does help somewhat, it doesn't do anything about the (= ::success result) boilerplate, and now two separate binding forms are required to achieve the desired result:
(let [{:keys [::result] :as m} (create-foo)]
(if (= ::success result)
(with-foo [foo (::foo m)]
(println "Got a Foo:")
(prn foo))
(do
(println "Got an error:")
(prn result))))
I simply can't figure out a good way to handle this. I mean, I could complect the behaviors of if-let and with-foo into some sort of if-with-foo macro:
(defmacro if-with-foo [bindings then else]
{:pre [(vector? bindings)
(= 2 (count bindings))]}
`(let [{result# ::result foo# ::foo :as m#} ~(bindings 1)
~(bindings 0) m#]
(if (= ::success result#)
(try
~then
(finally
(destroy-foo foo#)))
~else)))
This does eliminate even more boilerplate:
(if-with-foo [{:keys [::result ::foo]} (create-foo)]
(do
(println "Got a Foo:")
(prn foo))
(do
(println "Got a result:")
(prn result)))
However, I don't like this if-with-foo macro for several reasons:
it's very tightly coupled to the specific structure of the map returned by create-foo
unlike if-let, it causes all bindings to be in scope in both branches
its ugly name reflects its ugly complexity
Are these macros the best I can do here? Or is there a more elegant way to handle resource handling with possible resource obtainment failure? Perhaps this is a job for monads; I don't have enough experience with monads to know whether they would be useful tool here.

I'd add an error-handler to with-foo. This way the macro has a focus on what should be done. However, this simplifies the code only when all error-cases are treated by a handful of error handlers. If you have to define a custom error-handler every time you call with-foo this solution makes readability worse than an if-else construct.
I added copy-to-map. copy-to-map should copy all relevant information from the object to a map. This way the user of the macro doesn't by accident return the foo-object, since it gets destroyed inside the macro
(defn foo? [foo]
(= ::success (:result foo)))
(defn create-foo [param-one param-two]
(rand-nth (map #(merge {:obj :foo-obj :result %} {:params [param-one param-two]})
[::success ::bar-too-full ::baz-not-available])))
(defn destroy-foo [foo]
nil)
(defn err-handler [foo]
[:error foo])
(defn copy-to-map [foo]
;; pseudo code here
(into {} foo))
(defmacro with-foo [[f-sym foo-params & {:keys [on-error]}] & body]
`(let [foo# (apply ~create-foo [~#foo-params])
~f-sym (copy-to-map foo#)]
(if (foo? foo#)
(try ~#body
(finally (destroy-foo foo#)))
(when ~on-error
(apply ~on-error [~f-sym])))))
Now you call it
(with-foo [f [:param-one :param-two] :on-error err-handler]
[:success (str "i made it: " f)])

Building from #murphy's excellent idea to put the error handler into with-foo's bindings to keep the focus on the normal case, I've ended up with a solution that I like quite a lot:
(defmacro with-foo [bindings & body]
{:pre [(vector? bindings)
(even? (count bindings))]}
(if-let [[sym init temp error] (not-empty bindings)]
(let [error? (= :error temp)]
`(let [{result# ::result foo# ::foo :as m#} ~init]
(if (contains? m# ::foo)
(try
(let [~sym foo#]
(with-foo ~(subvec bindings (if error? 4 2))
~#body))
(finally
(destroy-foo foo#)))
(let [f# ~(if error? error `(constantly nil))]
(f# result#)))))
`(do
~#body)))
like my if-with-foo macro in the question, this with-foo macro is still tied to the structure returned by create-foo; unlike my if-with-foo macro and #murphy's with-foo macro, it eliminates the need for the user to manually take apart that structure
all names are properly scoped; the user's sym is only bound in the main body, not in the :error handler, and conversely, the ::result is only bound in the :error handler, not in the main body
like #murphy's solution, this macro has a nice, fitting name, instead of something ugly like if-with-foo
unlike #murphy's with-foo macro, this with-foo macro allows the user to provide any init value, rather than forcing a call to create-foo, and doesn't transform the returned value
The most basic use case simply binds a symbol to a Foo returned by create-foo in some body, returning nil if the construction fails:
(with-foo [foo (create-foo)]
["Got a Foo!" foo])
To handle the exceptional case, an :error handler can be added to the binding:
(with-foo [foo (create-foo)
:error (partial vector "Got an error!")]
["Got a Foo!" foo])
Any number of Foo bindings can be used:
(with-foo [foo1 (create-foo)
foo2 (create-foo)]
["Got some Foos!" foo1 foo2])
Each binding can have its own :error handler; any missing error handlers are replaced with (constantly nil):
(with-foo [foo1 (create-foo)
:error (partial vector "Got an error!")
foo2 (create-foo)]
["Got some Foos!" foo1 foo2])

Related

Getting a function's name in its body or :test body

In clojure, can one idiomatically obtain a function's name inside of its body, hopefully accomplishing so without introducing a new wrapper for the function's definition? can one also access the function's name inside of the body of the function's :test attribute as well?
For motivation, this can be helpful for certain logging situations, as well as for keeping the body of :test oblivious to changes to the name of the function which it is supplied for.
A short elucidation of the closest that meta gets follows; there's no this notion to supply to meta, as far as I know, in clojure.
(defn a [] (:name (meta (var a))))
Obviously it is easy to accomplish with a wrapper macro.
Edit: luckily no one so far mentioned lambda combinators.
There are 2 ways to approach your question. However, I suspect that to fully automate what you want to do, you would need to define your own custom defn replacement/wrapper.
The first thing to realize is that all functions are anonymous. When we type:
(defn hello [] (println "hi"))
we are really typing:
(def hello (fn [] (println "hi"))
we are creating a symbol hello that points to an anonymous var which in turn points to an anonymous function. However, we can give the function an "internal name" like so:
(def hello (fn fn-hello [] (println "hi")))
So now we can access the function from the outside via hello or from the inside using either hello of fn-hello symbols (please don't ever use hello in both locations or you create a lot of confusion...even though it is legal).
I frequently use the fn-hello method in (otherwise) anonymous functions since any exceptions thrown will include the fn-hello symbol which makes tracking down the source of the problem much easier (the line number of the error is often missing from the stack trace). For example when using Instaparse we need a map of anonymous transform functions like:
{
:identifier fn-identifier
:string fn-string
:integer (fn fn-integer [arg] [:integer (java.lang.Integer. arg)])
:boolean (fn fn-boolean [arg] [:boolean (java.lang.Boolean. arg)])
:namespace (fn fn-namespace [arg] [:namespace arg])
:prefix (fn fn-prefix [arg] [:prefix arg])
:organization (fn fn-organization [arg] [:organization arg])
:contact (fn fn-contact [arg] [:contact arg])
:description (fn fn-description [arg] [:description arg])
:presence (fn fn-presence [arg] [:presence arg])
:revision (fn fn-revision [& args] (prepend :revision args))
:iso-date (fn fn-iso-date [& args] [:iso-date (str/join args)])
:reference (fn fn-reference [arg] [:reference arg])
:identity (fn fn-identity [& args] (prepend :identity args))
:typedef (fn fn-typedef [& args] (prepend :typedef args))
:container (fn fn-container [& args] (prepend :container args))
:rpc (fn fn-rpc [& args] (prepend :rpc args))
:input (fn fn-input [& args] (prepend :input args))
...<snip>...
}
and giving each function the "internal name" makes debugging much, much easier. Perhaps this would be unnecessary if Clojure had better error messages, but that is a longstanding (& so far unfullfilled) wish.
You can find more details here: https://clojure.org/reference/special_forms#fn
If you read closely, it claims that (defn foo [x] ...) expands into
(def foo (fn foo [x] ...))
although you may need to experiment to see if this has already solved the use-case you are seeking. It works either way as seen in this example where we explicitly avoid the inner fn-fact name:
(def fact (fn [x] ; fn-fact omitted here
(if (zero? x)
1
(* x (fact (dec x))))))
(fact 4) => 24
This version also works:
(def fact (fn fn-fact [x]
(if (zero? x)
1
(* x (fn-fact (dec x))))))
(fact 4) => 24
(fn-fact 4) => Unable to resolve symbol: fn-fact
So we see that the "internal name" fn-fact is hidden inside the function and is invisible from the outside.
A 2nd approach, if using a macro, is to use the &form global data to access the line number from the source code. In the Tupelo library this technique is used to improve error messages for the
(defmacro dotest [& body] ; #todo README & tests
(let [test-name-sym (symbol (str "test-line-" (:line (meta &form))))]
`(clojure.test/deftest ~test-name-sym ~#body)))
This convenience macro allows the use of unit tests like:
(dotest
(is (= 3 (inc 2))))
which evalutes to
(deftest test-line-123 ; assuming this is on line 123 in source file
(is (= 3 (inc 2))))
instead of manually typing
(deftest t-addition
(is (= 3 (inc 2))))
You can access (:line (meta &form)) and other information in any macro which can make your error messages and/or Exceptions much more informative to the poor reader trying to debug a problem.
Besides the above macro wrapper example, another (more involved) example of the same technique can be seen in the Plumatic Schema library, where they wrap clojure.core/defn with an extended version.
You may also wish to view this question for clarification on how Clojure uses the "anonymous" var as an intermediary between a symbol and a function: When to use a Var instead of a function?

Why in this example calling (f arg) and calling the body of f explicitly yields different results?

First, I have no experience with CS and Clojure is my first language, so pardon if the following problem has a solution, that is immediately apparent for a programmer.
The summary of the question is as follows: one needs to create atoms at will with unknown yet symbols at unknown times. My approach revolves around a) storing temporarily the names of the atoms as strings in an atom itself; b) changing those strings to symbols with a function; c) using a function to add and create new atoms. The problem pertains to step "c": calling the function does not create new atoms, but using its body does create them.
All steps taken in the REPL are below (comments follow code blocks):
user=> (def atom-pool
#_=> (atom ["a1" "a2"]))
#'user/atom-pool
'atom-pool is the atom that stores intermediate to-be atoms as strings.
user=> (defn atom-symbols []
#_=> (mapv symbol (deref atom-pool)))
#'user/atom-symbols
user=> (defmacro populate-atoms []
#_=> (let [qs (vec (remove #(resolve %) (atom-symbols)))]
#_=> `(do ~#(for [s qs]
#_=> `(def ~s (atom #{}))))))
#'user/populate-atoms
'populate-atoms is the macro, that defines those atoms. Note, the purpose of (remove #(resolve %) (atom-symbols)) is to create only yet non-existing atoms. 'atom-symbols reads 'atom-pool and turns its content to symbols.
user=> (for [s ['a1 'a2 'a-new]]
#_=> (resolve s))
(nil nil nil)
Here it is confirmed that there are no 'a1', 'a2', 'a-new' atoms as of yet.
user=> (defn new-atom [a]
#_=> (do
#_=> (swap! atom-pool conj a)
#_=> (populate-atoms)))
#'user/new-atom
'new-atom is the function, that first adds new to-be atom as string to `atom-pool. Then 'populate-atoms creates all the atoms from 'atom-symbols function.
user=> (for [s ['a1 'a2 'a-new]]
#_=> (resolve s))
(#'user/a1 #'user/a2 nil)
Here we see that 'a1 'a2 were created as clojure.lang.Var$Unbound just by defining a function, why?
user=> (new-atom "a-new")
#'user/a2
user=> (for [s ['a1 'a2 'a-new]]
#_=> (resolve s))
(#'user/a1 #'user/a2 nil)
Calling (new-atom "a-new") did not create the 'a-new atom!
user=> (do
#_=> (swap! atom-pool conj "a-new")
#_=> (populate-atoms))
#'user/a-new
user=> (for [s ['a1 'a2 'a-new]]
#_=> (resolve s))
(#'user/a1 #'user/a2 #'user/a-new)
user=>
Here we see that resorting explicitly to 'new-atom's body did create the 'a-new atom. 'a-new is a type of clojure.lang.Atom, but 'a1 and 'a2 were skipped due to already being present in the namespace as clojure.lang.Var$Unbound.
Appreciate any help how to make it work!
EDIT: Note, this is an example. In my project the 'atom-pool is actually a collection of maps (atom with maps). Those maps have keys {:name val}. If a new map is added, then I create a corresponding atom for this map by parsing its :name key.
"The summary of the question is as follows: one needs to create atoms at will with unknown yet symbols at unknown times. "
This sounds like a solution looking for a problem. I would generally suggest you try another way of achieving whatever the actual functionality is without generating vars at runtime, but if you must, you should use intern and leave out the macro stuff.
You cannot solve this with macros since macros are expanded at compile time, meaning that in
(defn new-atom [a]
(do
(swap! atom-pool conj a)
(populate-atoms)))
populate-atoms is expanded only once; when the (defn new-atom ...) form is compiled, but you're attempting to change its expansion when new-atom is called (which necessarily happens later).
#JoostDiepenmaat is right about why populate-atoms is not behaving as expected. You simply cannot do this using macros, and it is generally best to avoid generating vars at runtime. A better solution would be to define your atom-pool as a map of keywords to atoms:
(def atom-pool
(atom {:a1 (atom #{}) :a2 (atom #{})}))
Then you don't need atom-symbols or populate-atoms because you're not dealing with vars at compile-time, but typical data structures at run-time. Your new-atom function could look like this:
(defn new-atom [kw]
(swap! atom-pool assoc kw (atom #{})))
EDIT: If you don't want your new-atom function to override existing atoms which might contain actual data instead of just #{}, you can check first to see if the atom exists in the atom-pool:
(defn new-atom [kw]
(when-not (kw #atom-pool)
(swap! atom-pool assoc kw (atom #{}))))
I've already submitted one answer to this question, and I think that that answer is better, but here is a radically different approach based on eval:
(def atom-pool (atom ["a1" "a2"]))
(defn new-atom! [name]
(load-string (format "(def %s (atom #{}))" name)))
(defn populate-atoms! []
(doseq [x atom-pool]
(new-atom x)))
format builds up a string where %s is substituted with the name you're passing in. load-string reads the resulting string (def "name" (atom #{})) in as a data structure and evals it (this is equivalent to (eval (read-string "(def ...)
Of course, then we're stuck with the problem of only defining atoms that don't already exist. We could change the our new-atom! function to make it so that we only create an atom if it doesn't already exist:
(defn new-atom! [name]
(when-not (resolve (symbol name))
(load-string (format "(def %s (atom #{}))" name name))))
The Clojure community seems to be against using eval in most cases, as it is usually not needed (macros or functions will do what you want in 99% of cases*), and eval can be potentially unsafe, especially if user input is involved -- see Brian Carper's answer to this question.
*After attempting to solve this particular problem using macros, I came to the conclusion that it either cannot be done without relying on eval, or my macro-writing skills just aren't good enough to get the job done with a macro!
At any rate, I still think my other answer is a better solution here -- generally when you're getting way down into the nuts & bolts of writing macros or using eval, there is probably a simpler approach that doesn't involve metaprogramming.

Using with-redefs inside a doseq

I have a Ring handler which uses several functions to build the response. If any of these functions throw an exception, it should be caught so a custom response body can be written before returning a 500.
I'm writing the unit test for the handler, and I want to ensure that an exception thrown by any of these functions will be handled as described above. My instinct was to use with-redefs inside a doseq:
(doseq [f [ns1/fn1 ns1/fn2 ns2/fn1]]
(with-redefs [f (fn [& args] (throw (RuntimeException. "fail!"))]
(let [resp (app (request :get "/foo")))))]
(is (= (:status resp) 500))
(is (= (:body resp) "Something went wrong")))))
Of course, given that with-redefs wants to change the root bindings of vars, it is treating f as a symbol. Is there any way to get it to rebind the var referred to by f? I suspect that I'm going to need a macro to accomplish this, but I'm hoping that someone can come up with a clever solution.
with-redefs is just sugar over repeated calls to alter-var-root, so you can just write the desugared form yourself, something like:
(doseq [v [#'ns1/fn1 #'ns1/fn2 #'ns2/fn1]]
(let [old #v]
(try
(alter-var-root v (constantly (fn [& args]
(throw (RuntimeException. "fail!")))))
(let [resp (app (request :get "/foo")))
(is (= (:status resp) 500))
(is (= (:body resp) "Something went wrong")))
(finally (alter-var-root v (constantly old))))))
Following on from amalloy's great answer, here's a utility function that I wrote to use in my tests:
(defn with-mocks
"Iterates through a list of functions to-mock, rebinding each to mock-fn, and calls
test-fn with the optional test-args.
Example:
(defn foobar [a b]
(try (+ (foo a) (bar b))
(catch Exception _ 1)))
(deftest test-foobar
(testing \"Exceptions are handled\"
(with-mocks
[#'foo #'bar]
(fn [& _] (throw (RuntimeException. \"\")))
(fn [a b] (is (= 1 (foobar a b)))) 1 2)))"
[to-mock mock-fn test-fn & test-args]
(doseq [f to-mock]
(let [real-fn #f]
(try
(alter-var-root f (constantly mock-fn))
(apply test-fn test-args)
(finally
(alter-var-root f (constantly real-fn)))))))

Handling user input validation with preconditions functionally in Clojure

I write a game server and have to check that messages arriving from users are correct and valid. That means they have to be of correct syntax, comply to parameter formatting and are semantically correct, i.e. complying to the game's rules.
My goal is to have an expressive, functional way without throwing exceptions that allows composability as good as possible.
I am aware of other similar questions but they either refer to {:pre ..., :post ...} which I dislike as only stringified information can be processed once the exception is thrown, or refer exception handling in general which I dislike because Clojure should be able to do this kind of task, or they refer to Haskell's monadic style with e.g. a maybe Monad à la (-> [err succ]) which I also dislike because Clojure should be able to handle this kind of task without needing a Monad.
So far I do the ugly way using cond as pre-condition checker and error codes which I then send back to the client who send the request:
(defn msg-handler [client {:keys [version step game args] :as msg}]
(cond
(nil? msg) :4001
(not (valid-message? msg)) :4002
(not (valid-version? version)) :5050
(not (valid-step? step)) :4003
(not (valid-game-id? game)) :4004
(not (valid-args? args)) :4007
:else (step-handler client step game args)))
and similar...
(defn start-game [game-id client]
(let [games #*games*
game (get games game-id)
state (:state game)
players (:players game)]
(cond
(< (count players) 2) :4120
(= state :started) :4093
(= state :finished) :4100
:else ...)))
Another way would be to write a macro, similar to defn and {:pre} but instead of throwing an AssertionError throw an ex-info with a map, but again: opposed to exception throwing.
The heart of your question seems to be in your comment:
Yeah, maybe I should explain what about this is "ugly": It's the not-well composability of just return an actual result, which can be represented almost arbitrarily and a numbered keyword as error. My callstack looks like this: (-> msg msg-handler step-handler step-N sub-function), and all of them could return this one error type, but none of them returns the same success type and another thing is, that I have to manually design if en error return type should short-circuit or has to be expected to do some intermediate work (undo data changes or notify other clients in parallel)
Clojure 1.5+ has the some-> threading macro to get rid of nil? check boilerplate. We just need to gently adjust the code to substitute the nil? check for a check of our choice.
(defmacro pred->
"When predicate is not satisfied, threads expression into the first form
(via ->), and when that result does not satisfy the predicate, through the
next, etc. If an expression satisfies the predicate, that expression is
returned without evaluating additional forms."
[expr pred & forms]
(let [g (gensym)
pstep (fn [step] `(if (~pred ~g) ~g (-> ~g ~step)))]
`(let [~g ~expr
~#(interleave (repeat g) (map pstep forms))]
~g)))
Note with this definition, (pred-> expr nil? form1 form2 ...) is (some-> expr form1 form2...). But now we can use other predicates.
Example
(defn foo [x] (if (even? x) :error-even (inc x)))
(defn bar [x] (if (zero? (mod x 3)) :error-multiple-of-three (inc x)))
(pred-> 1 keyword? foo) ;=> 2
(pred-> 1 keyword? foo foo) ;=> :error-even
(pred-> 1 keyword? foo foo foo) ;=> :error-even
(pred-> 1 keyword? foo bar foo bar) ;=> 5
(pred-> 1 keyword? foo bar foo bar foo bar foo bar) ;=> :error-multiple-of-three
Your use case
A flexible choice would be to make a wrapper for validation errors
(deftype ValidationError [msg])
Then you can wrap your error code/messages as in (->ValidationError 4002) and change your threading to
(pred-> msg #(instance? ValidationError %)
msg-handler step-handler step-N sub-function)

Converting a string into a function that is not in a namespace in clojure

Here is the sample code I want to get to work:
(letfn [(CONC [f] f)
(CONT [f] (str "\newline" f))]
((voodoo "CONC") "hamster"))
Is there some voodo that will make it call the CONC function with hamster as the parameter? That is, is there some way to convert the string "CONC" into a function that is not bound to a namespace but rather to a local binding?
EDIT:
To be clearer, the way this will be called is:
(map #((voodoo (:tag %)) (:value %))
[
{:tag "CONC" :value "hamster"}
{:tag "CONT" :value "gerbil"}
]
)
I'd probably solve this by creating a map of functions indexed by strings:
(def voodoo
{"CONC" (fn [f] f)
"CONT" (fn [f] (str "\newline" f))})
Then your desired code should work directly (exploiting the fact that a map is a function that looks up it's argument)
(map #((voodoo (:tag %)) (:value %))
[
{:tag "CONC" :value "hamster"}
{:tag "CONT" :value "gerbil"}
]
)
Note that the functions here are fully anonymous - you don't need them to be referenced anywhere in the namespace for this to work. In my view this is a good thing, because unless you also need the functions somewhere else then it's best to avoid polluting your top-level namespace too much.
No. Eval does not have access to the local/lexical environment, ever.
Edit: This is not a very good answer, and not really accurate either. You could write voodoo as a macro, and then it doesn't need runtime access to the lexical environment, just compile-time. However, this means it would only work if you know at compile time that the function you want to call is x, and so it wouldn't be very useful - why not just type x instead of (voodoo "x")?
(defmacro voodoo [fname]
(symbol fname))
(letfn [(x [y] (inc y))]
((voodoo "x") 2))
;; 3
(letfn [(x [y] (inc y))]
(let [f "x"]
((voodoo f) 2)))
;; error
Well, it's sort of possible:
(defmacro voodoo [s]
(let [env (zipmap (map (partial list 'quote) (keys &env))
(keys &env))]
`(if-let [v# (~env (symbol ~s))]
v#
(throw (RuntimeException. "no such local")))))
...and now we can do weird stuff like this:
user> (defn example [s]
(letfn [(foo [x] {:foo x})
(bar [x] {:bar x})]
((voodoo s) :quux)))
#'user/example
user> (example "foo")
{:foo :quux}
user> (example "bar")
{:bar :quux}
user> (example "quux")
; Evaluation aborted.
user> *e
#<RuntimeException java.lang.RuntimeException: no such local>
That "Evaluation aborted" means an exception was thrown.
You could also replace the throw branch of the if in voodoo with (resolve (symbol ~s)) to defer to the globals if no local is found:
(defmacro voodoo [s]
(let [env (zipmap (map (partial list 'quote) (keys &env))
(keys &env))]
`(if-let [v# (~env (symbol ~s))]
v#
(resolve (symbol ~s)))))
...and now this works with definition of example as above (though note that if you are experimenting at the REPL, you will need to recompile example after redefining voodoo):
user> (defn quux [x] {:quux x})
#'user/quux
user> (example "quux")
{:quux :quux}
Now, this is an abuse of Clojure's facilities which one would do well to try to do without. If one cannot, one should probably turn to evalive by Michael Fogus; it's a library which provides an "eval-with-locals" facility in the form of an evil function and a couple of utilities. The functionality seems to be well factored too, e.g. something like the ~(zipmap ...) thing above is encapsulated as a macro and evil there appears to be almost a drop-in replacement for eval (add the env parameter and you're good to go). I haven't read the source properly, but I probably will now, looks like fun. :-)
Im not really clear what you are asking for so i'll try a couple answers:
if you have a string that is the name of the function you wish to call:
(def name "+")
((find-var (symbol (str *ns* "/" name))) 1 2 3)
this would give voodoo a deffinition like this:
(defn voodoo [name args] (apply (find-var (symbol (str *ns* "/" name))) args))
#'clojure.core/voodoo
clojure.core=> (voodoo "+" [1 2 3])
6
clojure.core=>
this assumes your function is in the current namepace ns.
if you want to turn a string into a function you could use this pattern
(let [f (eval (read-string "(fn [] 4)"))] (f))