archive567/chart-unit

Scaling cells in histograms

Closed this issue · 4 comments

I modified one of your examples to attempt to draw a cell at a time in an animation. But, see below, the cells get rescaled in each frame. You have to click on the image to get it to animate.

anim

{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NegativeLiterals  #-}
{-# LANGUAGE OverloadedStrings  #-}

module Main ( main ) where

import Chart
import NumHask.Prelude

import FakeData

import Data.List ((!!))

import Diagrams.Backend.Rasterific.CmdLine

import Diagrams.Backend.CmdLine

import Codec.Picture.Gif


histDefs :: [RectConfig]
histDefs =
    [ def
    , rectBorderColor .~ Color 0 0 0 0
      $ rectColor .~ Color 0.333 0.333 0.333 0.4
      $ def
    ]

exampleHist :: [[Rect Double]] -> Chart' a
exampleHist rs =
    histChart histDefs widescreen rs <>
    axes
    ( chartRange .~ Just (fold . fold $ rs)
    $ chartAspect .~ widescreen
    $ def)

chartRange' :: [[Rect Double]] -> Rect Double
chartRange' = fold . fold

exampleHist' :: Rect Double -> [[Rect Double]] -> Chart' a
exampleHist' cr rs =
    histChart histDefs widescreen rs <>
    axes
    ( chartRange .~ Just cr
    $ chartAspect .~ widescreen
    $ def)

main :: IO ()
main = do
  let sWide = (750,250)

  xs <- mkHistData
  let yss = inits (xs!!0)
  let cr = chartRange' yss
  let us :: [Diagram B ]
      us = map (exampleHist' cr) $ map return $ inits (xs!!0)

  displayHeader' "other/anim.gif" $ zip us (repeat (10 :: Int))
  fileCairo "other/exampleHist.png" sWide (exampleHist xs)

displayHeader :: FilePath -> Diagram B -> IO ()
displayHeader fn =
  mainRender ( DiagramOpts (Just 900) (Just 700) fn
             , DiagramLoopOpts False Nothing 0
             )

displayHeader' :: FilePath -> [(Diagram B, GifDelay)] -> IO ()
displayHeader' fn =
  mainRender ( DiagramOpts (Just 900) (Just 700) fn
             , GifOpts {_dither = False, _noLooping = False, _loopRepeat = Just 10}
             )

I seem to have created fileCairo but you don't need that. Here's a shorter version.

{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NegativeLiterals  #-}
{-# LANGUAGE OverloadedStrings  #-}

module Main ( main ) where

import Chart
import NumHask.Prelude

import FakeData

import Data.List ((!!))

import Diagrams.Backend.Rasterific.CmdLine

import Diagrams.Backend.CmdLine

import Codec.Picture.Gif


histDefs :: [RectConfig]
histDefs =
    [ def
    , rectBorderColor .~ Color 0 0 0 0
      $ rectColor .~ Color 0.333 0.333 0.333 0.4
      $ def
    ]

chartRange' :: [[Rect Double]] -> Rect Double
chartRange' = fold . fold

exampleHist :: Rect Double -> [[Rect Double]] -> Chart' a
exampleHist cr rs =
    histChart histDefs widescreen rs <>
    axes
    ( chartRange .~ Just cr
    $ chartAspect .~ widescreen
    $ def)

main :: IO ()
main = do
  xs <- mkHistData
  let yss = inits (xs!!0)
  let cr = chartRange' yss
  let us :: [Diagram B ]
      us = map (exampleHist cr) $ map return $ inits (xs!!0)

  displayHeader "other/anim.gif" $ zip us (repeat (10 :: Int))

displayHeader :: FilePath -> [(Diagram B, GifDelay)] -> IO ()
displayHeader fn =
  mainRender ( DiagramOpts (Just 900) (Just 700) fn
             , GifOpts {_dither = False, _noLooping = False, _loopRepeat = Just 10}
             )

Try this:

exampleHist :: Rect Double -> [[Rect Double]] -> Chart' a
exampleHist cr rs =
    (mconcat . zipWith rect1 histDefs $ (fmap (projectRect cr (unAspect widescreen)) <$> rs)) <>
    axes
    ( chartRange .~ Just cr
    $ chartAspect .~ widescreen
    $ def)

The default charts are self-scaling to their own range. I'll tweak the API to include scaling to a concrete range. histChartWithRange etc maybe.

Do you mind if I include the animation as another example?

Thanks for this. Please do use the example.