Commit 7663b5a7 authored by Ali's avatar Ali

Initial commit

parents
/bower_components/
/node_modules/
/.pulp-cache/
/output/
/generated-docs/
/.psc-package/
/.psc*
/.purs*
/.psa*
/.spago
{
"name": "purescript-d3",
"description": "PureScript bindings for D3",
"repository": {
"type": "git",
"url": "git://github.com/pelotom/purescript-d3.git"
},
"license": "MIT",
"ignore": [
"**/.*",
"docsrc",
"gulpfile.js",
"package.json"
],
"dependencies": {
"d3": "^3.4.9",
"purescript-foreign": "^4.0.1",
"purescript-easy-ffi": "^2.1.2",
"purescript-js-date": "^5.1.0"
},
"private": false,
"homepage": "https://github.com/pelotom/purescript-d3",
"_release": "d907d98043",
"_resolution": {
"type": "branch",
"branch": "master",
"commit": "d907d9804343b843244add72e00b6c3827575919"
},
"_source": "https://github.com/pelotom/purescript-d3.git",
"_target": "master",
"_originalSource": "pelotom/purescript-d3"
}
\ No newline at end of file
Copyright (c) 2014 Tom Crockett
Permission is hereby granted, free of charge, to any person obtaining
a copy of this software and associated documentation files (the
"Software"), to deal in the Software without restriction, including
without limitation the rights to use, copy, modify, merge, publish,
distribute, sublicense, and/or sell copies of the Software, and to
permit persons to whom the Software is furnished to do so, subject to
the following conditions:
The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION
OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION
WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
# purescript-d3
### Example
Here is the JavaScript code from [part 1](http://bl.ocks.org/mbostock/7322386) of Mike Bostock's [Let's Make a Bar Chart](http://bost.ocks.org/mike/bar/) series of tutorials for D3:
```javascript
var data = [4, 8, 15, 16, 23, 42];
var x = d3.scale.linear()
.domain([0, d3.max(data)])
.range([0, 420]);
d3.select(".chart")
.selectAll("div")
.data(data)
.enter().append("div")
.style("width", function(d) { return x(d) + "px"; })
.text(function(d) { return d; });
```
And here is the PureScript equivalent:
```haskell
array = [4, 8, 15, 16, 23, 42]
main = do
x <- linearScale
.. domain [0, max id array]
.. range [0, 420]
.. toFunction
rootSelect ".chart"
.. selectAll "div"
.. bindData array
.. enter .. append "div"
.. style' "width" (\d -> show (x d) ++ "px")
.. text' show
```
Note that `..` is an alias for `>>=`. The [fluent interface](http://en.wikipedia.org/wiki/Fluent_interface) is just a poor man's [programmable semicolon](http://en.wikipedia.org/wiki/Monad_(functional_programming))!
The PureScript D3 bindings statically enforce several properties of D3's selection semantics; for instance, if you were to remove the `.. append "div"` above you would get a type error, because the code following it would be attempting to set things on the unrealized nodes of an [enter selection](https://github.com/mbostock/d3/wiki/Selections#enter). Similarly, if you removed the `.. bindData array` line you would get a type error because you can only obtain an enter selection from an update selection (the selection produced by calling `data` in JavaScript or `bindData` in PureScript). In JavaScript you would have to wait until runtime to see these kinds of errors.
Selections also carry information about the type of data bound to them (if any). Until data is bound to a selection it is only possible to set constant attributes on it; afterwards you can use well-typed functions of the data.
You can find more examples [here](https://github.com/pelotom/purescript-d3-examples/tree/master/src).
### Development
```
yarn # install dependencies from package.json and bower.json
yarn build # compile the code
```
{
"name": "purescript-d3",
"description": "PureScript bindings for D3",
"repository": {
"type": "git",
"url": "git://github.com/pelotom/purescript-d3.git"
},
"license": "MIT",
"ignore": [
"**/.*",
"docsrc",
"gulpfile.js",
"package.json"
],
"dependencies": {
"d3": "^3.4.9",
"purescript-foreign": "^4.0.1",
"purescript-easy-ffi": "^2.1.2",
"purescript-js-date": "^5.1.0"
},
"private": false
}
/* global exports */
"use strict";
// module Graphics.D3.SVG.Axis
exports.axis = d3.svg.axis;
module Graphics.D3.SVG.Axis
( Axis()
, axis
, scale
, orient
, ticks
, tickFormat
, renderAxis
) where
import Graphics.D3.Base (D3Eff)
import Graphics.D3.Selection (class Existing, Selection)
import Graphics.D3.Scale (class Scale)
import Data.Foreign.EasyFFI (unsafeForeignFunction)
ffi :: forall a. Array String -> String -> a
ffi = unsafeForeignFunction
foreign import data Axis :: Type
foreign import axis :: D3Eff Axis
scale :: forall s d. (Scale s) => s d Number -> Axis -> D3Eff Axis
scale = ffi ["scale", "axis", ""] "axis.scale(scale)"
orient :: String -> Axis -> D3Eff Axis
orient = ffi ["orientation", "axis", ""] "axis.orient(orientation)"
ticks :: Number -> Axis -> D3Eff Axis
ticks = ffi ["count", "axis", ""] "axis.ticks(count)"
tickFormat :: String -> Axis -> D3Eff Axis
tickFormat = ffi ["format", "axis", ""] "axis.tickFormat(d3.format(format))"
renderAxis :: forall s d. (Existing s) => Axis -> s d -> D3Eff (Selection d)
renderAxis = ffi ["axis", "selection", ""] "selection.call(axis)"
module Graphics.D3.Base
( D3()
, D3Eff()
) where
import Control.Monad.Eff
foreign import data D3 :: Effect
type D3Eff a = forall e. Eff (d3 :: D3 | e) a
\ No newline at end of file
module Graphics.D3.Interpolate
( Interpolator()
, makeInterpolator
) where
import Data.Foreign.EasyFFI
ffi = unsafeForeignFunction
foreign import data Interpolator :: Type -> Type
makeInterpolator :: forall a. (a -> a -> Number -> a) -> Interpolator a
makeInterpolator = ffi ["f"] "function (x, y) { return f(x)(y); }"
module Graphics.D3.Layout.Base
( class GraphLayout
, size
, nodes
, links
) where
import Graphics.D3.Base
class GraphLayout l where
nodes :: forall a. Array a -> l -> D3Eff l
links :: forall a. Array a -> l -> D3Eff l
size :: forall d. { width :: Number, height :: Number | d } -> l -> D3Eff l
class (GraphLayout l) <= HierarchyLayout l where
-- TODO: children, sort, value, revalue
/* global exports */
"use strict";
// module Graphics.D3.Layout.Force
exports.forceLayout = d3.layout.force;
module Graphics.D3.Layout.Force
( ForceLayout(..)
, forceLayout
, linkDistance
, linkStrength
, friction
, charge
, chargeDistance
, theta
, gravity
, start
, alpha
, resume
, stop
, tick
, drag
, onDragStart
, onTick
, createDrag
) where
import Control.Monad.Eff (Eff)
import Data.Foreign (Foreign)
import Data.Foreign.EasyFFI (unsafeForeignFunction)
import Graphics.D3.Base (D3Eff)
import Graphics.D3.Selection (Selection)
import Graphics.D3.Layout.Base
ffi :: forall a. Array String -> String -> a
ffi = unsafeForeignFunction
foreign import data ForceLayout :: Type
foreign import forceLayout :: D3Eff ForceLayout
instance forceGraphLayout :: GraphLayout ForceLayout where
size dims = ffi ["w", "h", "force", ""] "force.size([w, h])" dims.width dims.height
nodes = ffi ["nodes", "force", ""] "force.nodes(nodes)"
links = ffi ["links", "force", ""] "force.links(links)"
linkDistance :: Number -> ForceLayout -> D3Eff ForceLayout
linkDistance = ffi ["distance", "force", ""] "force.linkDistance(distance)"
linkStrength :: Number -> ForceLayout -> D3Eff ForceLayout
linkStrength = ffi ["strength", "force", ""] "force.linkStrength(strength)"
friction :: Number -> ForceLayout -> D3Eff ForceLayout
friction = ffi ["friction", "force", ""] "force.friction(friction)"
charge :: Number -> ForceLayout -> D3Eff ForceLayout
charge = ffi ["charge", "force", ""] "force.charge(charge)"
chargeDistance :: Number -> ForceLayout -> D3Eff ForceLayout
chargeDistance = ffi ["distance", "force", ""] "force.chargeDistance(distance)"
theta :: Number -> ForceLayout -> D3Eff ForceLayout
theta = ffi ["theta", "force", ""] "force.theta(theta)"
gravity :: Number -> ForceLayout -> D3Eff ForceLayout
gravity = ffi ["gravity", "force", ""] "force.gravity(gravity)"
start :: ForceLayout -> D3Eff ForceLayout
start = ffi ["force", ""] "force.start()"
alpha :: Number -> ForceLayout -> D3Eff ForceLayout
alpha = ffi ["alpha", "force", ""] "force.alpha(alpha)"
resume :: ForceLayout -> D3Eff ForceLayout
resume = ffi ["force", ""] "force.resume()"
stop :: ForceLayout -> D3Eff ForceLayout
stop = ffi ["force", ""] "force.stop()"
tick :: ForceLayout -> D3Eff ForceLayout
tick = ffi ["force", ""] "force.tick()"
onTick :: forall e r. (Foreign -> Eff e r) -> ForceLayout -> D3Eff ForceLayout
onTick = ffi
["callback", "force", ""]
"force.on('tick', function (d) { return callback(d)(); })"
onDragStart :: forall e r. (Foreign -> Eff e r) -> ForceLayout -> D3Eff ForceLayout
onDragStart = ffi ["callback", "force", ""] "force.on('dragstart', callback)"
drag :: ForceLayout -> D3Eff ForceLayout
drag = ffi ["force", ""] "force.drag()"
createDrag :: forall s. ForceLayout -> Selection s -> D3Eff (Selection s)
createDrag = ffi ["obj", "callable", ""] "callable.call(obj);"
module Graphics.D3.Request
( RequestError ()
, csv
, tsv
, json
) where
import Data.Either (Either(..))
import Data.Foreign (Foreign)
import Data.Foreign.EasyFFI (unsafeForeignFunction)
import Control.Monad.Eff (Eff)
import Graphics.D3.Base (D3Eff, D3)
import Prelude ( Unit() )
type RequestError = { status :: Number, statusText :: String }
csv :: forall e a. String -> (Either RequestError (Array Foreign) -> Eff (d3 :: D3 | e) a) -> D3Eff Unit
csv = ff (\d -> d) Left Right
where
ff = unsafeForeignFunction
["acc", "Left", "Right", "url", "handle", ""]
"d3.csv(url, acc, function(error, data) { if (error) handle(Left(error))(); else handle(Right(data))(); })"
tsv :: forall e a. String -> (Either RequestError (Array Foreign) -> Eff (d3 :: D3 | e) a) -> D3Eff Unit
tsv = ff (\d -> d) Left Right
where
ff = unsafeForeignFunction
["acc", "Left", "Right", "url", "handle", ""]
"d3.tsv(url, acc, function(error, data) { if (error) handle(Left(error))(); else handle(Right(data))(); })"
json :: forall e a. String -> (Either RequestError Foreign -> Eff (d3 :: D3 | e) a) -> D3Eff Unit
json = ff Left Right
where
ff = unsafeForeignFunction
["Left", "Right", "url", "handle", ""]
"d3.json(url, function (error, data) { if (error) handle(Left(error))(); else handle(Right(data))(); })"
/* global exports */
"use strict";
// module Graphics.D3.Scale
exports.linearScale = d3.scale.linear;
exports.powerScale = d3.scale.pow;
exports.sqrtScale = d3.scale.sqrt;
exports.logScale = function() {
return d3.scale.log();
};
exports.quantizeScale = d3.scale.quantize;
exports.quantileScale = d3.scale.quantile;
exports.thresholdScale = d3.scale.threshold;
exports.ordinalScale = d3.scale.ordinal;
module Graphics.D3.Scale
( class Scale
, class Quantitative
, LinearScale()
, PowerScale()
, LogScale()
, QuantizeScale()
, QuantileScale()
, ThresholdScale()
, OrdinalScale()
, linearScale
, powerScale
, sqrtScale
, logScale
, quantizeScale
, quantileScale
, thresholdScale
, ordinalScale
, domain
, range
, copy
, toFunction
, invert
, rangeRound
, interpolate
, clamp
, nice
, getTicks
, getTickFormat
, exponent
, base
, rangePoints
, rangeBands
, rangeRoundBands
, rangeBand
, rangeExtent
) where
import Graphics.D3.Base (D3Eff)
import Graphics.D3.Interpolate (Interpolator)
import Graphics.D3.Unsafe (unsafeToFunction, unsafeCopy, unsafeRange, unsafeDomain)
import Control.Monad.Eff.Exception.Unsafe (unsafeThrow)
import Data.Tuple (Tuple(..))
import Data.Maybe (Maybe(..))
import Data.Foreign.EasyFFI (unsafeForeignFunction)
import Prelude ( ($), (>>=), pure, bind )
ffi = unsafeForeignFunction
-- A base class for all scale types
class Scale s where
domain :: forall d r. Array d -> s d r -> D3Eff (s d r)
range :: forall d r. Array r -> s d r -> D3Eff (s d r)
copy :: forall d r. s d r -> D3Eff (s d r)
toFunction :: forall d r. s d r -> D3Eff (d -> r)
-- Quantitative (numeric domain) scales
class Quantitative s where
invert :: s Number Number -> D3Eff (Number -> Number)
rangeRound :: Array Number -> s Number Number -> D3Eff (s Number Number)
interpolate :: forall r. Interpolator r -> s Number r -> D3Eff (s Number r)
clamp :: forall r. Boolean -> s Number r -> D3Eff (s Number r)
nice :: forall r. Maybe Number -> s Number r -> D3Eff (s Number r)
getTicks :: forall r. Maybe Number -> s Number r -> D3Eff (Array Number)
getTickFormat :: forall r. Number -> Maybe String -> s Number r -> D3Eff (Number -> String)
-- Scale types
foreign import data LinearScale :: Type -> Type -> Type
foreign import data IdentityScale :: Type -> Type -> Type
foreign import data PowerScale :: Type -> Type -> Type
foreign import data LogScale :: Type -> Type -> Type
foreign import data QuantizeScale :: Type -> Type -> Type
foreign import data QuantileScale :: Type -> Type -> Type
foreign import data ThresholdScale :: Type -> Type -> Type
foreign import data OrdinalScale :: Type -> Type -> Type
-- Scale constructors
foreign import linearScale :: forall r. D3Eff (LinearScale Number r)
foreign import powerScale :: forall r. D3Eff (PowerScale Number r)
foreign import sqrtScale :: forall r. D3Eff (PowerScale Number r)
foreign import logScale :: forall r. D3Eff (LogScale Number r)
foreign import quantizeScale :: forall r. D3Eff (QuantizeScale Number r)
foreign import quantileScale :: forall r. D3Eff (QuantileScale Number r)
foreign import thresholdScale :: forall r. D3Eff (ThresholdScale Number r)
foreign import ordinalScale :: forall d r. D3Eff (OrdinalScale d r)
-- Power scale methods
exponent :: forall r. Number -> PowerScale Number r -> D3Eff (PowerScale Number r)
exponent = ffi ["k", "scale", ""] "scale.exponent(k)"
-- Log scale methods
base :: forall r. Number -> LogScale Number r -> D3Eff (LogScale Number r)
base = ffi ["base", "scale", ""] "scale.base(base)"
-- Quantile scale methods
quantiles :: forall r. QuantileScale Number r -> D3Eff (QuantileScale Number r)
quantiles = ffi ["scale", ""] "scale.quantiles()"
-- Ordinal scale methods
rangePoints :: forall d. Number -> Number -> Number -> OrdinalScale d Number -> D3Eff (OrdinalScale d Number)
rangePoints = ffi
["min", "max", "padding", "scale", ""]
"scale.rangePoints([min, max], padding)"
rangeBands :: forall d. Number -> Number -> Number -> Number -> OrdinalScale d Number -> D3Eff (OrdinalScale d Number)
rangeBands = ffi
["min", "max", "padding", "outerPadding", "scale", ""]
"scale.rangeBands([min, max], padding, outerPadding)"
rangeRoundBands :: forall d. Number -> Number -> Number -> Number -> OrdinalScale d Number -> D3Eff (OrdinalScale d Number)
rangeRoundBands = ffi
["min", "max", "padding", "outerPadding", "scale", ""]
"scale.rangeRoundBands([min, max], padding, outerPadding)"
rangeBand :: forall d. OrdinalScale d Number -> D3Eff Number
rangeBand = ffi ["scale"] "scale.rangeBand"
rangeExtent :: forall d. OrdinalScale d Number -> D3Eff (Tuple Number Number)
rangeExtent scale = do
rng <- ffi ["scale"] "scale.rangeExtent" scale
case rng of
[min, max] -> pure $ Tuple min max
_ -> unsafeThrow "scale function returned more or less than 2 elements"
-- Scale class instances
instance scaleLinear :: Scale LinearScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
instance quantitativeLinear :: Quantitative LinearScale where
invert = unsafeInvert
rangeRound = unsafeRangeRound
interpolate = unsafeInterpolate
clamp = unsafeClamp
nice = unsafeNice
getTicks = unsafeTicks
getTickFormat = unsafeTickFormat
instance scalePower :: Scale PowerScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
instance quantitativePower :: Quantitative PowerScale where
invert = unsafeInvert
rangeRound = unsafeRangeRound
interpolate = unsafeInterpolate
clamp = unsafeClamp
nice = unsafeNice
getTicks = unsafeTicks
getTickFormat = unsafeTickFormat
instance scaleLog :: Scale LogScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
instance quantitativeLog :: Quantitative LogScale where
invert = unsafeInvert
rangeRound = unsafeRangeRound
interpolate = unsafeInterpolate
clamp = unsafeClamp
nice = unsafeNice
getTicks = unsafeTicks
getTickFormat = unsafeTickFormat
instance scaleQuantize :: Scale QuantizeScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
instance scaleQuantile :: Scale QuantileScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
instance scaleThreshold :: Scale ThresholdScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
instance scaleOrdinal :: Scale OrdinalScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
unsafeInvert = ffi ["scale", ""] "scale.copy().invert"
unsafeRangeRound = ffi ["values", "scale", ""] "scale.rangeRound(values)"
unsafeInterpolate = ffi ["factory", "scale", ""] "scale.interpolate(factory)"
unsafeClamp = ffi ["bool", "scale", ""] "scale.clamp(bool)"
unsafeNice count = case count of
Nothing -> ffi ["scale", ""] "scale.nice()"
Just c -> ffi ["count", "scale", ""] "scale.nice(count)" c
unsafeTicks count = case count of
Nothing -> ffi ["scale", ""] "scale.ticks()"
Just c -> ffi ["count", "scale", ""] "scale.ticks(count)" c
unsafeTickFormat count format = case format of
Nothing -> ffi ["count", "scale", ""] "scale.tickFormat(count)" count
Just f -> ffi ["count", "format", "scale", ""] "scale.tickFormat(count, format)" count f
module Graphics.D3.Selection
( Selection()
, Update()
, Enter()
, Exit()
, Transition()
, Void()
, class AttrValue
, class Existing
, class Appendable
, class Clickable
, rootSelect
, rootSelectAll
, select
, selectAll
, bindData
, enter
, exit
, transition
, append
, remove
, attr
, attr'
, attr''
, style
, style'
, style''
, text
, text'
, text''
, delay
, delay'
, delay''
, duration
, duration'
, duration''
, onClick
, onDoubleClick
) where
import Graphics.D3.Base (D3Eff)
import Control.Monad.Eff (Eff)
import Data.Foreign (Foreign)
import Data.Foreign.EasyFFI (unsafeForeignFunction)
import Prelude ( Unit() )
ffi :: forall a. Array String -> String -> a
ffi = unsafeForeignFunction
-- The "selection-y" types, parameterized by the type of their bound data
foreign import data Selection :: Type -> Type
foreign import data Update :: Type -> Type
foreign import data Enter :: Type -> Type
foreign import data Transition :: Type -> Type
-- Exit selections have the same semantics as regular selections
type Exit d = Selection d
-- The (uninhabited) type of an unbound selection's data
data Void
-- The class of types which element attribute values can have (numbers and strings)
class AttrValue a
instance attrValNumber :: AttrValue Number
instance attrValString :: AttrValue String
rootSelect :: String -> D3Eff (Selection Void)
rootSelect = ffi ["selector", ""] "d3.select(selector)"
rootSelectAll :: String -> D3Eff (Selection Void)
rootSelectAll = ffi ["selector", ""] "d3.selectAll(selector)"
select :: forall d. String -> Selection d -> D3Eff (Selection d)
select = ffi ["selector", "selection", ""] "selection.select(selector)"
selectAll :: forall d. String -> Selection d -> D3Eff (Selection Void)
selectAll = ffi ["selector", "selection", ""] "selection.selectAll(selector)"
bindData :: forall oldData newData. Array newData -> Selection oldData -> D3Eff (Update newData)
bindData = ffi ["array", "selection", ""] "selection.data(array)"
enter :: forall d. Update d -> D3Eff (Enter d)
enter = ffi ["update", ""] "update.enter()"
exit :: forall d. Update d -> D3Eff (Exit d)
exit = ffi ["update", ""] "update.exit()"
transition :: forall s d. (Existing s) => s d -> D3Eff (Transition d)
transition = ffi ["selection", ""] "selection.transition()"
unsafeAppend :: forall x y. String -> x -> D3Eff y
unsafeAppend = ffi ["tag", "selection", ""] "selection.append(tag)"
unsafeRemove :: forall s. s -> D3Eff Unit
unsafeRemove = ffi ["selection", ""] "selection.remove()"
unsafeAttr :: forall v s. (AttrValue v) => String -> v -> s -> D3Eff s
unsafeAttr = ffi ["key", "val", "selection", ""] "selection.attr(key, val)"
unsafeAttr' :: forall d v s. (AttrValue v) => String -> (d -> v) -> s -> D3Eff s
unsafeAttr' = ffi ["key", "val", "selection", ""] "selection.attr(key, val)"
unsafeAttr'' :: forall d v s. (AttrValue v) => String -> (d -> Number -> v) -> s -> D3Eff s
unsafeAttr'' = ffi
["key", "val", "selection", ""]
"selection.attr(key, function (d, i) { return val(d)(i); })"
unsafeStyle :: forall s. String -> String -> s -> D3Eff s
unsafeStyle = ffi ["key", "val", "selection", ""] "selection.style(key, val)"
unsafeStyle' :: forall d s. String -> (d -> String) -> s -> D3Eff s
unsafeStyle' = ffi ["key", "val", "selection", ""] "selection.style(key, val)"
unsafeStyle'' :: forall d s. String -> (d -> Number -> String) -> s -> D3Eff s
unsafeStyle'' = ffi
["key", "val", "selection", ""]
"selection.style(key, function (d, i) { return val(d)(i); })"
unsafeText :: forall s. String -> s -> D3Eff s
unsafeText = ffi ["text", "selection", ""] "selection.text(text)"
unsafeText' :: forall d s. (d -> String) -> s -> D3Eff s
unsafeText' = ffi ["text", "selection", ""] "selection.text(text)"
unsafeText'' :: forall d s. (d -> Number -> String) -> s -> D3Eff s
unsafeText'' = ffi
["text", "selection", ""]
"selection.text(function (d, i) { return text(d)(i); })"
unsafeOnClick :: forall eff c i r. (Clickable c) => (i -> Eff eff r) -> c -> D3Eff c
unsafeOnClick = ffi ["callback", "clickable", ""] "clickable.on('click', function(data) { callback(data)(); })"
unsafeOnDoubleClick :: forall eff c i r. (Clickable c) => (i -> Eff eff r) -> c -> D3Eff c
unsafeOnDoubleClick = ffi ["callback", "clickable", ""] "clickable.on('dblclick', function (data) { callback(data)(); })"
-- Transition-only stuff
delay :: forall d. Number -> Transition d -> D3Eff (Transition d)
delay = ffi ["delay", "transition", ""] "transition.delay(delay)"
delay' :: forall d. (d -> Number) -> Transition d -> D3Eff (Transition d)
delay' = ffi ["delay", "transition", ""] "transition.delay(delay)"
delay'' :: forall d. (d -> Number -> Number) -> Transition d -> D3Eff (Transition d)
delay'' = ffi
["delay", "transition", ""]
"transition.delay(function (d, i) { return delay(d)(i); })"
duration :: forall d. Number -> Transition d -> D3Eff (Transition d)
duration = ffi ["duration", "transition", ""] "transition.duration(duration)"
duration' :: forall d. (d -> Number) -> Transition d -> D3Eff (Transition d)
duration' = ffi ["duration", "transition", ""] "transition.duration(duration)"
duration'' :: forall d. (d -> Number -> Number) -> Transition d -> D3Eff (Transition d)
duration'' = ffi
["duration", "transition", ""]
"transition.duration(function (d, i) { return duration(d)(i); })"
-- Selection-y things which can be appended to / inserted into
class Appendable s where
append :: forall d. String -> s d -> D3Eff (Selection d)
instance appendableSelection :: Appendable Selection where
append = unsafeAppend
instance appendableUpdate :: Appendable Update where
append = unsafeAppend
instance appendableEnter :: Appendable Enter where
append = unsafeAppend
-- Selection-y things that contain existing DOM elements
class Existing s where
attr :: forall d v. (AttrValue v) => String -> v -> s d -> D3Eff (s d)
attr' :: forall d v. (AttrValue v) => String -> (d -> v) -> s d -> D3Eff (s d)
attr'' :: forall d v. (AttrValue v) => String -> (d -> Number -> v) -> s d -> D3Eff (s d)
style :: forall d. String -> String -> s d -> D3Eff (s d)
style' :: forall d. String -> (d -> String) -> s d -> D3Eff (s d)
style'' :: forall d. String -> (d -> Number -> String) -> s d -> D3Eff (s d)
text :: forall d. String -> s d -> D3Eff (s d)
text' :: forall d. (d -> String) -> s d -> D3Eff (s d)
text'' :: forall d. (d -> Number -> String) -> s d -> D3Eff (s d)
remove :: forall d. s d -> D3Eff Unit
instance existingSelection :: Existing Selection where
attr = unsafeAttr
attr' = unsafeAttr'
attr'' = unsafeAttr''
style = unsafeStyle
style' = unsafeStyle'
style'' = unsafeStyle''
text = unsafeText
text' = unsafeText'
text'' = unsafeText''
remove = unsafeRemove
instance existingUpdate :: Existing Update where
attr = unsafeAttr
attr' = unsafeAttr'
attr'' = unsafeAttr''
style = unsafeStyle
style' = unsafeStyle'
style'' = unsafeStyle''
text = unsafeText
text' = unsafeText'
text'' = unsafeText''
remove = unsafeRemove
instance existingTransition :: Existing Transition where
attr = unsafeAttr
attr' = unsafeAttr'
attr'' = unsafeAttr''
style = unsafeStyle
style' = unsafeStyle'
style'' = unsafeStyle''
text = unsafeText
text' = unsafeText'
text'' = unsafeText''
remove = unsafeRemove
class Clickable c where
onClick :: forall eff r. (Foreign -> Eff eff r) -> c -> D3Eff c
onDoubleClick :: forall eff r. (Foreign -> Eff eff r) -> c -> D3Eff c
instance clickableSelection :: Clickable (Selection a) where
-- NOTE: psc complains about cycles unless onclick/onDoubleClick are inlined
onClick = ffi ["callback", "clickable", ""] "clickable.on('click', function(data) { callback(data)(); })"
onDoubleClick = ffi ["callback", "clickable", ""] "clickable.on('dblclick', function (data) { callback(data)(); })"
/* global exports */
"use strict";
// module Graphics.D3.Time
exports.timeScale = d3.time.scale;
module Graphics.D3.Time (
TimeScale(),
timeScale
) where
import Data.JSDate (JSDate)
import Graphics.D3.Base (D3Eff)
import Graphics.D3.Scale (class Scale)
import Graphics.D3.Unsafe
foreign import data TimeScale :: Type -> Type -> Type
foreign import timeScale :: forall r. D3Eff (TimeScale JSDate r)
instance scaleTime :: Scale TimeScale where
domain = unsafeDomain
range = unsafeRange
copy = unsafeCopy
toFunction = unsafeToFunction
module Graphics.D3.Unsafe (
unsafeDomain,
unsafeRange,
unsafeCopy,
unsafeToFunction
) where
import Data.Foreign.EasyFFI
ffi = unsafeForeignFunction
unsafeDomain = ffi ["domain", "scale", ""] "scale.domain(domain)"
unsafeRange = ffi ["values", "scale", ""] "scale.range(values)"
unsafeCopy = ffi ["scale", ""] "scale.copy()"
unsafeToFunction = ffi ["scale", ""] "scale.copy()"
\ No newline at end of file
module Graphics.D3.Util
( class Magnitude
, min
, max
, min'
, max'
, extent
, extent'
, (..)
, (...)
) where
import Data.Foreign.EasyFFI
import Data.JSDate (JSDate)
import Control.Bind (bind)
import Data.Function (applyFlipped)
class Magnitude n
instance numberMagnitude :: Magnitude Number
instance dateMagnitude :: Magnitude JSDate
min' :: forall d m. (Magnitude m) => (d -> m) -> Array d -> m
min' = unsafeForeignFunction ["fn", "data"] "d3.min(data, fn)"
max' :: forall d m. (Magnitude m) => (d -> m) -> Array d -> m
max' = unsafeForeignFunction ["fn", "data"] "d3.max(data, fn)"
min :: forall m. (Magnitude m) => Array m -> m
min = unsafeForeignFunction ["data"] "d3.min(data)"
max :: forall m. (Magnitude m) => Array m -> m
max = unsafeForeignFunction ["data"] "d3.max(data)"
-- extent takes a data array and returns [min,max]
-- not restricted to Number, i.e. also works with time
extent :: forall m. (Magnitude m) => Array m -> Array m
extent = unsafeForeignFunction ["data"] "d3.extent(data)"
extent' :: forall d m. (Magnitude m) => (d->m) -> Array d -> Array m
extent' = unsafeForeignFunction ["fn", "data"] "d3.extent(data, fn)"
-- Syntactic sugar to make chained monadic statements look similar to the
-- "fluid interface" style of chained method calls in JavaScript
infixl 4 bind as ..
-- Reversed function application, useful for applying extended monadic chains
-- to already-obtained values
infixl 4 applyFlipped as ...
This source diff could not be displayed because it is too large. You can view the blob instead.
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="UTF-8">
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>Sandbox D3</title>
</head>
<body>
<script src="./index.js"></script>
</body>
</html>
\ No newline at end of file
// Generated by purs bundle 0.13.8
var PS = {};
(function(exports) {
"use strict";
exports.log = function (s) {
return function () {
console.log(s);
return {};
};
};
})(PS["Effect.Console"] = PS["Effect.Console"] || {});
(function($PS) {
// Generated by purs version 0.13.8
"use strict";
$PS["Effect.Console"] = $PS["Effect.Console"] || {};
var exports = $PS["Effect.Console"];
var $foreign = $PS["Effect.Console"];
exports["log"] = $foreign.log;
})(PS);
(function($PS) {
// Generated by purs version 0.13.8
"use strict";
$PS["Main"] = $PS["Main"] || {};
var exports = $PS["Main"];
var Effect_Console = $PS["Effect.Console"];
var main = Effect_Console.log("\ud83c\udf5d");
exports["main"] = main;
})(PS);
PS["Main"].main();
\ No newline at end of file
{
"name": "D3purs",
"version": "0.0.1",
"scripts": {
"generate-purs-packages-nix": "./nix/generate-purs-packages.nix",
"generate-psc-packages-nix": "./nix/generate-packages-json.bash",
"rebase-set": "spago upgrade-set && yarn generate-psc-packages-nix",
"rebuild-set": "yarn generate-psc-packages-nix",
"install-ps": "psc-package install",
"compile": "pulp build",
"build": "pulp browserify -t dist/bundle.js",
"css": "sass src/sass/sass.sass:dist/styles/sass.css && sass src/sass/bootstrap/default.sass:dist/styles/bootstrap-default.css && cp node_modules/bootstrap-dark/src/bootstrap-dark.css dist/styles/bootstrap-dark.css && sass src/sass/bootstrap/greyson.scss:dist/styles/bootstrap-greyson.css && sass src/sass/bootstrap/monotony.scss:dist/styles/bootstrap-monotony.css && sass src/sass/bootstrap/darkster.scss:dist/styles/bootstrap-darkster.css && sass src/sass/bootstrap/herbie.scss:dist/styles/bootstrap-herbie.css",
"docs": "pulp docs -- --format html",
"repl": "pulp repl",
"clean": "rm -Rf output node_modules",
"clean-js": "rm -Rf node_modules",
"clean-ps": "rm -Rf output",
"test": "pulp test",
"server": "serve dist",
"prod": "yarn prod:compile && yarn prod:dce && yarn prod:bundle && yarn prod:pack",
"prod:compile": "pulp build -- -g corefn",
"prod:dce": "zephyr -f Main.main",
"prod:bundle": "pulp browserify --skip-compile -o dce-output -t app.js",
"prod:pack": "parcel build index.html -d prod --public-url . --no-source-maps"
},
"dependencies": {
"aes-js": "^3.1.1",
"base-x": "^3.0.2",
"bootstrap": "4.4.1",
"bootstrap-dark": "^1.0.3",
"create-react-class": "^15.6.3",
"d3": "^6.7.0",
"echarts": "^4.1.0",
"echarts-for-react": "^2.0.14",
"highlightjs": "^9.16.2",
"immer": "^8.0.1",
"prop-types": "^15.6.2",
"pullstate": "^1.20.6",
"react": "^16.10",
"react-awesome-popover": "^6.1.1",
"react-dom": "^16.10",
"react-tooltip": "^4.2.8",
"secp256k1": "^3.3.0",
"sigma": "git://github.com/poorscript/sigma.js#garg"
},
"devDependencies": {
"@babel/core": "^7.12.9",
"@babel/preset-react": "^7.12.7",
"parcel": "^1.12.4",
"psc-package": "^4.0.1",
"pulp": "^15.0.0",
"purescript": "^0.13.8",
"purescript-language-server": "^0.12.9",
"react-testing-library": "^6.1.2",
"sass": "^1.23.7",
"serve": "^11.3.1",
"spago": "^0.19.1",
"vscode-languageserver": "^6.0.0",
"xhr2": "^0.1.4"
}
}
let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.13.8-20210226/packages.dhall sha256:7e973070e323137f27e12af93bc2c2f600d53ce4ae73bb51f34eb7d7ce0a43ea
let overrides =
{ thermite =
{ dependencies =
[ "aff"
, "coroutines"
, "web-dom"
, "freet"
, "profunctor-lenses"
, "react"
, "react-dom"
]
, repo = "https://github.com/poorscript/purescript-thermite.git"
, version = "hide-2020-03-04"
}
, globals =
{ dependencies = [ "functions", "maybe" ]
, repo = "https://github.com/purescript/purescript-globals"
, version = "v4.1.0"
}
}
let additions =
{ sequences =
{ dependencies =
[ "prelude"
, "unsafe-coerce"
, "partial"
, "unfoldable"
, "lazy"
, "arrays"
, "profunctor"
, "maybe"
, "tuples"
, "newtype"
]
, repo = "https://github.com/hdgarrood/purescript-sequences.git"
, version = "v2.1.0"
}
, spec-discovery =
{ dependencies = [ "prelude", "effect", "arrays", "spec", "node-fs" ]
, repo = "https://github.com/purescript-spec/purescript-spec-discovery"
, version = "v4.0.0"
}
, spec-quickcheck =
{ dependencies = [ "prelude", "aff", "random", "quickcheck", "spec" ]
, repo = "https://github.com/purescript-spec/purescript-spec-quickcheck"
, version = "v3.1.0"
}
, ffi-simple =
{ dependencies =
[ "prelude"
, "effect"
, "maybe"
, "functions"
, "nullable"
, "unsafe-coerce"
]
, repo = "https://github.com/irresponsible/purescript-ffi-simple"
, version = "v0.2.10"
}
, dom-simple =
{ dependencies =
[ "arrays"
, "console"
, "effect"
, "ffi-simple"
, "functions"
, "nullable"
, "prelude"
, "unsafe-coerce"
]
, repo = "https://github.com/irresponsible/purescript-dom-simple"
, version = "v0.2.7"
}
, dom-filereader =
{ dependencies = [ "aff", "arraybuffer-types", "web-file", "web-html" ]
, repo = "https://github.com/nwolverson/purescript-dom-filereader"
, version = "v5.0.0"
}
, formula =
{ dependencies =
[ "effect"
, "prelude"
, "reactix"
, "record"
, "toestand"
, "tuples"
, "typelevel-prelude"
, "typisch"
]
, repo = "https://github.com/poorscript/purescript-formula"
, version = "v0.2.1"
}
, markdown =
{ dependencies = [ "precise" ]
, repo = "https://github.com/poorscript/purescript-markdown"
, version = "2020-03-04"
}
, markdown-smolder =
{ dependencies = [ "markdown", "smolder" ]
, repo = "https://github.com/poorscript/purescript-markdown-smolder"
, version = "2020-03-04"
}
, precise =
{ dependencies = [ "prelude" ]
, repo = "https://github.com/purescript-contrib/purescript-precise"
, version = "v4.0.0"
}
, reactix =
{ dependencies =
[ "aff"
, "dom-simple"
, "effect"
, "ffi-simple"
, "functions"
, "nullable"
, "prelude"
, "unsafe-coerce"
]
, repo = "https://github.com/irresponsible/purescript-reactix"
, version = "v0.4.11"
}
, toestand =
{ dependencies =
[ "effect"
, "reactix"
, "prelude"
, "record"
, "tuples"
, "typelevel-prelude"
, "typisch"
]
, repo = "https://github.com/poorscript/purescript-toestand"
, version = "v0.6.1"
}
, typisch =
{ dependencies = [ "prelude" ]
, repo = "https://github.com/poorscript/purescript-typisch"
, version = "v0.2.1"
}
, tuples-native =
{ dependencies =
[ "generics-rep", "prelude", "typelevel", "unsafe-coerce" ]
, repo = "https://github.com/athanclark/purescript-tuples-native"
, version = "v2.0.1"
}
, uint =
{ dependencies = [ "maybe", "math", "generics-rep" ]
, repo = "https://github.com/zaquest/purescript-uint"
, version = "v5.1.1"
}
, uri =
{ dependencies =
[ "these"
, "arrays"
, "profunctor-lenses"
, "unfoldable"
, "parsing"
, "integers"
, "globals"
, "generics-rep"
]
, repo = "https://github.com/slamdata/purescript-uri"
, version = "v7.0.0"
}
, read =
{ dependencies = [ "prelude", "maybe", "strings" ]
, repo = "https://github.com/truqu/purescript-read"
, version = "v1.0.1"
}
, versions =
{ dependencies = [ "prelude" ]
, repo = "https://github.com/hdgarrood/purescript-versions.git"
, version = "v5.0.1"
}
, simplecrypto =
{ dependencies = [ "prelude", "maybe", "node-buffer" ]
, repo = "https://github.com/alpacaaa/purescript-simplecrypto"
, version = "v1.0.1"
}
}
in upstream // overrides // additions
{
"name": "untitled",
"set": "psc-0.13.8",
"source": "https://github.com/purescript/package-sets.git",
"depends": [
"prelude"
]
}
{-
Welcome to a Spago project!
You can edit this file as you like.
Need help? See the following resources:
- Spago documentation: https://github.com/purescript/spago
- Dhall language tour: https://docs.dhall-lang.org/tutorials/Language-Tour.html
When creating a new Spago project, you can use
`spago init --no-comments` or `spago init -C`
to generate this file without the comments in this block.
-}
{ name = "untitled"
, dependencies =
[ "aff-promise"
, "affjax"
, "argonaut"
, "console"
, "css"
, "datetime"
, "debug"
, "dom-filereader"
, "dom-simple"
, "easy-ffi"
, "effect"
, "foreign-generic"
, "foreign-object"
, "formula"
, "generics-rep"
, "globals"
, "integers"
, "js-timers"
, "markdown-smolder"
, "math"
, "maybe"
, "milkis"
, "nonempty"
, "now"
, "numbers"
, "prelude"
, "psci-support"
, "random"
, "react"
, "reactix"
, "read"
, "record-extra"
, "routing"
, "sequences"
, "simplecrypto"
, "smolder"
, "spec-discovery"
, "spec-quickcheck"
, "string-parsers"
, "strings"
, "stringutils"
, "toestand"
, "tuples-native"
, "typisch"
, "uint"
, "uri"
, "versions"
, "web-html"
]
, packages = ./packages.dhall
, sources = [ "src/**/*.purs", "test/**/*.purs" ]
}
module Test.Main where
import Prelude
import Effect (Effect)
import Effect.Class.Console (log)
main :: Effect Unit
main = do
log "🍝"
log "You should add some tests."
This source diff could not be displayed because it is too large. You can view the blob instead.
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment