Skip to content

Instantly share code, notes, and snippets.

@snoyberg
Created October 3, 2012 22:02
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save snoyberg/3830169 to your computer and use it in GitHub Desktop.
Save snoyberg/3830169 to your computer and use it in GitHub Desktop.
Create a reusable widget for jqplot
{-# LANGUAGE OverloadedStrings, MultiParamTypeClasses, TemplateHaskell, QuasiQuotes, TypeFamilies #-}
import Yesod
import Jqplot
-- Let's kick off a basic Yesod app with three routes: a homepage and two
-- charts.
data App = App
mkYesod "App" [parseRoutes|
/ HomeR GET
/chart1 Chart1R GET
/chart2 Chart2R GET
|]
-- Next we create typeclass instances. We can use the default methods for
-- YesodJquery and YesodJqplot and take advantage of the built-in CDNs, or
-- could override and use a local copy instead. For simplicity, we choose the
-- former.
instance Yesod App
instance YesodJquery App
instance YesodJqplot App
-- Basic handler, nothing special.
getHomeR :: Handler RepHtml
getHomeR = defaultLayout $ do
setTitle "Homepage"
[whamlet|
<p>Demonstration of a reusable widget.
<p>
<a href=@{Chart1R}>First chart
|
<a href=@{Chart2R}>Second chart
|]
-- | In this chart, we create a graph of the x^2 function, without writing a
-- single line of HTML, CSS, or Javascript. In theory, as more widgets become
-- available in the Yesod ecosystem, this type of development could become more
-- standard. But for now, the following example is more normative.
getChart1R :: Handler RepHtml
getChart1R = defaultLayout $ do
setTitle "Graph of x\xb2"
plot PlotSettings
{ psXLabel = "x"
, psYLabel = "x\xb2"
, psData = map (\x -> (x, x * x)) $ [0, 0.1..10]
}
-- | Very often, you'll want to take some precomposed widget and embed it
-- inside some other HTML. That's entirely possible with widget interpolation.
getChart2R :: Handler RepHtml
getChart2R = defaultLayout $ do
setTitle "Made up data"
toWidget [lucius|
.chart {
width: 500px;
height: 300px;
}
|]
[whamlet|
<p>You can just as easily embed a reusable widget inside other source.
<div .chart>^{madeUpData}
<p>And it just works.
|]
where
-- Yup, totally bogus data...
madeUpData = plot PlotSettings
{ psXLabel = "Month"
, psYLabel = "Hackage uploads"
, psData =
[ (1, 100)
, (2, 105)
, (3, 115)
, (4, 137)
, (5, 168)
, (6, 188)
, (7, 204)
, (8, 252)
, (9, 256)
, (10, 236)
, (11, 202)
, (12, 208)
]
}
-- And now we just run our app!
main :: IO ()
main = warpDebug 3000 App
<div ##{divId}>
{-# LANGUAGE OverloadedStrings, TemplateHaskell, RecordWildCards #-}
-- | We're going to provide a module that provides a pure-Haskell interface to
-- the jqplot library. To use it, you don't need to write any HTML, CSS, or
-- Javascript in your code, as we'll see in our example app.
--
-- The idea is that all of the low-level Javascript code goes in this module,
-- and apps just deal with the widget.
--
-- Note that, for simplicity, we're only implementing a tiny subset of jqPlot's
-- full functionality. A more full-fledged wrapper could be written, but would
-- obviously be more involved.
module Jqplot
( YesodJqplot (..)
, YesodJquery (..)
, PlotSettings (..)
, plot
) where
import Yesod
import Yesod.Form.Jquery (YesodJquery (..))
import Data.Monoid ((<>))
import Data.Text.Lazy.Builder (toLazyText)
import Data.Aeson.Encode (fromValue)
import Data.Aeson (ToJSON (toJSON))
import Data.Text (Text)
import qualified Data.Text.Lazy
import Text.Julius (juliusFile)
-- | This is just a minor utility function which renders values to JSON text.
-- jqPlot, like many Javascript libraries, allows its functions to take
-- arguments as JSON data. This function could in theory be provided by aeson.
encodeText :: ToJSON a => a -> Data.Text.Lazy.Text
encodeText = toLazyText . fromValue . toJSON
-- | We need to be able to find the jqPlot Javascript files. By putting the
-- location in a typeclass, users are able to provide whichever location they
-- want (e.g., on a local webserver) or use the default value, which in this
-- case uses the jsdelivr CDN.
--
-- Note that the YesodJquery typeclass, provided by the yesod-form package, works the same way.
class YesodJqplot master where
jqplotRoot :: master -> Text
jqplotRoot _ = "http://cdn.jsdelivr.net/jqplot/1.0.4/"
-- | Now we begin our Haskell API. For a plot, we'll have three settings: the
-- label for the X and Y axes, and the datapoints to be plotted.
data PlotSettings = PlotSettings
{ psXLabel :: Text
, psYLabel :: Text
, psData :: [(Double, Double)]
}
-- | This function is the meat of our module. It takes the PlotSettings and
-- turns it into a Widget. Note the type signature here: we're using GWidget
-- with arbitrary subsite and master site, so that this widget will work with
-- many different applications. However, since we need to know the location of
-- the jQuery and jqPlot libraries, we have the relevant typeclasses in the
-- context.
plot :: (YesodJquery master, YesodJqplot master) => PlotSettings -> GWidget sub master ()
plot PlotSettings {..} = do
-- Grab the master site...
master <- lift getYesod
let root = jqplotRoot master
-- So that we can add dependencies to the widget. Note that the calling app
-- will automatically inherit these dependencies, and can remain completely
-- ignorant of what's going on inside this function. Yesod will also ensure
-- that each file is only included in the page once.
addScriptEither $ urlJqueryJs master
addScriptRemote $ root <> "jquery.jqplot.min.js"
addScriptRemote $ root <> "plugins/jqplot.canvasTextRenderer.min.js"
addScriptRemote $ root <> "plugins/jqplot.canvasAxisLabelRenderer.min.js"
addStylesheetRemote $ root <> "jquery.jqplot.min.css"
-- We need to give a unique ID to a div tag where the chart will be placed.
-- We ask Yesod to provide a unique identifier and then both the Julius and
-- Hamlet templates are able to use it. This avoids two problems: typos
-- between the two files, and name collisions when using the same widget
-- twice in a page.
divId <- lift newIdent
-- And as a standard best practice, we've placed the Julius and Hamlet in
-- separate files.
toWidget $(juliusFile "jqplot.julius")
$(whamletFile "jqplot.hamlet")
$(function(){
$.jqplot('#{divId}', [#{encodeText psData}], {
series:[{showMarker:false}],
axes:{
xaxis:{
label:#{encodeText psXLabel}
},
yaxis:{
label:#{encodeText psYLabel},
labelRenderer: $.jqplot.CanvasAxisLabelRenderer
}
}
});
});
@sanketr
Copy link

sanketr commented Nov 29, 2012

On ghc 7.6.1 (Linux), Jqplot.hs throws type error - since I am not very familiar with Yesod layout (yet), I am stumped how to fix this error:

Jqplot.hs:86:16:
Could not deduce (Text.Julius.ToJavascript Data.Text.Lazy.Text)
  arising from a use of `Text.Julius.toJavascript'
from the context (YesodJquery master, YesodJqplot master)
  bound by the type signature for
             plot :: (YesodJquery master, YesodJqplot master) =>
                     PlotSettings -> GWidget sub master ()
  at Jqplot.hs:61:9-89
Possible fix:
  add an instance declaration for
  (Text.Julius.ToJavascript Data.Text.Lazy.Text)
In the first argument of `Text.Julius.Javascript', namely
  `Text.Julius.toJavascript (encodeText psData)'
In the expression:
  Text.Julius.Javascript
    (Text.Julius.toJavascript (encodeText psData))
In the first argument of `Data.Monoid.mconcat', namely
  `[Text.Julius.Javascript
      ((Data.Text.Lazy.Builder.fromText . Text.Shakespeare.pack')
         "$(function(){\
         \  $.jqplot('"),
    Text.Julius.Javascript (Text.Julius.toJavascript divId),
    Text.Julius.Javascript
      ((Data.Text.Lazy.Builder.fromText . Text.Shakespeare.pack')
         "', ["),
    Text.Julius.Javascript
      (Text.Julius.toJavascript (encodeText psData)),
    ....]'
Failed, modules loaded: none.

@JAnthelme
Copy link

Hi,
I am new to Yesod and need a bit of hand holding : I cannot compile Jqplot.hs. Seems like it's coming from GWidget :
"
Not in scope: type constructor or class GWidget' Perhaps you meant one of these: WidgetT' (imported from Yesod), `ToWidget' (imported from Yesod)
Failed, modules loaded: none.
"
I am on yesod-platform-1.2.2 package
Thanks. ja.

@smoothdeveloper
Copy link

I changed the type signature to

plot :: (YesodJquery master, YesodJqplot master) => PlotSettings -> WidgetT master m ()

but I get this error

Could not deduce (master ~ HandlerSite m)
from the context (YesodJquery master, YesodJqplot master)
  bound by the type signature for
             plot :: (YesodJquery master, YesodJqplot master) =>
                     PlotSettings -> WidgetT master m ()
  at Jqplot.hs:61:9-87
  `master' is a rigid type variable bound by
           the type signature for
             plot :: (YesodJquery master, YesodJqplot master) =>
                     PlotSettings -> WidgetT master m ()
           at Jqplot.hs:61:9
Expected type: m master
  Actual type: m (HandlerSite m)
In the first argument of `lift', namely `getYesod'
In a stmt of a 'do' block: master <- lift getYesod
In the expression:
  do { master <- lift getYesod;
       let root = jqplotRoot master;
       addScriptEither $ urlJqueryJs master;
       addScriptRemote $ root <> "jquery.jqplot.min.js";
       .... }

I get similar issue when trying to roll my own widget (https://bitbucket.org/gauthier/yesod-widgets)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment