[Haskell-cafe] Best way to use the google visualization (javascript) API rather than static image charts (hs-gchart)?
Ryan Newton
rrnewton at gmail.com
Mon Mar 19 01:09:44 CET 2012
Thanks David,
As an update, HJScript is a bit of a nightmare to figure out (missing
documentation, examples). And the model of JS values:
http://hackage.haskell.org/packages/archive/language-javascript/0.4.10/doc/html/Language-JavaScript-Parser.html#t:Node
Seems less human comprehensible than, for example, WebBits':
http://hackage.haskell.org/packages/archive/WebBits/2.0/doc/html/BrownPLT-JavaScript-Syntax.html
However, jmacro is a breeze for spitting out JS code. The little script
below will make a simple line plot with google charts.
I'll give flot a try latter. Zooming / panning sounds nice.
Cheers,
-Ryan
Aforementioned script:
-------------------------------------------------------------------------------
{-# LANGUAGE QuasiQuotes #-}
import Language.Javascript.JMacro
hdr :: String
hdr = "<html> <head> <script type=\"text/javascript\" src=\"
https://www.google.com/jsapi\"></script> <script type=\"text/javascript\">"
ftr :: String
ftr = " </script> </head> <body> <div id=\"chart_div\" style=\"width:
900px; height: 500px;\"></div> </body> </html>"
testdata :: [(String, Int, Int)]
testdata = [
("2004", 100, 400),
("2005", 1170, 460),
("2006", 860, 580),
("2007", 1030, 540)
]
-- | This provides a set of basic functional programming primitives, a few
utility functions
-- and, more importantly, a decent sample of idiomatic jmacro code. View
the source for details.
-- body :: JStat
body :: (ToJExpr a3, ToJExpr a2, ToJExpr a1, ToJExpr a) => (a, a1, a2) ->
a3 -> JStat
body (title,line1,line2) testdata = [$jmacro|
google.load("visualization", "1", {packages:["corechart"]});
fun drawChart {
var dat = new google.visualization.DataTable();
dat.addColumn('string', `(title)` );
dat.addColumn('number', `(line1)` );
dat.addColumn('number', `(line2)` );
// -- Here's our data... this can get BIG:
dat.addRows( `(testdata)` );
var options = { title: `(title)` };
var chart = new
google.visualization.LineChart(document.getElementById('chart_div'));
chart.draw(dat, options);
}
google.setOnLoadCallback(drawChart);
|]
main = do
putStrLn hdr
print$ renderJs$ body ("blah","line1","line2") testdata
putStrLn ftr
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120318/c85fe693/attachment.htm>
More information about the Haskell-Cafe
mailing list