(ns my.reagent-examples
  (:require
    [clojure.string :as string]
    [reagent.core :as reagent]
    [reagent.dom.server]
[reagent.ratom]))

(enable-console-print!)
(defn str->url [s t]
(let[blob (js/Blob. #js [s] #js {:type t})]
              (.createObjectURL js/URL blob) ))

(def worker-url (let[ gif-worker-src (.-textContent (. js/document (getElementById "gif-js-worker-code")))] 
(str->url gif-worker-src "application/javascript")))

(defn svgs->animated-gif-url![cb delays svgs]
  (let [delays (if (number? delays) (repeat delays) delays)
       [w h] ((comp (juxt :width :height) second first) svgs)
         gif (js/GIF. #js {:workers 4
                          :quality 1
                          :width w
                          :height h
                          :workerScript worker-url
                          })
        process (fn process[svgs delays](let[img (js/Image.)
                                             svg-url (str->url (reagent.dom.server/render-to-static-markup 
                                                                 (first svgs))
                                                               "image/svg+xml")]
                                          (do
                                            (set! (.-onload img)
                                                  (fn[](do
                                                         (.addFrame gif img #js{:copy true :delay (first delays)})
                                                         (let[r (rest svgs)]
                                                           (if (seq r)
                                                             (process r (rest delays))
                                                             (.render gif)
                                                             )))))
                                            (set! (.-src img) svg-url))))]
    (do
      (.on gif "finished" cb);; partial does not work ?!
      (process svgs delays))))

(defn save-svgs![filename delays svgs]
(letfn [(download-blob! [filename blob]
  (let[download-link (. js/document (createElement "a"))]
    (do
      (set! (.-download download-link) filename)
      (set! (.-href download-link) (.createObjectURL js/URL blob))
      (.click download-link))))]
(svgs->animated-gif-url! (fn[blob](download-blob! filename blob)) delays svgs)))

(defn display-svgs![parent delays svgs]
(svgs->animated-gif-url! (fn[blob]
                          (let[img (js/Image.)]
                            (do
                            (.appendChild parent img)
                            (set! (.-src img) (.createObjectURL js/URL blob)))))
                            delays svgs))

(defn svg-polyline[ps]
(let[[[x0 y0] & ps] ps
init-point (str "M " x0 ", " y0 " ")
seg (fn[[x y]] (str "L " x ", " y " "))]
(reduce #(str %1 (seg %2)) init-point ps)))
(defn draw-polylines[[w h] pss]
          [:svg {:xmlns "http://www.w3.org/2000/svg" :width w :height h}
[:rect {:x 0 :y 0 :width w :height h :fill "white"}]
          [:path {:stroke "black" :stroke-width 1 :fill "none" :d  (reduce str (map svg-polyline pss))}] ])
(defn add [[x0 y0][x1 y1]]
[(+ x0 x1)(+ y0 y1)])
(def make-polylines-transform (comp (partial partial mapv) (partial partial mapv) ))
(defn sin[x]
  (.sin js/Math x))
(defn cos[x]
          (.cos js/Math x))

(def PI
  (.-PI js/Math))
    (def sqrt #(.sqrt js/Math %))

    (defn rotate [a [x y]]
    (let [c (cos a)
          s (sin a)]
    [(- (* c x) (* s y)) (+ (* s x) (* c y))]))
(defn scale [k p]
(mapv (partial * k) p))
(def minus (partial scale -1.))
(def -INF (.-NEGATIVE_INFINITY js/Number))
(def INF (.-POSITIVE_INFINITY js/Number))

    (defn bounding-box[pss]
    (->> pss (reduce into [])(reduce (fn[[[x-min y-min][x-max y-max]][x y]] [[(min x-min x) (min y-min y)][(max x-max x)(max y-max y)]]) [[INF INF][-INF -INF]])))
      (defn make-fitting-transform[[w h] pss]
      (let[[[x-min y-min][x-max y-max]](bounding-box pss)
      s (min (/ w (- x-max x-min)) (/ h (- y-max y-min)))
      center (scale 0.5  (add [x-min y-min] [x-max y-max]))]
      (comp (partial add [(/ w 2) (/ h 2)]) (partial scale s) (partial add (minus center)))))
      (defn draw-fitted-polylines[wh pss]
      (draw-polylines wh ((make-polylines-transform (make-fitting-transform wh pss)) pss)))
(defn make-rotate-around [r a]
  (comp (partial add r)(partial rotate a) (partial add (minus r))))
(def TWO_PI (* 2 PI))
(defn regular-polygon [n]
(vec (take (inc n)(iterate (partial rotate (/ TWO_PI n)) [1. 0]))))
(defn weighted-mean [t [p0 p1]]
(add (scale (- 1 t) p0) (scale t p1)))
(defn str->url [s t]
(let[blob (js/Blob. #js [s] #js {:type t})]
              (.createObjectURL js/URL blob) ))

(def worker-url (let[ gif-worker-src (.-textContent (. js/document (getElementById "gif-js-worker-code")))] 
(str->url gif-worker-src "application/javascript")))

(defn svgs->animated-gif-url![cb delays svgs]
  (let [delays (if (number? delays) (repeat delays) delays)
       [w h] ((comp (juxt :width :height) second first) svgs)
         gif (js/GIF. #js {:workers 4
                          :quality 1
                          :width w
                          :height h
                          :workerScript worker-url
                          })
        process (fn process[svgs delays](let[img (js/Image.)
                                             svg-url (str->url (reagent.dom.server/render-to-static-markup 
                                                                 (first svgs))
                                                               "image/svg+xml")]
                                          (do
                                            (set! (.-onload img)
                                                  (fn[](do
                                                         (.addFrame gif img #js{:copy true :delay (first delays)})
                                                         (let[r (rest svgs)]
                                                           (if (seq r)
                                                             (process r (rest delays))
                                                             (.render gif)
                                                             )))))
                                            (set! (.-src img) svg-url))))]
    (do
      (.on gif "finished" cb);; partial does not work ?!
      (process svgs delays))))

(defn save-svgs![filename delays svgs]
(letfn [(download-blob! [filename blob]
  (let[download-link (. js/document (createElement "a"))]
    (do
      (set! (.-download download-link) filename)
      (set! (.-href download-link) (.createObjectURL js/URL blob))
      (.click download-link))))]
(svgs->animated-gif-url! (fn[blob](download-blob! filename blob)) delays svgs)))

(defn display-svgs![parent delays svgs]
(svgs->animated-gif-url! (fn[blob]
                          (let[img (js/Image.)]
                            (do
                            (.appendChild parent img)
                            (set! (.-src img) (.createObjectURL js/URL blob)))))
                            delays svgs))

(defn bezier-step [ps t]
(condp = (count ps)
1 (first ps)
2 (weighted-mean t ps)
3 (let[[p0 p1 p2] ps] (add (scale (* (- 1 t) (- 1 t)) p0) (add (scale (* 2 t (- 1 t)) p1) (scale (* t t) p2))))
(bezier-step (map (partial weighted-mean t) (partition 2 1 ps)) t)))

(defn bezier [n ps]
(if (< (count ps) 2) ps (mapv (comp (partial bezier-step ps) (partial * (/ 1 n))) (range (inc n)))))
(defn square-curve[n p0-p2 angle]
(let[inv-sqrt-2 (/ 1. (sqrt 2))
  p01 (weighted-mean inv-sqrt-2 p0-p2)
  p21 (weighted-mean (- 1. inv-sqrt-2) p0-p2)
  [p0 p2] p0-p2
  p1  (weighted-mean 0.5 [((make-rotate-around p0 (/ angle 2)) p01)
                          ((make-rotate-around p2 (/ angle -2)) p21)])]
                          (bezier n [p0 p1 p2])))

(defn square-with-curve [n angle]
(let[square (regular-polygon 4)]
[square (square-curve n [(first square)(nth square 2)] angle)]))
(defn power [x n] (nth (iterate (partial * x) 1) n))
(defn squares-params-f[angle invertRatio]
  (let[golden-ratio (/ 2. (+ 1. (sqrt 5)))
       [factor ratio a] (if invertRatio [-1 (/ 1. golden-ratio) angle ]
                                        [1 golden-ratio (- angle)])]
    [[] [(make-polylines-transform (comp (make-rotate-around [factor 0] a)
                                         (partial add [(* factor (+ 1. ratio)) 0])
                                         (partial scale ratio)))
         ;; should use (power ratio ?)
         (fn[n](square-with-curve (max 1 (if invertRatio (+ 10 n) (- 10 n))) 
                                  (* factor a)))]]))
         (defn fractal-step-f [[step-f step-elts-f] [current-elts i]]
  (into (step-elts-f i) (step-f current-elts)))

(defn params->params-f [[init-elts [step-f step-elts]]] [init-elts [step-f (constantly step-elts)]])

(defn fractal-f [[init-elts step-params-f] details]
  (reduce (fn[current-elts i] (fractal-step-f step-params-f [current-elts i])) init-elts (range (dec details) -1 -1)))
(def golden-squares-state (reagent.core/atom {:angle (/ PI -2) }))
(defn gui-golden-squares[]
  (let[angle (:angle @golden-squares-state)]
    [:div 
     [:div [:input {:type "range" :value (:angle @golden-squares-state) :step 0.01 :min (/ PI -2)  :max (/ PI 2)  :style {:width "90%"}
                    :on-change (fn[e] (swap! golden-squares-state assoc 
:angle (js/parseFloat (.-target.value e))))}]]
[draw-fitted-polylines [400 400](fractal-f (squares-params-f angle false) 4)]]))
(defn centered-golden-squares[[dx zoom angle] [details-inc details-dec]]
  ((make-polylines-transform (comp (partial add [(+ dx) 0]) (partial rotate (* angle -0.5)) (partial scale zoom)))
   (into (fractal-f (squares-params-f angle true) details-inc) (fractal-f (squares-params-f angle false) details-dec))))

(defn inclusive-range [n [[first last] times]]
  (if (== times 1) (mapv (comp (partial + first) (partial * (/ (- last first) n))) (range n))
    (into (inclusive-range (quot n times) [[first last] 1]) (inclusive-range (- n (quot n times)) [[last first] (dec times)]))))

(defn golden-squares-anim-params [n1 n2]
  (let[golden-ratio (/ 2. (+ 1. (sqrt 5)))
       with-break (fn[c](let[h (quot n1 2)
                             half-1 (vec (take h c))
                             half-2 (drop h c)]
                          (-> half-1 (into (repeat n2 (first half-2)))
                                      (into half-2))))
       dx (with-break (inclusive-range n1 [[0 (/ (+ 1 golden-ratio) golden-ratio)] 1]))
       dx (into dx dx)
       zoom (with-break (inclusive-range n1 [[(/ (+ 1 (sqrt 5)) 2) 1] 1]))
       zoom (into zoom zoom)
       angles (into (with-break (inclusive-range n1 [[0 (/ PI 2)] 2]))
                          (with-break (inclusive-range n1 [[0 (/ PI -2)] 2])))]
    (mapv vector dx zoom angles)))
(def golden-squares-anim-state (reagent.core/atom {:step 0 }))
(def anim-params (golden-squares-anim-params 100 10))
(def data (into anim-params anim-params))
(def wh [1024 512])
(def details [5 8])
;; comment fitting-tranform def to speed things up
(def fitting-transform (make-polylines-transform (make-fitting-transform wh 
                                                                         (reduce into [] (map (fn[p] (centered-golden-squares p
                                                                                                        [0 5])) anim-params)))))
(defn gui-golden-squares[]
  (let[step (:step @golden-squares-anim-state)
       n-steps (count data)]
    [:div
     [:div [:input {:type "range" :value (:step @golden-squares-anim-state) :min 0  :max n-steps :style {:width "90%"}
                    :on-change (fn[e] (swap! golden-squares-anim-state assoc 
                                             :step (js/parseFloat (.-target.value e))))}]]
     [draw-polylines wh (fitting-transform (centered-golden-squares (nth data step) details))]]))


(display-svgs! js/klipse-container 200 (map (fn[p](draw-polylines [1024 512] (fitting-transform 
                     (centered-golden-squares p [5 8])))) anim-params))


(let[n-steps 128
     half-n-steps (/ n-steps 2)
     rs->a (fn[rs](+ (/ PI -2) (* (/ rs half-n-steps) PI))) 
     s->a (fn[s](if (< s half-n-steps) (rs->a s) (rs->a (- n-steps s))))]
(display-svgs! js/klipse-container 200 (map (comp (partial draw-fitted-polylines [512 512])
(fn[angle]
(let[f1 (fractal-f (squares-params-f angle false) 12)]
((make-polylines-transform (partial rotate (/ angle -2)))
(reduce into [] [f1 ((make-polylines-transform (comp (make-rotate-around [-1 0] angle)(partial add [-2 0])
                                                                                        (fn[[x y]][(- x) y]))) f1)]))))
s->a)
(range n-steps))))


(def golden-squares-state (reagent.core/atom {:angle (/ PI -2) }))
(defn gui-golden-squares[]
  (let[angle (:angle @golden-squares-state)]
    [:div 
     [:div [:input {:type "range" :value (:angle @golden-squares-state) :step 0.01 :min (/ PI -2)  :max (/ PI 2)  :style {:width "90%"}
                    :on-change (fn[e] (swap! golden-squares-state assoc 
:angle (js/parseFloat (.-target.value e))))}]]
[draw-fitted-polylines [400 400](fractal-f (squares-params-f angle false) 4)]]))


(def golden-squares-state-2 (reagent.core/atom {:angle (/ PI -2) }))
(defn gui-golden-squares-2[]
  (let[angle (:angle @golden-squares-state-2)]
    [:div 
     [:div [:input {:type "range" :value (:angle @golden-squares-state-2) :step 0.01 :min (/ PI -2)  :max (/ PI 2)  :style {:width "90%"}
                    :on-change (fn[e] (swap! golden-squares-state-2 assoc 
:angle (js/parseFloat (.-target.value e))))}]]
     [draw-fitted-polylines [512 512](let[f1 (fractal-f (squares-params-f angle false) 12)]
                                   ((make-polylines-transform (partial rotate (/ angle -2)))(reduce into [] [f1 ((make-polylines-transform (comp (make-rotate-around [-1 0] angle)(partial add [-2 0])
                                                                                        (fn[[x y]][(- x) y]))) f1)])))]]))


(defn centered-golden-squares[[dx zoom angle] [details-inc details-dec]]
  ((make-polylines-transform (comp (partial add [(+ dx) 0]) (partial rotate (* angle -0.5)) (partial scale zoom)))
   (into (fractal-f (squares-params-f angle true) details-inc) (fractal-f (squares-params-f angle false) details-dec))))

(defn inclusive-range [n [[first last] times]]
  (if (== times 1) (mapv (comp (partial + first) (partial * (/ (- last first) n))) (range n))
    (into (inclusive-range (quot n times) [[first last] 1]) (inclusive-range (- n (quot n times)) [[last first] (dec times)]))))

(defn golden-squares-anim-params [n1 n2]
  (let[golden-ratio (/ 2. (+ 1. (sqrt 5)))
       with-break (fn[c](let[h (quot n1 2)
                             half-1 (vec (take h c))
                             half-2 (drop h c)]
                          (-> half-1 (into (repeat n2 (first half-2)))
                                      (into half-2))))
       dx (with-break (inclusive-range n1 [[0 (/ (+ 1 golden-ratio) golden-ratio)] 1]))
       dx (into dx dx)
       zoom (with-break (inclusive-range n1 [[(/ (+ 1 (sqrt 5)) 2) 1] 1]))
       zoom (into zoom zoom)
       angles (into (with-break (inclusive-range n1 [[0 (/ PI 2)] 2]))
                          (with-break (inclusive-range n1 [[0 (/ PI -2)] 2])))]
    (mapv vector dx zoom angles)))
[draw-fitted-polylines [400 400](centered-golden-squares (nth (golden-squares-anim-params 100 10) 55) [4 4])]


         (defn fractal-step-f [[step-f step-elts-f] [current-elts i]]
  (into (step-elts-f i) (step-f current-elts)))

(defn params->params-f [[init-elts [step-f step-elts]]] [init-elts [step-f (constantly step-elts)]])

(defn fractal-f [[init-elts step-params-f] details]
  (reduce (fn[current-elts i] (fractal-step-f step-params-f [current-elts i])) init-elts (range (dec details) -1 -1)))
[draw-fitted-polylines [400 400](fractal-f (squares-params-f (/ PI 4) false) 4)]


(defn power [x n] (nth (iterate (partial * x) 1) n))
(defn squares-params-f[angle invertRatio]
  (let[golden-ratio (/ 2. (+ 1. (sqrt 5)))
       [factor ratio a] (if invertRatio [-1 (/ 1. golden-ratio) angle ]
                                        [1 golden-ratio (- angle)])]
    [[] [(make-polylines-transform (comp (make-rotate-around [factor 0] a)
                                         (partial add [(* factor (+ 1. ratio)) 0])
                                         (partial scale ratio)))
         ;; should use (power ratio ?)
         (fn[n](square-with-curve (max 1 (if invertRatio (+ 10 n) (- 10 n))) 
                                  (* factor a)))]]))
[draw-fitted-polylines [400 400]
 (let[[init [step-f step-elts-f]] (squares-params-f (/ PI 4) false)]
     (step-f (step-elts-f 5)))]


(defn square-curve[n p0-p2 angle]
(let[inv-sqrt-2 (/ 1. (sqrt 2))
  p01 (weighted-mean inv-sqrt-2 p0-p2)
  p21 (weighted-mean (- 1. inv-sqrt-2) p0-p2)
  [p0 p2] p0-p2
  p1  (weighted-mean 0.5 [((make-rotate-around p0 (/ angle 2)) p01)
                          ((make-rotate-around p2 (/ angle -2)) p21)])]
                          (bezier n [p0 p1 p2])))

(defn square-with-curve [n angle]
(let[square (regular-polygon 4)]
[square (square-curve n [(first square)(nth square 2)] angle)]))
[draw-fitted-polylines [400 400] (square-with-curve 10 (/ PI 4))] 


(defn bezier-step [ps t]
(condp = (count ps)
1 (first ps)
2 (weighted-mean t ps)
3 (let[[p0 p1 p2] ps] (add (scale (* (- 1 t) (- 1 t)) p0) (add (scale (* 2 t (- 1 t)) p1) (scale (* t t) p2))))
(bezier-step (map (partial weighted-mean t) (partition 2 1 ps)) t)))

(defn bezier [n ps]
(if (< (count ps) 2) ps (mapv (comp (partial bezier-step ps) (partial * (/ 1 n))) (range (inc n)))))
(def ctrl-pts [[0 0][0 1][2 1]])
[draw-fitted-polylines [400 400] [ctrl-pts (bezier 16 ctrl-pts)]]


(defn weighted-mean [t [p0 p1]]
(add (scale (- 1 t) p0) (scale t p1)))
(weighted-mean 0.25 [[0 1] [1 2]])


(defn sierp-sq-step[pps]
  (reduce into [] (for [x [-1 0 1] y [-1 0 1] :when (or (not (zero? x)) (not(zero? y)))] 
                    ((make-polylines-transform 
                       (comp (partial add (rotate (/ PI 4)
                                                  (scale (sqrt 2) [x y])))
                             (partial scale (/ 1 3)))) pps))))
(def sierp-sq-params-f [[]
                        [sierp-sq-step
                         (constantly [(regular-polygon 4)])]])
(defn sierp-sq[n]
  (let[center (fn c [n](if (<= n 0) 0 (+ (/ 2 (power 3 (dec n))) (c (dec n))) ))
       u (fn[n](+ (center n) (/ 1 (power 3 n))))]
    ((make-polylines-transform (partial scale (/ 1 (u (dec n)))))
     (fractal-f sierp-sq-params-f n))))

(defn sierp-params-f[angle invertRatio]
  (let[golden-ratio (/ 2. (+ 1. (sqrt 5)))
       [factor ratio a] (if invertRatio [-1 (/ 1. golden-ratio) angle ]
                          [1 golden-ratio (- angle)])]
    [[] [(make-polylines-transform (comp (make-rotate-around [factor 0] a)
                                         (partial add [(* factor (+ 1. ratio)) 0])
                                         (partial scale ratio)))
         ;; should use (power ratio ?)
         (fn[n](sierp-sq (if invertRatio 3 
                           (min 3 (max 1 (- 3 n))))))]]))
(;; <- wait for other anim to be done before starting this
(defn centered-golden-sierp[[dx zoom angle]
                            [details-inc details-dec]]
  ((make-polylines-transform (comp (partial add [(+ dx) 0])
                                   (partial rotate (* angle -0.5))
                                   (partial scale zoom)))
   (into (fractal-f (sierp-params-f angle true) details-inc)
         (fractal-f (sierp-params-f angle false) details-dec))))
(display-svgs! js/klipse-container 200 (map (fn[p](draw-polylines [1024 512] (fitting-transform 
                                                                               (centered-golden-sierp p [5 8]))))
 anim-params))

test