{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

{-|
Module      : Graphics.Vega.VegaLite.Output
Copyright   : (c) Douglas Burke, 2018-2019
License     : BSD3

Maintainer  : dburke.gw@gmail.com
Stability   : unstable
Portability : CPP, OverloadedStrings

Write out the VegaLite specification.

-}

module Graphics.Vega.VegaLite.Output
       ( toHtml
       , toHtmlFile
       , toHtmlWith
       , toHtmlFileWith
       ) where

import qualified Data.Aeson.Text as A
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.IO as TL

import Data.Aeson (Value)

#if !(MIN_VERSION_base(4, 12, 0))
import Data.Monoid ((<>))
#endif

import Graphics.Vega.VegaLite.Specification (VegaLite, fromVL)


{-|

Converts VegaLite to html Text. Uses Vega-Embed with the
default options. See 'toHtmlWith' for more control.

@since 0.2.1.0
-}
toHtml :: VegaLite -> TL.Text
toHtml :: VegaLite -> Text
toHtml = Maybe Value -> VegaLite -> Text
toHtmlWith Maybe Value
forall a. Maybe a
Nothing

{-|

Converts VegaLite to an html file. Uses Vega-Embed with the
default options. See 'toHtmlFileWith' for more control.

@since 0.2.1.0
-}
toHtmlFile :: FilePath -> VegaLite -> IO ()
toHtmlFile :: FilePath -> VegaLite -> IO ()
toHtmlFile FilePath
file = FilePath -> Text -> IO ()
TL.writeFile FilePath
file (Text -> IO ()) -> (VegaLite -> Text) -> VegaLite -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VegaLite -> Text
toHtml

{-|

Converts VegaLite to html Text. Uses Vega-Embed and is for when
some control is needed over the output: 'toHtml' is a simpler
form which just uses the default Vega-Embed options.

The render you use to view the output file must support Javascript,
since it is needed to create the visualization from the Vega-Lite
specification. The Vega and Vega-Lite Javascript versions are pegged
to 5 and 4, but no limit is applied to the Vega-Embed library.

@since 0.4.0.0
-}
toHtmlWith ::
  Maybe Value
  -- ^ The options to pass to the Vega-Embed @embed@ routine. See
  --   <https://github.com/vega/vega-embed#options> for the
  --   supported options.
  -> VegaLite
  -- ^ The Vega-Lite specification to display.
  -> TL.Text
toHtmlWith :: Maybe Value -> VegaLite -> Text
toHtmlWith Maybe Value
mopts VegaLite
vl =
  let spec :: Text
spec = Value -> Text
forall a. ToJSON a => a -> Text
A.encodeToLazyText (VegaLite -> Value
fromVL VegaLite
vl)
      opts :: Text
opts = Text -> (Value -> Text) -> Maybe Value -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (\Value
o -> Text
"," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Value -> Text
forall a. ToJSON a => a -> Text
A.encodeToLazyText Value
o) Maybe Value
mopts

  in [Text] -> Text
TL.unlines
    [ Text
"<!DOCTYPE html>"
    , Text
"<html>"
    , Text
"<head>"
      -- versions are fixed at vega 5, vega-lite 4
    , Text
"  <script src=\"https://cdn.jsdelivr.net/npm/vega@5\"></script>"
    , Text
"  <script src=\"https://cdn.jsdelivr.net/npm/vega-lite@4\"></script>"
    , Text
"  <script src=\"https://cdn.jsdelivr.net/npm/vega-embed\"></script>"
    , Text
"</head>"
    , Text
"<body>"
    , Text
"<div id=\"vis\"></div>"
    , Text
"<script type=\"text/javascript\">"
    , Text
"  var spec = " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
spec Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";"
    , Text
"  vegaEmbed(\'#vis\', spec" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
opts Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
").then(function(result) {"
    , Text
"  // Access the Vega view instance (https://vega.github.io/vega/docs/api/view/) as result.view"
    , Text
"  }).catch(console.error);"
    , Text
"</script>"
    , Text
"</body>"
    , Text
"</html>"
    ]

{-|

Converts VegaLite to an html file. Uses Vega-Embed and is for when
some control is needed over the output: 'toHtmlFile' is a simpler
form which just uses the default Vega-Embed options.

@since 0.4.0.0
-}
toHtmlFileWith ::
  Maybe Value
  -- ^ The options to pass to the Vega-Embed @embed@ routine. See
  --   <https://github.com/vega/vega-embed#options> for the
  --   supported options.
  -> FilePath
  -- ^ The output file name (it will be over-written if it already exists).
  -> VegaLite
  -- ^ The Vega-Lite specification to display.
  -> IO ()
toHtmlFileWith :: Maybe Value -> FilePath -> VegaLite -> IO ()
toHtmlFileWith Maybe Value
mopts FilePath
file = FilePath -> Text -> IO ()
TL.writeFile FilePath
file (Text -> IO ()) -> (VegaLite -> Text) -> VegaLite -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Value -> VegaLite -> Text
toHtmlWith Maybe Value
mopts