rigel-viz-0.2.0.0: A mid-level wrapper for vega-lite

Copyright(c) Marco Zocca 2019
LicenseBSD3
Maintainerocramz fripost org
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

RigelViz

Contents

Description

A (mid-level, simplified, opinionated) Haskell wrapper for vega-lite, currently targeting version 3 of the vega-lite schema.

Aims / definitions

  • mid-level :

    • types which can take one of a few possible values are represented by sum types, not by strings.
    • glyph colours are encoded via the colour Haskell library.
  • simplified : the generated vega-lite JSON is not normalized, i.e. has some redundancies. This reflects the internal representation but also makes it easier to reason "locally" (i.e. code sections don't visibly exploit inheritance from higher layers).
  • opinionated : part of the vega-lite API is not used at all. For example, there is no support for data preprocessing (e.g. summarization etc.). This forces the user to use the host language for preprocessing, which is bound to be more expressive and robust.

Examples

These examples require lucid and lucid-extras (> 0.2.2): lucid provides renderToFile and lucid-extras provides mkVegaHtml.

Scatter plot

render0 :: IO ()
render0 = renderToFile "scatter.html" $ mkVegaHtml $ toJSON vls0

vls0 :: VLSpec TestValue
vls0 =
  vegaLiteSpec 400 300 [
    layer MCircle (DataJSON testVs) (
       posEnc X "tv" Nominal <>
       posEnc Y "tvb" Quantitative <>
       colourEnc "tvb" Quantitative <>
       sizeEnc "tvb" Quantitative
       )
    ]

data TestValue = TV { tv :: T, tvb :: Double } deriving (Eq, Show, Generic)
instance A.ToJSON TestValue
data T = A | B | C deriving (Eq, Show, Generic)
instance A.ToJSON T

testVs :: [TestValue]
testVs = [TV A 3.2, TV B 5.4, TV A 2.2, TV A 6.7, TV B 4.9]

Heatmap

render0 :: IO ()
render0 = renderToFile "heatmap.html" $ mkVegaHtml $ toJSON vls1

vls1 :: VLSpec (V3 Double)
vls1 = vegaLiteSpec 400 400 [
  layer MRect (DataJSON dats) $
      posEnc X "v3x" Ordinal <>
      posEnc Y "v3y" Ordinal  <>
      colourEnc "v3z" Quantitative <>
      sizeEnc "v3z" Quantitative

data V3 a = V3 { v3x :: a, v3y :: a, v3z :: a } deriving (Eq, Show, Generic)
instance A.ToJSON a => A.ToJSON (V3 a)

dats :: [V3 Double]
dats = [V3 x y (f x y) | x <- xs, y <- ys] where
  xs = map (/10) [0, 1 .. 20]
  ys = xs
  f x y = sin $ 2 * pi * sqrt (x ** 2 + y ** 2)
Synopsis

Documentation

vegaLiteSpec Source #

Arguments

:: Int

Plot width

-> Int

Plot height

-> [LayerMetadata a] 
-> VLSpec a 

Create a vega-lite spec

data VLSpec a Source #

Specification of a vega-lite plot

A VLSpec can be encoded into a JSON blob via its ToJSON instance.

Instances
Eq a => Eq (VLSpec a) Source # 
Instance details

Defined in RigelViz

Methods

(==) :: VLSpec a -> VLSpec a -> Bool #

(/=) :: VLSpec a -> VLSpec a -> Bool #

Show a => Show (VLSpec a) Source # 
Instance details

Defined in RigelViz

Methods

showsPrec :: Int -> VLSpec a -> ShowS #

show :: VLSpec a -> String #

showList :: [VLSpec a] -> ShowS #

Generic (VLSpec a) Source # 
Instance details

Defined in RigelViz

Associated Types

type Rep (VLSpec a) :: Type -> Type #

Methods

from :: VLSpec a -> Rep (VLSpec a) x #

to :: Rep (VLSpec a) x -> VLSpec a #

ToJSON a => ToJSON (VLSpec a) Source # 
Instance details

Defined in RigelViz

type Rep (VLSpec a) Source # 
Instance details

Defined in RigelViz

type Rep (VLSpec a) = D1 (MetaData "VLSpec" "RigelViz" "rigel-viz-0.2.0.0-1vfhSp89GHB1TbuLgcwhbH" False) (C1 (MetaCons "VLSpec" PrefixI True) (S1 (MetaSel (Just "vlsWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Just "vlsHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "vlsView") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [LayerMetadata a]))))

Data sources

data DataSource a Source #

Data source

Constructors

DataJSON [a]

Data row type must have a ToJSON instance

DataURI String

URI or filepath of dataset

Instances
Eq a => Eq (DataSource a) Source # 
Instance details

Defined in RigelViz

Methods

(==) :: DataSource a -> DataSource a -> Bool #

(/=) :: DataSource a -> DataSource a -> Bool #

Show a => Show (DataSource a) Source # 
Instance details

Defined in RigelViz

Generic (DataSource a) Source # 
Instance details

Defined in RigelViz

Associated Types

type Rep (DataSource a) :: Type -> Type #

Methods

from :: DataSource a -> Rep (DataSource a) x #

to :: Rep (DataSource a) x -> DataSource a #

ToJSON a => ToJSON (DataSource a) Source # 
Instance details

Defined in RigelViz

type Rep (DataSource a) Source # 
Instance details

Defined in RigelViz

type Rep (DataSource a) = D1 (MetaData "DataSource" "RigelViz" "rigel-viz-0.2.0.0-1vfhSp89GHB1TbuLgcwhbH" False) (C1 (MetaCons "DataJSON" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a])) :+: C1 (MetaCons "DataURI" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

Layer

layer :: MarkType -> DataSource a -> EncSet -> LayerMetadata a Source #

Declare a plot layer

data LayerMetadata a Source #

Plot layer data and encoding metadata

Instances
Eq a => Eq (LayerMetadata a) Source # 
Instance details

Defined in RigelViz

Show a => Show (LayerMetadata a) Source # 
Instance details

Defined in RigelViz

Generic (LayerMetadata a) Source # 
Instance details

Defined in RigelViz

Associated Types

type Rep (LayerMetadata a) :: Type -> Type #

ToJSON a => ToJSON (LayerMetadata a) Source # 
Instance details

Defined in RigelViz

type Rep (LayerMetadata a) Source # 
Instance details

Defined in RigelViz

Mark

data MarkType Source #

Mark type alternatives

Constructors

MPoint

"point"

MCircle

"circle"

MRect

"rect"

MSquare

"square"

MBar

"bar"

MArea

"area"

MRule

"rule"

MLine

"line"

Instances
Eq MarkType Source # 
Instance details

Defined in RigelViz

Show MarkType Source # 
Instance details

Defined in RigelViz

Generic MarkType Source # 
Instance details

Defined in RigelViz

Associated Types

type Rep MarkType :: Type -> Type #

Methods

from :: MarkType -> Rep MarkType x #

to :: Rep MarkType x -> MarkType #

ToJSON MarkType Source # 
Instance details

Defined in RigelViz

type Rep MarkType Source # 
Instance details

Defined in RigelViz

type Rep MarkType = D1 (MetaData "MarkType" "RigelViz" "rigel-viz-0.2.0.0-1vfhSp89GHB1TbuLgcwhbH" False) (((C1 (MetaCons "MPoint" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MCircle" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MRect" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MSquare" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "MBar" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MArea" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MRule" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MLine" PrefixI False) (U1 :: Type -> Type))))

Data encoding options

data EncSet Source #

Set of channel encoding options.

Options are created with posEnc, colourEnc, colour, sizeEnc, size and can be added to an EncSet via its Semigroup instance

Instances
Eq EncSet Source # 
Instance details

Defined in RigelViz

Methods

(==) :: EncSet -> EncSet -> Bool #

(/=) :: EncSet -> EncSet -> Bool #

Show EncSet Source # 
Instance details

Defined in RigelViz

Generic EncSet Source # 
Instance details

Defined in RigelViz

Associated Types

type Rep EncSet :: Type -> Type #

Methods

from :: EncSet -> Rep EncSet x #

to :: Rep EncSet x -> EncSet #

Semigroup EncSet Source # 
Instance details

Defined in RigelViz

ToJSON EncSet Source # 
Instance details

Defined in RigelViz

type Rep EncSet Source # 
Instance details

Defined in RigelViz

type Rep EncSet

posEnc Source #

Arguments

:: Pos 
-> Text

Field in the data source

-> EncodingType 
-> EncSet 

Position encoding

data Pos Source #

Position encoding alternatives

Constructors

X 
Y 
X2 
Y2 
Instances
Eq Pos Source # 
Instance details

Defined in RigelViz

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Ord Pos Source # 
Instance details

Defined in RigelViz

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Show Pos Source # 
Instance details

Defined in RigelViz

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

colourEnc Source #

Arguments

:: Text

Field in the data source

-> EncodingType 
-> EncSet 

Colour encoding

colour :: Colour Double -> EncSet Source #

Fixed colour

size :: Double -> EncSet Source #

Fixed size

sizeEnc Source #

Arguments

:: Text

Field in the data source

-> EncodingType 
-> EncSet 

Size encoding

data EncodingType Source #

encoding type

Instances
Eq EncodingType Source # 
Instance details

Defined in RigelViz

Ord EncodingType Source # 
Instance details

Defined in RigelViz

Show EncodingType Source # 
Instance details

Defined in RigelViz

Generic EncodingType Source # 
Instance details

Defined in RigelViz

Associated Types

type Rep EncodingType :: Type -> Type #

ToJSON EncodingType Source # 
Instance details

Defined in RigelViz

type Rep EncodingType Source # 
Instance details

Defined in RigelViz

type Rep EncodingType = D1 (MetaData "EncodingType" "RigelViz" "rigel-viz-0.2.0.0-1vfhSp89GHB1TbuLgcwhbH" False) ((C1 (MetaCons "Nominal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Quantitative" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Temporal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ordinal" PrefixI False) (U1 :: Type -> Type)))