-- GoogleChart -- a Haskell module for using Google's Chart API
-- Copyright (c) 2008 Evan Martin <martine@danga.com>

{-| This module is for generating web-based charts using Google's Chart API:
<http://code.google.com/apis/chart/>.  Its output is URLs that will resolve
to a PNG image of the resulting chart.

Most of the functions in this module, with names like @setFoo@, take a 'Chart'
as an argument and produce a new 'Chart' with the specified attribute added.
These calls are designed to be chained together.  See the example below.

'Chart's are represented as a hierarchy of type classes so that parameters
that only affect a specific chart type are only available to that chart type.

@
putStrLn \"URL for your chart:\"
putStrLn $ 'chartURL' $
  'setSize' 400 257 $
  'setTitle' \"My Chart\" $
  'setData' ('encodeDataSimple' [[1..20]]) $
  'setLegend' [\"1 to 20\"] $
  'newLineChart'
@

This produces:
<http://chart.apis.google.com/chart?chs=400x257&chtt=My+Chart&chd=s%3aBCDEFGHIJKLMNOPQRSTU&chdl=1+to+20&cht=lc>

-}

module Graphics.Google.Chart (
  -- * Chart basics
  -- | These functions and types are shared by all chart types.
  Chart,
  chartURL,
  setSize, setTitle, setTitleOpts, setData,
  -- ** Chart data
  -- | There are multiple options for encoding chart data.  See
  -- <http://code.google.com/apis/chart/#chart_data> for more details.
  ChartData, encodeDataSimple, encodeDataText, encodeDataExtended,

  -- * Chart features
  LegendChart, setLegend,

  -- * Specific chart types
  -- ** Line charts
  LineChart, newLineChart,

  -- ** Pie charts
  PieChart, newPieChart, PieStyle(..), setLabels,

  -- ** Bar charts
  BarChart, newBarChart, Orientation(..), BarStyle(..)
) where

import Data.Char (chr, ord)
import Data.List (intercalate)
import Numeric (showHex)

-- | Bar

urlEnc str = concatMap enc str where
  enc c | c >= 'A' && c <= 'Z' || c >= 'a' && c <= 'z' = [c]
        | c >= '0' && c <= '9'                         = [c]
        | c == '-' || c == '_' || c == '.' || c == '~' = [c]
        | c == ' '                                     = "+"
        | otherwise  = '%':(showHex (ord c) "")

-- All charts are internally represented as a list of (key,value) pairs.
-- We could switch this to Data.Map if it matters.
type Params = [(String,String)]

-- |The type class underneath all Charts.
class Chart c where
  params :: c -> Params
  fromParams :: Params -> c

setParam :: (Chart c) => String -> String -> c -> c
setParam key val c = fromParams $ (key,val) : filter ((/= key) . fst) (params c)

-- |Set the width and height, in pixels, of the resulting image.
setSize :: (Chart c) => Int -> Int -> c -> c
setSize width height = setParam "chs" (show width ++ "x" ++ show height)

-- |Set the title of the chart.
setTitle :: (Chart c) => String -> c -> c
setTitle title = setParam "chtt" title

-- |Set options for the display of the title of the chart.
setTitleOpts :: (Chart c) => String -- ^Color of the text.
                          -> Int -- ^Size of the text.
                          -> c -> c
setTitleOpts color size = setParam "chts" (color ++ "," ++ show size)

-- |Set the data displayed by the chart.
setData :: (Chart c) => ChartData -> c -> c
setData (ChartData str) = setParam "chd" str

-- |Construct the URL used to show the chart.
chartURL :: (Chart c) => c -> String
chartURL chart = baseURL ++ intercalate "&" urlparams where
  baseURL = "http://chart.apis.google.com/chart?"
  urlparams = [urlEnc a ++ "=" ++ urlEnc b | (a,b) <- params chart]

-- |All the encoding methods produce 'ChartData', which is usable by 'setData'.
newtype ChartData = ChartData String deriving Show

-- |Encode data using the \"simple\" encoding.  This produces minimal URLs but
-- doesn't have as much resolution.  Input values must be in the range @0 <= x
-- <= 61@.  Values outside the valid input range will be considered missing
-- data.
encodeDataSimple :: [[Int]] -> ChartData
encodeDataSimple datas =
  ChartData $ "s:" ++ intercalate "," (map (map enc) datas) where
  enc i | i >= 0  && i <= 25 = chr (ord 'A' + i)
        | i >= 26 && i <= 51 = chr (ord 'a' + (i - 26))
        | i >= 52 && i <= 61 = chr (ord '0' + (i - 52))
        | otherwise          = '_'

-- |Encode data using the \"text\" encoding.  XXX unimplemented.
encodeDataText :: [[Int]] -> ChartData
encodeDataText = undefined

-- |Encode data using the \"extended\" encoding.  XXX unimplemented.
encodeDataExtended :: [[Int]] -> ChartData
encodeDataExtended = undefined

-- |LegendChart represents charts that can display legends with 'setLegend'.
class Chart c => LegendChart c where
  -- |Set the legend for the corresponding data sets.  The colors are taken
  -- from the data set colors.
  setLegend :: [String] -> c -> c
  setLegend strs = setParam "chdl" (intercalate "|" strs)

newtype LineChart = LineChart Params
instance Chart LineChart where
  params (LineChart p) = p
  fromParams = LineChart
instance LegendChart LineChart

newLineChart :: LineChart
newLineChart = fromParams [("cht","lc")]

newtype PieChart = PieChart Params
instance Chart PieChart where
  params (PieChart p) = p
  fromParams = PieChart
data PieStyle = Pie2D | Pie3D
newPieChart :: PieStyle -> PieChart
newPieChart Pie2D = fromParams [("cht","p")]
newPieChart Pie3D = fromParams [("cht","p3")]

-- Specify missing values by passing an empty string.
setLabels :: [String] -> PieChart -> PieChart
setLabels labels = setParam "chl" $ intercalate "|" labels

newtype BarChart = BarChart Params
instance Chart BarChart where
  params (BarChart p) = p
  fromParams = BarChart
instance LegendChart BarChart
data Orientation = Horizontal | Vertical
data BarStyle = Stacked | Grouped
newBarChart :: Orientation -> BarStyle -> BarChart
newBarChart orient style =
  fromParams [("cht",'b':oLetter orient:sLetter style:[])] where
  oLetter Horizontal = 'h'
  oLetter Vertical   = 'v'
  sLetter Stacked = 's'
  sLetter Grouped = 'g'