Multiple plots with Rlang-QQ

An example of Rlang-QQ-0.1.1, which supports multiple figures.

First a pile of imports needed:

In [1]:
:set -XQuasiQuotes -XTupleSections
import RlangQQ
import System.Directory
import System.FilePath
import Data.Maybe
import Data.List
import Text.Read
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as Char
import qualified Data.ByteString.Base64 as Base64
import IHaskell.Display
import IHaskell.Display.Blaze () -- to confirm it's installed
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as H
import Data.Monoid
import Data.Char
import Control.Monad
import Data.Ord
import Data.List.Split
import Text.XFormat.Show hiding ((<>))

Rlang-QQ saves intermediate files into Rtmp/. Figures from the first [r| quasi quote |] go into Rtmp/fig1. Figures from the next one go into Rtmp/fig2.

So, taking a look at the filesystem from the notebook allows finding out which plots should be loaded.

In [2]:
chunksWithPlots :: IO [Int]
chunksWithPlots = do
  fs <- mapMaybe (readMaybe <=< stripPrefix "fig" . takeBaseName)
    <$> getDirectoryContents "Rtmp"
  fs' <- forM fs $ \f-> fmap (,f) (getModificationTime ("Rtmp/fig"++show f))
  return $ map snd $ sortBy (flip (comparing fst)) fs'


getPlotNames :: IO [String]
getPlotNames = do
  ns <- chunksWithPlots
  case ns of
    [] -> return []
    n : _ -> 
            map (\t -> "Rtmp/fig"++show n </> t) . filter (`notElem` ["..","."])
            <$> getDirectoryContents (showf ("Rtmp/fig"%Int) n)
            
getCaptions :: IO [String]
getCaptions = do
  n : _ <- chunksWithPlots

  f <- readFile (showf ("Rtmp/raw"%Int%".md") n)
  let end s = case splitOn "](" s of
              a:_ -> Just a
              _ -> Nothing
      isBoring s = maybe False (all isDigit)
                  (stripPrefix "plot of chunk unnamed-chunk-" s)
  return $ 
      map (\x -> if isBoring x then "" else x) $
      mapMaybe (end <=< stripPrefix "![") (lines f)

rPlots :: IO [DisplayData]
rPlots = do
 ns <- getPlotNames
 cs <- getCaptions
 imgs <- forM (ns `zip` cs) $ \(n,c) -> do
   e <- Base64.encode <$> B.readFile n
   return $ H.img H.! H.src (H.unsafeByteStringValue
                                   (Char.pack "data:image/png;base64," <> e))
            <> if null c then mempty
                else H.p (H.toMarkup c)
 display (mconcat imgs)
In [3]:
[r| plot(1:10)
    plot(sin(1:10), type='l') |]
getPlotNames
rPlots
["Rtmp/fig1/unnamed-chunk-11.png","Rtmp/fig1/unnamed-chunk-12.png"]

The obligatory Fibonacci

In [4]:
fibs = 0:1: zipWith (+) fibs (drop 1 fibs)

[r| plot(1:20, $(take 20 $ map fromIntegral fibs :: [Double]),
         main='rabbit population',
         ylab='', xlab='') |]
rPlots
In [5]: