GithubHelp home page GithubHelp logo

plumbing's Introduction

Plumbing and Graph: the Clojure utility belt

prismatic/plumbing logo

This first release includes our 'Graph' library, our plumbing.core library of very commonly used functions (the only namespace we :use across our codebase), and a few other supporting namespaces.

New in 0.3.0: support for ClojureScript

New in 0.2.0: support for schema.core/defn-style schemas on fnks and Graphs. See (doc fnk) for details.

Leiningen dependency (Clojars):

Clojars Project

Latest API docs.

This is an alpha release. We are using it internally in production, but the API and organizational structure are subject to change. Comments and suggestions are much appreciated.

Check back often, because we'll keep adding more useful namespaces and functions as we work through cleaning up and open-sourcing our stack of Clojure libraries.

Graph: the Functional Swiss-Army Knife

Graph is a simple and declarative way to specify a structured computation, which is easy to analyze, change, compose, and monitor. Here's a simple example of an ordinary function definition, and its Graph equivalent:

(require '[plumbing.core :refer (sum)])
(defn stats
  "Take a map {:xs xs} and return a map of simple statistics on xs"
  [{:keys [xs] :as m}]
  (assert (contains? m :xs))
  (let [n  (count xs)
        m  (/ (sum identity xs) n)
        m2 (/ (sum #(* % %) xs) n)
        v  (- m2 (* m m))]
    {:n n   ; count
     :m m   ; mean
     :m2 m2 ; mean-square
     :v v   ; variance
     }))

(require '[plumbing.core :refer (fnk sum)])
(def stats-graph
  "A graph specifying the same computation as 'stats'"
  {:n  (fnk [xs]   (count xs))
   :m  (fnk [xs n] (/ (sum identity xs) n))
   :m2 (fnk [xs n] (/ (sum #(* % %) xs) n))
   :v  (fnk [m m2] (- m2 (* m m)))})

A Graph is just a map from keywords to keyword functions (learn more). In this case, stats-graph represents the steps in taking a sequence of numbers (xs) and producing univariate statistics on those numbers (i.e., the mean m and the variance v). The names of arguments to each fnk can refer to other steps that must happen before the step executes. For instance, in the above, to execute :v, you must first execute the :m and :m2 steps (mean and mean-square respectively).

We can "compile" this Graph to produce a single function (equivalent to stats), which also checks that the map represents a valid Graph:

(require '[plumbing.graph :as graph] '[schema.core :as s])
(def stats-eager (graph/compile stats-graph))

(= {:n 4
    :m 3
    :m2 (/ 25 2)
    :v (/ 7 2)}
   (into {} (stats-eager {:xs [1 2 3 6]})))

;; Missing :xs key exception
(thrown? Throwable (stats-eager {:ys [1 2 3]}))

Moreover, as of the 0.1.0 release, stats-eager is fast -- only about 30% slower than the hand-coded stats if xs has a single element, and within 5% of stats if xs has ten elements.

Unlike the opaque stats fn, however, we can modify and extend stats-graph using ordinary operations on maps:

(def extended-stats
  (graph/compile
    (assoc stats-graph
      :sd (fnk [^double v] (Math/sqrt v)))))

(= {:n 4
    :m 3
    :m2 (/ 25 2)
    :v (/ 7 2)
    :sd (Math/sqrt 3.5)}
   (into {} (extended-stats {:xs [1 2 3 6]})))

A Graph encodes the structure of a computation, but not how it happens, allowing for many execution strategies. For example, we can compile a Graph lazily so that step values are computed as needed. Or, we can parallel-compile the Graph so that independent step functions are run in separate threads:

(def lazy-stats (graph/lazy-compile stats-graph))

(def output (lazy-stats {:xs [1 2 3 6]}))
;; Nothing has actually been computed yet
(= (/ 25 2) (:m2 output))
;; Now :n and :m2 have been computed, but :v and :m are still behind a delay


(def par-stats (graph/par-compile stats-graph))

(def output (par-stats {:xs [1 2 3 6]}))
;; Nodes are being computed in futures, with :m and :m2 going in parallel after :n
(= (/ 7 2) (:v output))

We can also ask a Graph for information about its inputs and outputs (automatically computed from its definition):

(require '[plumbing.fnk.pfnk :as pfnk])

;; stats-graph takes a map with one required key, :xs
(= {:xs s/Any}
   (pfnk/input-schema stats-graph))

;; stats-graph outputs a map with four keys, :n, :m, :m2, and :v
(= {:n s/Any :m s/Any :m2 s/Any :v s/Any}
   (pfnk/output-schema stats-graph))

If schemas are provided on the inputs and outputs of the node functions, these propagate through into the Graph schema as expected.

We can also have higher-order functions on Graphs to wrap the behavior on each step. For instance, we can automatically profile each sub-function in 'stats' to see how long it takes to execute:

(def profiled-stats (graph/compile (graph/profiled ::profile-data stats-graph)))

;;; times in milliseconds for each step:
(= {:n 1.001, :m 0.728, :m2 0.996, :v 0.069}
   @(::profile-data (profiled-stats {:xs (range 10000)})))

… and so on. For more examples and details about Graph, check out the graph examples test.

Many of the functions we write (in Graph and elsewhere) take a single (nested) map argument with keyword keys and have expectations about which keys must be present and which are optional. We developed a new style of binding (read more here) to make this a lot easier and to check that input data has the right 'shape'. We call these 'keyword functions' (defined by defnk) and here's what one looks like:

(use 'plumbing.core)
(defnk simple-fnk [a b c]
  (+ a b c))

(= 6 (simple-fnk {:a 1 :b 2 :c 3}))
;; Below throws: Key :c not found in (:a :b)
(thrown? Throwable (simple-fnk {:a 1 :b 2}))

You can declare a key as optional and provide a default:

(defnk simple-opt-fnk [a b {c 1}]
  (+ a b c))

(= 4 (simple-opt-fnk {:a 1 :b 2}))

You can do nested map bindings:

(defnk simple-nested-fnk [a [:b b1] c]
  (+ a b1 c))

(= 6 (simple-nested-fnk {:a 1 :b {:b1 2} :c 3}))
;; Below throws: Expected a map at key-path [:b], got type class java.lang.Long
(thrown? Throwable (simple-nested-fnk {:a 1 :b 1 :c 3}))

Of course, you can bind multiple variables from an inner map and do multiple levels of nesting:

(defnk simple-nested-fnk2 [a [:b b1 [:c {d 3}]]]
  (+ a b1 d))

(= 4 (simple-nested-fnk2 {:a 1 :b {:b1 2 :c {:d 1}}}))
(= 5 (simple-nested-fnk2 {:a 1 :b {:b1 1 :c {}}}))

You can also use this binding style in a let statement using letk or within an anonymous function by using fnk.

More good stuff

There are a bunch of functions in plumbing.core that we can't live without. Here are a few of our favorites.

When we build maps, we often use for-map, which works like for but for maps:

(use 'plumbing.core)
(= (for-map [i (range 3)
             j (range 3)
	         :let [s (+ i j)]
			 :when (< s 3)]
	  [i j]
	  s)
   {[0 0] 0, [0 1] 1, [0 2] 2, [1 0] 1, [1 1] 2, [2 0] 2})

safe-get is like get but throws when the key doesn't exist:

;; IllegalArgumentException Key :c not found in {:a 1, :b 2}
(thrown? Exception (safe-get {:a 1 :b 2} :c))

Another frequently used map function is map-vals:

;; return k -> (f v) for [k, v] in map
(= (map-vals inc {:a 0 :b 0})
   {:a 1 :b 1})

Ever wanted to conditionally do steps in a ->> or ->? Now you can with our 'penguin' operators. Here's a few examples:

(use 'plumbing.core)
(= (let [add-b? false]
     (-> {:a 1}
         (merge {:c 2})
         (?> add-b? (assoc :b 2))))
   {:a 1 :c 2})

(= (let [inc-all? true]
     (->> (range 10)
          (filter even?)
          (?>> inc-all? (map inc))))
	[1 3 5 7 9])

Check out plumbing.core for many other useful functions.

ClojureScript

As of 0.3.0, plumbing is available in ClojureScript! The vast majority of the library supports ClojureScript, with the only exceptions that are JVM-specific optimizations.

Here's an example usage of for-map:

(ns plumbing.readme
  (:require [plumbing.core :refer-macros [for-map]]))

(defn js-obj->map
  "Recursively converts a JavaScript object into a map with keyword keys"
  [obj]
  (for-map [k (js-keys obj)
            :let [v (aget obj k)]]
    (keyword k) (if (object? v) (js-obj->map v) v)))

(is (= {:a 1 :b {:x "x" :y "y"}}
       (js-obj->map
        (js-obj "a" 1
                "b" (js-obj "x" "x"
                            "y" "y")))))

;; Note: this is a contrived example; you would normally use `cljs.core/clj->js`

Community

Plumbing now has a mailing list. Please feel free to join and ask questions or discuss how you're using Plumbing and Graph.

Supported Clojure versions

Plumbing is currently supported on Clojure 1.8 or later, and the latest ClojureScript version.

License

Distributed under the Eclipse Public License, the same as Clojure.

plumbing's People

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

plumbing's Issues

Plans on full support of nested calculations?

I have scenario where I have a root graph for the main calculation and a subgraph that needs to be applied to a collection of input maps. Currently, this is implemented via two different graphs together with a function for applying the subgraph to each input map.
The mentioned collection of input maps will not fit into memory in general.

But that way I need to manage dependencies on properties of the subgraph in the root graph myself. It would be nice if that could be done with prismatic.graph.

Are there any plans to wnable something like that? Or is this already possible with the current implementation using some implementation pattern?

schemas defined with defschema are not eager-compile friendly

If you define your schemas defschema:

(ns defschema-not-eager-compile-friendly.schemas
  (:require [schema.core :as s]
            [schema.macros :as sm]))

(sm/defschema WithDefSchema {s/Keyword s/Num})

And then you try to use that schema in graph that is eager-compileed in another ns then you run into an error:

(ns defschema-not-eager-compile-friendly.core
  (:require
   [defschema-not-eager-compile-friendly.schemas :as schemas]
   [plumbing.core :refer [fnk]]
   [plumbing.graph :as graph]))


(def graph-with-defschema
  {:foo (fnk [bar :- schemas/WithDefSchema])})

(def with-defschema (graph/eager-compile graph-with-defschema))
;; clojure.lang.Compiler$CompilerException: java.lang.RuntimeException: Unable to resolve symbol: WithDefSchema in this context, compiling:(/tmp/defschema-not-eager-compile-friendly/src/defschema_not_eager_compile_friendly/core.clj:11:1)
;;              java.lang.RuntimeException: Unable to resolve symbol: WithDefSchema in this context
;;                                         clojure.lang.Util.runtimeException                         Util.java:  221
;;                                            clojure.lang.Compiler.resolveIn                     Compiler.java: 6940
;;                                              clojure.lang.Compiler.resolve                     Compiler.java: 6884
;;                                        clojure.lang.Compiler.analyzeSymbol                     Compiler.java: 6845
;;  ......

However, if you simply replace the use of defschema with a def everything works fine. You can see both cases in this small project I created to reproduce the bug: https://github.com/bmabey/defschema-not-eager-compile-friendly/tree/master/src/defschema_not_eager_compile_friendly

Adding if-letk and when-letk macros

Hey guys,

Are there any plans to add these letk variants?

I'd be happy to implement these myself and PR you, but it would be nice if they were included in plumbing.core so that we don't need to use or refer from another namespace.

Cheers,
Mike

fnk binding form can't combine optional parameters with destructuring

When defining a fnk, I'd hope to be able to do something like this:

((fnk [{[:sub foo] 1} bar] (+ foo bar)) {:sub {:bar 1}})

to get back 2. Unfortunately, combining the optional {} syntax with the [] destructuring syntax does not work:

CompilerException java.lang.ClassCastException: clojure.lang.PersistentVector cannot be cast to clojure.lang.Named, compiling:(*cider-repl trapperkeeper*:16:32) 

:advanced optimizations not removing dead code from Plumbing lib

I am experiencing an issue where the closure compiler is not eliminating dead code from plumbing.

I have created a simple example of the issue described: https://gist.github.com/SamHowie/aaf8f6b616bb59528ab8

Output file size when requiring plumbing - 145KB
Output file size when manually copy pasting used plumbing functions - 61KB

I am unsure if this is:

  1. a project.clj config error on my part
  2. a closure compiler issue
  3. a cljsbuild issue
  4. a plumbing issue

Has anyone else experienced this?

Improve capabilities for handling errors from plumbing library?

Hi. We're using your graph library to build a simple service / application container to run some of our code in. The library is really useful, so first I should thank you for graciously sharing it!

One small issue that we've run into a few times has to do with error handling when we are using the fnk destructuring syntax. Basically, when we are trying to use the destructuring to get access to a dependency function that is nested one level deep, if the parent key doesn't exist in the graph we'd like to be able to catch the error from prismatic and format it slightly differently to give a useful error message to the end user.

Here's some example code that reproduces it:

https://gist.github.com/cprice404/7663330

With the current implementation, plumbing.fnk.impl/safe-get throws a pretty generic exception; a RuntimeException with the string Key :foo not found in null. We are currently catching that, doing a regex against the string, and trying to generate our more specific error from there. It'd be really handy, though, if the exception that the plumbing library was throwing was more specific and didn't require us to regex it.

Would you all be amenable to changing this in some way? We'd be happy to submit a PR if that would be helpful. We'd just need some guidance from you on what more specific exception type you'd be willing to use there. We could maybe create a concrete FnkException with a few data members, or use slingshot to throw a map (but that would obviously force the introduction of a dependency that you may prefer to avoid).

If you're amenable to making some sort of change and have any better ideas on how to make it more specific, we can work with whatever you think is the best solution... it'd just be nice if it was something a tiny bit more specific.

Thoughts? Thanks again for the great library.

Incorrect use of schema for function explicit-schema-key-map ?

I am not familiar with the use of Schema yet, but while testing Eastwood on plumbing code it flagged the symbols :- s/Keyword and s/Bool as 'unused' in the function definition below, while it gave no such warnings for many other similar function definitions, so this one may be incorrect:

File: src/plumbing/fnk/schema.cljx

(sm/defn explicit-schema-key-map
"Given a possibly-unevaluated map schema, return a map from bare keyword to true
(for required) or false (for optional)"
[s] :- {s/Keyword s/Bool}
(->> s
keys
(keep unwrap-schema-form-key)
(into {})))

like-some?

Because I use your plumbing already in my benrikuro and then just defcopy the forms I like, it would be nice if some of other forms I use myself would have a chance to be integrated in plumbing.

;;;;;;;;;;;;;;;; Somewhere from the Clojure community ;;;;;;;;;;;;;;;;

(defmacro defcopy
  "Defines a copy of a var: a new var with the same root binding (if
   any) and similar metadata. The metadata of the copy is its initial
   metadata (as provided by def) merged into the metadata of the original.
   source: same as defalias from clojure 1.2 and downwards."
  ([name orig]
  `(do
     (alter-meta!
      (if (.hasRoot (var ~orig))
        (def ~name (.getRawRoot (var ~orig)))
        (def ~name))
      ;; When copying metadata, disregard {:macro false}.
      ;; Workaround for http://www.assembla.com/spaces/clojure/tickets/273
      #(conj (dissoc % :macro)
             (apply dissoc (meta (var ~orig)) (remove #{:macro} (keys %)))))
     (var ~name)))
  ([name orig doc]
   (list `defcopy (with-meta name (assoc (meta name) :doc doc)) orig)))
(defn ffilter ; can be find-first too
  "Returns the first item of coll for which (pred item) returns logical true.
   Consumes sequences up to the first match, will consume the entire sequence
   and return nil if no match is found."
  [pred coll] (first (filter pred coll)))
(defn map-dregs [f & colls] ; by TimMc
  "Like map but when there is a different count between colls, applies input fn
   to the coll values until the biggest coll is empty."
  ((fn map* [f colls]
     (lazy-seq
       (when (some seq colls)
         (cons (apply f (map first (filter seq colls)))
               (map* f (map rest colls))))))
   f colls))
(defn update
  "Updates the value in map m at k with the function f.
  Like update-in, but for updating a single top-level key.
  Any additional args will be passed to f after the value."
  ([m k f] (assoc m k (f (get m k))))
  ([m k f x1] (assoc m k (f (get m k) x1)))
  ([m k f x1 x2] (assoc m k (f (get m k) x1 x2)))
  ([m k f x1 x2 & xs] (assoc m k (apply f (get m k) x1 x2 xs))))
(defn update-in*
  "Updates a value in a nested associative structure, where ks is a sequence of keys and f is a
  function that will take the old value and any supplied args and return the new value, and returns
  a new nested structure. If any levels do not exist, hash-maps will be created. This implementation
  was adapted from clojure.core, but the behavior is more correct if keys is empty and unchanged
  values are not re-assoc'd."
  [m keys f & args]
  (if-let [[k & ks] (seq keys)]
    (let [old (get m k)
          new (apply update-in* old ks f args)]
      (if (identical? old new)
        m
        (assoc m k new)))
     (apply f m args)))

(defn update-each
  "Update the values for each of the given keys in a map where f is a function that takes each
  previous value and the supplied args and returns a new value. Like update-in*, unchanged values
  are not re-assoc'd."
  [m keys f & args]
  (reduce (fn [m key]
                 (apply update-in* m [key] f args))
                   m keys))
(defn update-vals ; by Jay Fields
  "Updates all the values of a map"
  [m f & args]
  (reduce (fn [r [k v]] (assoc r k (apply f v args)))
          {} m))
(require '[clojure.reflect :refer [reflect]] '[clojure.pprint :refer [print-table]])

(defn get-members [some-type]
  (->> (-> some-type reflect :members)
         (filter :exception-types)
         (sort-by :name)
         print-table))
(defn call-method
  "Calls a private or protected method.

   params is a vector of classes which correspond to the arguments to
   the method e

   obj is nil for static methods, the instance object otherwise.

   The method-name is given a symbol or a keyword (something Named)."
  [klass method-name params obj & args]
  (-> klass (.getDeclaredMethod (name method-name)
                                (into-array Class params))
      (doto (.setAccessible true))
      (.invoke obj (into-array Object args))))
(defn get-field
  "Access to private or protected field. field-name is a symbol or
  keyword."
  [klass field-name obj]
  (-> klass (.getDeclaredField (name field-name))
      (doto (.setAccessible true))
      (.get obj)))
(defn unlazy
  "Same as map/filter/reduce, but preserves the input data type."
  [core-f f coll]
  (into (empty coll) (core-f f coll)))

;;;;;;;;;;;;;;;; my own ;;;;;;;;;;;;;;;;

(defn update-multi
  "Updates multiple keys of a map with multiple fns using a map of key/fn pairs."
  [m fn-m]
  (merge
    m
    (into {} (map (fn [[k f]] [k (f (k m))]) fn-m))))
(defn str->stream [string] (-> string .getBytes clojure.java.io/input-stream))
(def nilify (constantly nil))
(defn or->
  "Same as -> but defaults to the initial value if the result is falsey."
  [x & args]
  (or (eval `(-> ~x ~@args)) x))

Thank you for taking the time.

warnings compiling using clojure 1.7 and clojurescript

including:

[org.clojure/clojure "1.7.0-alpha2"]
[org.clojure/clojurescript "0.0-2371"]
[org.clojure/core.async "0.1.346.0-17112a-alpha"]
[om "0.7.3"]
[prismatic/om-tools "0.3.6"]

WARNING: update already refers to: #'clojure.core/update in namespace: plumbing.core, being replaced by: #'plumbing.core/update
WARNING: Use of undeclared Var cljs.core/class at line 12 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var clojure.data/diff at line 12 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var cljs.core/class at line 41 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var clojure.data/diff at line 41 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var cljs.core/class at line 51 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var clojure.data/diff at line 51 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var cljs.core/class at line 59 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var clojure.data/diff at line 59 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var cljs.core/class at line 98 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var clojure.data/diff at line 98 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var cljs.core/class at line 103 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs
WARNING: Use of undeclared Var clojure.data/diff at line 103 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/types.cljs

types.cljs uses schema, and also getting those on compiling om components (using defcomponentk):

WARNING: Bad method signature in protocol implementation, object does not declare method called display_name at line 7 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/components/generic.cljs
WARNING: Use of undeclared Var mex.components.generic/object at line 7 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/components/generic.cljs
WARNING: Symbol object is not a protocol at line 7 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/components/generic.cljs
WARNING: Bad method signature in protocol implementation, object does not declare method called display_name at line 10 /Users/talgiat/Dropbox/Dev/mex/src/main/cljs/mex/components/item_overview.cljs

How are you dealing with Clojure 1.7's clojure.core/update?

We require plumbing in a uniform manner:

(ns ...
  (:require [plumbing.core :refer :all]))

Using Clojure 1.7-alpha4, we now get a ton of warnings like this:

WARNING: update already refers to: #'clojure.core/update in namespace: one.of.our.namespaces, being replaced by: #'plumbing.core/update.

Do you anticipate altering plumbing to rename your update, or do we need to explicitly exclude clojure's update like this?

(ns ...
  (:refer-clojure :exclude [update])
  (:require [plumbing.core :refer :all]))

FWIW, we don't actually use plumbing.core/update. I just want the warnings to go away :-)

Metadata Reader Macros and fnks

Hey guys,
I'd expect fnks to keep the metadata I give them via reader macros, but they don't:

=> (keys (meta ^{:has-meta? true} (fn [] true)))
(:has-meta?)

=> (keys (meta ^{:has-meta? true} (fnk [] true)))
(:schema)

Is this intentional? I came across this while using fnks for my reagent components. Reagent uses function metadata to help work out e.g. the key or display name of its components.

In a similar vein, it looks like fnks don't have a “name” property like normal Clojure functions do:

my.namespace=> (.-name (fn blah [] 1))
"my$namespace$blah"
my.namespace=> (.-name (fnk blah [] 1))
nil

graph lazy-compile doesn't behave lazy :)

Hi friends,
Today I tried to use this minimal use of plumbing.graph/lazy-compile fn

(def lg
  (graph/lazy-compile
   {:http-listener (fnk [system] (-> system :http-listener-listener))
    :server (fnk [http-listener] (run-server (-> http-listener :h) {:port 8010}))}))

But when I invoke this graph

(def result (lg {:system system}))

I get my server running before I reference (:server result)

But theoretically this server shouldn't start in lazy-compile mode ....

Thanks in advance!
Juan

More common conditional arrow operations

Hello.

Why conditional operations can be used only for one function but not for whole branch?

Like it:

(defmacro ?>>
  "Conditional double-arrow operation (->> nums (?>> inc-all? (map inc)))"
  [do-it? & args]
  `(if ~do-it?
     (->> ~(last args) ~@(butlast args))
     ~(last args)))

(defmacro ?>
  "Conditional single-arrow operation (-> m (?> add-kv? (assoc :k :v)))"
  [arg do-it? & rest]
  `(if ~do-it?
     (-> ~arg ~@rest)
     ~arg))

So:

(let [add-b? true]
               (-> {:a 1}
                   (merge {:c 2})
                   (?> add-b? 
                       (assoc :b 2)
                       (dissoc :c))))

I think it's more useful and idiomatic.

Lots of warnings w/r/t Schema fn calls

I had plumbing pulled into my project by om-tools. I'm also using the newest version of Schema for my backend validation. I believe the combination of the two is what's resulting in quite a few warnings when I boot up Figwheel (see below).

william_jarvis@jackalope ~/C/shrike> lein figwheel
Figwheel: Starting server at http://localhost:3449
Focusing on build ids: app
Compiling "resources/public/js/app.js" from ["src/cljs"]...
WARNING: schema.core/either is deprecated. at line 23 file:/Users/william_jarvis/.m2/repository/prismatic/plumbing/0.4.4/plumbing-0.4.4.jar!/plumbing/fnk/schema.cljs
WARNING: schema.core/either is deprecated. at line 27 file:/Users/william_jarvis/.m2/repository/prismatic/plumbing/0.4.4/plumbing-0.4.4.jar!/plumbing/fnk/schema.cljs
WARNING: schema.core/both is deprecated. at line 66 file:/Users/william_jarvis/.m2/repository/prismatic/plumbing/0.4.4/plumbing-0.4.4.jar!/plumbing/fnk/schema.cljs
WARNING: schema.core/either is deprecated. at line 23 resources/public/js/out/plumbing/fnk/schema.cljs
WARNING: schema.core/either is deprecated. at line 27 resources/public/js/out/plumbing/fnk/schema.cljs
WARNING: schema.core/both is deprecated. at line 66 resources/public/js/out/plumbing/fnk/schema.cljs
Successfully compiled "resources/public/js/app.js" in 10.943 seconds.

Any chance of bumping Plumbing's dependency on Schema to a more recent version and cleaning up the deprecation dependencies?

Problems with some tests

File: test/plumbing/core_test.cljx

Spurious + at the end of this line: (is (thrown? Exception (p/safe-get {:a 2} :b)))+

Appears to be misplaced parens in this test:

  • (is (= {:foo 2 :bar 1})
  •  (p/update-in-when {:foo 1 :bar 1} [:foo] inc))
    
  • (is (= {:foo 2 :bar 1}
  •     (p/update-in-when {:foo 1 :bar 1} [:foo] inc)))
    

This test doesn't test anything, because (= x) is always true. Maybe it is intended to compare @called? to true?
(is (= @called?))

File: test/plumbing/map_test.cljx

These lines always return true because the number 2 is always truthy:
(is 2 (= (map/update-key! m :a inc)))
(is 2 (= (map/update-key! m :c conj "foo")))
It isn't obvious to me what the correct tests are yet, since at least with today's code the update-key! calls do not return 2.

Found using Eastwood lint tool.

Error when using plumbing from clojurescript

Hi,

I am trying to use plumbing 0.3.1 from clojurescript but I get the following error when compiling cljs with lein-cljsbuild:

Caused by: clojure.lang.ExceptionInfo: java.lang.RuntimeException: No such namespace: js, compiling:(schema/core.clj:135:5) at line 1 file:/home/.m2/repository/prismatic/plumbing/0.3.1/plumbing-0.3.1.jar!/plumbing/fnk/schema.cljs

Here is a sample project to reproduce the error: https://github.com/EwenG/test-plumbing.

Ewen.

Possible bug in ->graph

Hi,

the following code

(def wrong-graph?
  {:temp (fnk [inp1 inp2] (apply hash-map :sum (+ inp1 inp2)))
   :r (fnk [[:temp sum]] {:sum sum})})

(eager-compile wrong-graph?)

throws a

IllegalArgumentException Not a map true keyseq: null plumbing.fnk.schema/assert-satisfies-schema (schema.clj:66)

Pretty dubious. :)

However, the following works:

(def ok-graph?
  {:temp (fnk [inp1 inp2] {:sum (+ inp1 inp2)})
   :r (fnk [[:temp sum]] {:sum sum})})

(eager-compile ok-graph?)

Clojurescript version of topological-sort incorrectly (and randomly) reports a graph cycle error

Clojurescript topological-sort incorrectly generates a "Graph contains a cycle" error when sorting the following graph (which does not have a cycle):

{10 [1 0]
 20 [2 0]
 2 []
 0 []}

The current algorithm subtly relies on ordering to recognize that there is actually no cycle in a graph. If a key is randomly chosen (with rand-nth for example) instead of first in this line - https://github.com/Prismatic/plumbing/blob/master/src/plumbing/map.cljx#L243 - the above graph will accordingly return a sort or report an error depending on what order the keys are processed from the graph. The current algorithm is (sort of) behaving like depth-first sorting, not topological sorting.

The version of topo sort that was introduced before #71 correctly handles the above graph as does the clj version.

I'll submit a pull request shortly that restores the old topological-sort but introduces the un-implemented include-leaves? option of the older version.

Parallel graph & nested exceptions

Haallooooooo,

I've been using par-compile and every time it crashes I get my exception wrapped up nicely in 6 ExecutionExceptions hoo ray!

Should par-compile maybe use modified futures that unwrap exceptions? I'm not sure exactly how to do this, but if we can figure out a clean way is it a good idea? Should we leave one wrapper just for funsies?

Some minor feedback

Since you guys were asking for explicitly a few times, I figured I should at least write a few words on my experiences with plumbing so far. Partially, without knowing, I had already noticed a few of these patterns as well and with that grew a feeling your probably described best already as:

While Clojure's built-in destructuring is generally great, it leaves some things to be desired when we're only concerned with destructuring nested maps with keyword keys, and want to make heavy use of extra features like required keys or default values:

I hate me too! but I so want to say that. I have to admit, the way graph was setup, I probably wouldn't even have thought about that anytime soon, so it was a great discovery when I learned about your tool (and why I can spend so many hours in a software landscape scouting solutions, fearing I'd miss out on greatness floating around hyperspace).

One of the problems I was trying to tackle in a elegant fashion was the composition of Clojure web pages using hiccup and garden DSL in syntax-quoted or parsed/compiled forms, that I could more easily transform and pipe through decision nodes without writing, indeed, huge functions and let bodies. So one challenge that kept nagging me was how to do it all together in a more terse fashion than Clojure currently does with the whole destructuring/defauls/keys. Plumbing is definitely filling a niche here (I'm sure more people would use it if they knew about it) that at least I myself am going to keep using for a long while, or so I suspect.

Anyway, I've scoured the README of defnk/fnk and thing you guys nailed it on the head with the pro/con lists - I recognize those same points you make and somehow I wonder, if there is a clean solution 1,2,3. So I guess my feedback is: I have nothing I would change/improve at the moment that would be better. Oh well, enough time to let it sink in. Overall I'm very content with the result so far, that's an understatement probably. Heck I was even going to settle on the verbose/repetitive Clojure syntax as a fact of life and go on with it, although I was tempted to construct at least a macro to cover for some of it. That being said, I can conclude graph/plumbing even just being in existence as it is today, makes me a happy camper.

Thanks for the great work you've done so far, keep it up!

oh. One thing I didn't read in the documents (might be there somewhere) but probably going to experiment with today to see if/how easy it is to use defnk and hang them in a graph later on? Would it pick up on the same arguments from different defnk and treat them as one? Time to experiment some more and less writing/talking.

Cheers,
Rob

update

Would a pull request for (defn update [m k f & args] (apply update-in m [k] f args)) be accepted?

Every time I use update-in with a single key, I imagine a parenthesis losing its wings somewhere.

defnk example using & and :as doesn't work

defnk Example given at https://github.com/Prismatic/plumbing/tree/master/src/plumbing/fnk raises an exception:

(defnk foo [x & y :as z] [x y z])

java.lang.RuntimeException
   Got illegal special binding: clojure.lang.LazySeq@bce9dd88
                      impl.clj:  121  plumbing.fnk.impl/extract-special-arg
                      impl.clj:  134  plumbing.fnk.impl/letk-input-schema-and-body-form
                      impl.clj:  345  plumbing.fnk.impl/fnk-form
                     core.cljx:  435  plumbing.core$defnk/doInvoke
                   RestFn.java:  490  clojure.lang.RestFn/invoke
                      Var.java:  401  clojure.lang.Var/invoke
                      AFn.java:  171  clojure.lang.AFn/applyToHelper
                      Var.java:  700  clojure.lang.Var/applyTo

schema validation fails in eager-compile

This is happening on master where I know that the graph/schema integration is a WIP:

> (schema.core/set-fn-validation! true)
true
> (def foo (graph/eager-compile {:foo (fnk [a] a)}))

CompilerException clojure.lang.ExceptionInfo: 
Input to sequence-schemata does not match schema: 
[nil (named [nil (named [nil (named {:_ (not (satisfies? Schema nil))} output)] 
"inner-schemas")] arg1)] 
{:error [nil (named [nil (named [nil (named {:_ (not (satisfies? Schema nil))} output)]
 "inner-schemas")] arg1)], :schema [#schema.core.One{:schema
 [#schema.core.One{:schema {(either schema.core.OptionalKey Keyword) 
(protocol Schema)}, :optional? false, :name input} #schema.core.One{:schema
 {Keyword (protocol Schema)}, :optional? false, :name output}], :optional? false, 
:name arg0} #schema.core.One{:schema [#schema.core.One{:schema Keyword,
 :optional? false, :name "key"} #schema.core.One{:schema
 [#schema.core.One{:schema {(either (protocol Schema) 
schema.core.OptionalKey Keyword) (protocol Schema)}, :optional? false, :name input} 
#schema.core.One{:schema {Keyword (protocol Schema)}, :optional? false, 
:name output}], :optional? false, :name "inner-schemas"}], :optional? false, 
:name arg1}], :value [[{} {}] [:foo [{:a Any} Any]]]}, 
compiling:(form-init2876214811000312469.clj:1:10) 

uberjar-ed program using plumbing library above 0.3.4 throws exception

Hi,

I found this issue where uberjar-ed program using plumbing library above 0.3.4 throws exception.

Below is the minimal sample to reproduce this issue.

;; project.clj
(defproject plumbing-uberjar-issue "0.1.0-SNAPSHOT"
  :dependencies [[org.clojure/clojure "1.6.0"]
                 [prismatic/plumbing "0.3.5"]]
  :main ^:skip-aot plumbing-uberjar-issue.core
  :target-path "target/%s"
  :profiles {:uberjar {:aot :all}})
;;  core.clj
(ns plumbing-uberjar-issue.core
 (:require [plumbing.core :refer [fnk sum] :as p]
            [plumbing.graph :as graph])
  (:gen-class))

(def stats-graph
  "A graph specifying the same computation as 'stats'"
  {:n  (fnk [xs]   (count xs))
   :m  (fnk [xs n] (/ (sum identity xs) n))
   :m2 (fnk [xs n] (/ (sum #(* % %) xs) n))
   :v  (fnk [m m2] (- m2 (* m m)))})

(def stats-eager (graph/eager-compile stats-graph))

(defn -main
  "I don't do a whole lot ... yet."
  [& args]
  (println "Hello, World!"))

then execute below in shell.

$ lein uberjar
$ java -jar target/uberjar/plumbing-uberjar-issue-0.1.0-SNAPSHOT-standalone.jar

Below is the exception message that I'm getting.
I tried release 0.3.4, 0.3.5, and current-master, but they all fail the same way.

Exception in thread "main" java.lang.ExceptionInInitializerError
        at java.lang.Class.forName0(Native Method)
        at java.lang.Class.forName(Class.java:270)
        at clojure.lang.RT.loadClassForName(RT.java:2093)
        at clojure.lang.RT.load(RT.java:430)
        at clojure.lang.RT.load(RT.java:411)
        at clojure.core$load$fn__5066.invoke(core.clj:5641)
        at clojure.core$load.doInvoke(core.clj:5640)
        at clojure.lang.RestFn.invoke(RestFn.java:408)
        at clojure.lang.Var.invoke(Var.java:379)
        at plumbing_uberjar_issue.core.<clinit>(Unknown Source)
Caused by: java.lang.RuntimeException: No such var: schema.core/fn, compiling:(NO_SOURCE_PATH:0:0)
        at clojure.lang.Compiler.analyze(Compiler.java:6464)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$InvokeExpr.parse(Compiler.java:3665)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6646)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$InvokeExpr.parse(Compiler.java:3719)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6646)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$BodyExpr$Parser.parse(Compiler.java:5782)
        at clojure.lang.Compiler$LetExpr$Parser.parse(Compiler.java:6100)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6644)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6632)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$BodyExpr$Parser.parse(Compiler.java:5782)
        at clojure.lang.Compiler$LetExpr$Parser.parse(Compiler.java:6100)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6644)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6632)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$BodyExpr$Parser.parse(Compiler.java:5782)
        at clojure.lang.Compiler$LetExpr$Parser.parse(Compiler.java:6100)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6644)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6632)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$BodyExpr$Parser.parse(Compiler.java:5782)
        at clojure.lang.Compiler$FnMethod.parse(Compiler.java:5217)
        at clojure.lang.Compiler$FnExpr.parse(Compiler.java:3846)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6642)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.analyze(Compiler.java:6406)
        at clojure.lang.Compiler$BodyExpr$Parser.parse(Compiler.java:5782)
        at clojure.lang.Compiler$FnMethod.parse(Compiler.java:5217)
        at clojure.lang.Compiler$FnExpr.parse(Compiler.java:3846)
        at clojure.lang.Compiler.analyzeSeq(Compiler.java:6642)
        at clojure.lang.Compiler.analyze(Compiler.java:6445)
        at clojure.lang.Compiler.eval(Compiler.java:6700)
        at clojure.lang.Compiler.eval(Compiler.java:6666)
        at clojure.core$eval.invoke(core.clj:2927)
        at plumbing.graph.positional$eval_bound.invoke(positional.clj:48)
        at plumbing.graph.positional$positional_flat_compile.invoke(positional.clj:88)
        at plumbing.graph$eager_compile.invoke(graph.clj:122)
        at plumbing_uberjar_issue.core__init.load(Unknown Source)
        at plumbing_uberjar_issue.core__init.<clinit>(Unknown Source)
        ... 10 more
Caused by: java.lang.RuntimeException: No such var: schema.core/fn
        at clojure.lang.Util.runtimeException(Util.java:221)
        at clojure.lang.Compiler.resolveIn(Compiler.java:6914)
        at clojure.lang.Compiler.resolve(Compiler.java:6884)
        at clojure.lang.Compiler.analyzeSymbol(Compiler.java:6845)
        at clojure.lang.Compiler.analyze(Compiler.java:6427)
        ... 59 more

Merge input nodes into resulted map

I am using a graph as a box of a couple dozen of values that are calculated based on each other values.
And the graph is passed to several functions as a hashmap argument.
This use case might not be assumed, but I found this is very helpful and make my code succinct.
So I think that to merge input nodes into resulted map is useful because I can get input nodes in the functions.

(def lazy-stat (graph/lazy-compile {:a (pl/fnk [x] (+ x 1))}))
;=> #'user/lazy-stat
(def result (lazy-stat {:x 3}))
;=> #'user/result
(:x result)
;=> nil

Bug in async-compile

From the group:

My question is about the behavior of async-compile. It seems like it doesn't provide optional args to nodes in the graph.  The line in question uses
(select-keys @results (keys (pfnk/input-schema f)))

(select-keys @results (pfnk/input-schema-keys f))

update isn't excluded

I don't know why, but plumbing exports update even though I'm using Clojure 1.7

WARNING: update already refers to: #'clojure.core/update in namespace: plumbing.core, being replaced by: #'plumbing.core/update
WARNING: update already refers to: #'clojure.core/update in namespace: compojure.api.meta, being replaced by: #'plumbing.core/update
WARNING: update already refers to: #'clojure.core/update in namespace: ring.swagger.core, being replaced by: #'plumbing.core/update

lein deps :tree indicates I'm using plumbing 0.4.1

two weird errors

Hi,

I'm trying plumbing in a leiningen project, i've added [prismatic/plumbing "0.4.4"] to my project dependencies vector

require it in my ns like so:

(ns plumbing-test.core (:require [plumbing.core :as p]))

but when i'm loading the file into the repl

CompilerException java.lang.RuntimeException: No such var: schema-macros/cljs-env?, compiling:(plumbing/fnk/impl.clj:365:19)

and if i'm loading a second time i've got this:

CompilerException java.lang.Exception: namespace 'plumbing.fnk.impl' not found, compiling:(plumbing/core.clj:1:1)

any help would be welcome

PB

get partial node with partial inputs via lazy-compile

Must all inputs be provided even if I just want to get only specific node which doesn't depend on all inputs?

(def lazy-stat (graph/lazy-compile {:a (pl/fnk [x] (+ x 1))
                                    :b (pl/fnk [a y] (+ a y))
                                    :c (pl/fnk [a z] (+ a z))}))
; => #'user/lazy-stat
(:b (lazy-stat {:x 1 :y 2}))
; => IllegalArgumentException
; Missing top-level keys in graph input: #{:z}  
; plumbing.graph/abstract-compile/fn--3227 (graph.clj:103)

Perhaps, I am trying to apply plumbing to wrong use case.

Missing part of README: using Graph for building the whole application from "services"

There were a lot of mentions in various talks and mail lists that Prismatic uses Graph to structure it's applications and not only "computation flow" in a single part of a program. There is even a short example in tests. However, as far as I know, there is no definitive overview of how to really build an application this way.

There is a non-Prismatic library to do something similar, but how does that library differs from what you do?

Personally, I didn't find the perfect way to structure Clojure apps, everything that I've tried had some serious downsides. It looks like I'm not alone in this. Is it possible to extend this project's README to include more details on the topic?

`map-nested` or something

For years and years and years and years I keep running into the issue of how awkward it is to mix threading macros with updating the values in a collection.

I'm not sure if this can be made easier without getting into crazy-threading-macro-complexity-hell or something like that, but I thought I would check if you folks have some alternate approach, or if we might discover a decent extension for plumbing.

To be concrete, I often find myself doing something like:

(defn the-business-logic
  [m]
  (-> m
      (update :logic-count inc)
      (update :clients (fn [clients] (map (fn [client]
                                            (-> client
                                                (update-in ...)))
                                          clients)))))

This could also be accomplished with (partial map (fn [client] ...)) or even nicer with the fn-> I just re-discovered a few minutes ago, but it still feels like it takes a lot of work to map a nested collection.

Approaches using functions that don't exist yet:

  • The super higher-order (defn flip [f] (fn [x y] (f y x))) could be used to say (update :clients (flip map) (fn-> ...))
  • I once defined a map-nested that let me do (map-nested :clients (fn-> ...))

I dunno!

safe-get in ClojureScript

safe-get doesn't work in ClojureScript (as of 0.3.4):

 Uncaught TypeError: Cannot read property 'call' of undefined

An actual missing function is assert-iae here:

(schema/assert-iae false "Key %s not found in %s" k (mapv key m))))

In addition, ClojureScript compiler emits warnings:

WARNING: Use of undeclared Var plumbing.fnk.schema/assert-iae at line 117 file:/home/si14/.m2/repository/prismatic/plumbing/0.3.4/plumbing-0.3.4.jar!/plumbing/core.cljs

Proposal: mapply

Positional map arguments are a pain to work with programmatically.

(defn mapply
  "Takes a function, optional initial args, and a map, and applies 
  the keys/vals of the map as positional varargs to the function."
  ([f m] (apply f (apply concat m)))
  ([f & args]
    (apply f (concat (butlast args) (apply concat (last args))))))

Error in the Readme

There is a real error, only the syntax is wrong. In the topic Fnk syntax example is wrong:

(fn [{: keys [a]: or {2}])

the correct would be:

(fn [{: keys [a]: or {2}}])

Excuse me for bad English.

Thank you very much

Example of graph withouf fnk

Hey,

I'm trying to use Graph for some custom processing that does not rely on maps (basically I'm calling a bunch of RPCs), to prevent the overhead of serializing / deserializing the bytes on each step I was wondering if it's possible to use prismatic without the fnk

java equals/hash warnings

Should distinct-by have the same warnings about java equals/hash that frequencies-fast and distinct-fast do?

feature request: partially evaluated graphs

Hi,
It'd be nice to be able to pass partially-evaluated graphs to eager-compile and friends (I guess that means ->graph), i.e. I'd like to be able to do:

(eager-compile {:x 1, :y (fnk [x] (+ x 1))})

Right now, I use a hack along the lines of:

(defn map->graph [m] (map-vals (fn [x] (if (fnk? x) x (fnk [] x))) m))

which appears to work as intended.

My use case is a function which produces an output map from an input map, where some values are computed via graph and others are either static (e.g. type tags) or can be computed independently of the others (e.g. timestamps) and I don't want to have to keep track of which subset of the map is an actual graph (a map of fnks).

Binding qualified keywords

A Graph-lib I was working on supported binding of qualified keywords:

(def g
  {:a 1
   :d/b 2
   :b/a (fnk [a] (* a 7))
   :x (fnk [b/a d/b] (+ b/a d/b))})

That's all done via the following:

        ns-syms (filter namespace (concat req optks))
        mappings (ns-syms->mappings ns-syms)
        [req opt body] (map (partial replace-ns-syms mappings)
                            [req opt (:body fn-decl)])

Filter for dependencies with a namespace,
generate gensyms based on the qualified keywords,
finally replace every keyword occurence in the dependency declarations and body.

(ns clevejate.util.syms
  (:require [clojure.string :as str]
            [clojure.walk :refer [postwalk-replace]]))

(defn gensym-escape-ns [x]
  (gensym
   (str
    (when (namespace x)
      (str (str/replace (namespace x) \. \-) \$))
    (name x))))

(defn ns-syms->mappings [ns-syms]
  (reduce
   (fn [m ns-sym]
     (assoc m ns-sym
            (gensym-escape-ns ns-sym)))
   {}
   ns-syms))

(defn replace-ns-syms [mappings form]
  (if (seq mappings)
    (postwalk-replace mappings form)
    form))

Trying to clone and install fails

Hi Prismatic guys!
I'm trying to make minor changes #74 to your awesome lib

I've just forked and cloned the repo
but when I try
lein install
then I get

Reloading Clojure file "/plumbing/fnk/impl.clj" failed.
java.io.FileNotFoundException: Could not locate schema/core__init.class or schema/core.clj on classpath: 
              RT.java:443 clojure.lang.RT.load
              RT.java:411 clojure.lang.RT.load
            core.clj:5530 clojure.core/load[fn]
            core.clj:5529 clojure.core/load
          RestFn.java:408 clojure.lang.RestFn.invoke
            core.clj:5336 clojure.core/load-one
            core.clj:5375 clojure.core/load-lib[fn]
            core.clj:5374 clojure.core/load-lib
          RestFn.java:142 clojure.lang.RestFn.applyTo
             core.clj:619 clojure.core/apply
            core.clj:5413 clojure.core/load-libs
          RestFn.java:137 clojure.lang.RestFn.applyTo
             core.clj:619 clojure.core/apply
            core.clj:5496 clojure.core/require
          RestFn.java:482 clojure.lang.RestFn.invoke
               impl.clj:1 plumbing.fnk.impl/eval2307[fn]
               impl.clj:1 plumbing.fnk.impl/eval2307
       Compiler.java:6619 clojure.lang.Compiler.eval
       Compiler.java:6608 clojure.lang.Compiler.eval

....

Thanks!
Juan

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.