| Copyright | (c) Marco Zocca 2019 |
|---|---|
| License | BSD3 |
| Maintainer | ocramz fripost org |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
RigelViz
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
colourHaskell library.
- simplified : the generated
vega-liteJSON 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-liteAPI 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$toJSONvls0 vls0 ::VLSpecTestValue vls0 =vegaLiteSpec400 300 [layerMCircle(DataJSONtestVs) (posEncX"tv"Nominal<> posEncY"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$toJSONvls1 vls1 :: VLSpec (V3 Double) vls1 = vegaLiteSpec 400 400 [ layerMRect(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
- vegaLiteSpec :: Int -> Int -> [LayerMetadata a] -> VLSpec a
- data VLSpec a
- data DataSource a
- layer :: MarkType -> DataSource a -> EncSet -> LayerMetadata a
- data LayerMetadata a
- data MarkType
- data EncSet
- posEnc :: Pos -> Text -> EncodingType -> EncSet
- data Pos
- colourEnc :: Text -> EncodingType -> EncSet
- colour :: Colour Double -> EncSet
- size :: Double -> EncSet
- sizeEnc :: Text -> EncodingType -> EncSet
- data EncodingType
Documentation
Arguments
| :: Int | Plot width |
| -> Int | Plot height |
| -> [LayerMetadata a] | |
| -> VLSpec a |
Create a vega-lite spec
Instances
| Eq a => Eq (VLSpec a) Source # | |
| Show a => Show (VLSpec a) Source # | |
| Generic (VLSpec a) Source # | |
| ToJSON a => ToJSON (VLSpec a) Source # | |
| type Rep (VLSpec a) Source # | |
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 |
| DataURI String | URI or filepath of dataset |
Instances
| Eq a => Eq (DataSource a) Source # | |
Defined in RigelViz | |
| Show a => Show (DataSource a) Source # | |
Defined in RigelViz Methods showsPrec :: Int -> DataSource a -> ShowS # show :: DataSource a -> String # showList :: [DataSource a] -> ShowS # | |
| Generic (DataSource a) Source # | |
| ToJSON a => ToJSON (DataSource a) Source # | |
Defined in RigelViz Methods toJSON :: DataSource a -> Value # toEncoding :: DataSource a -> Encoding # toJSONList :: [DataSource a] -> Value # toEncodingList :: [DataSource a] -> Encoding # | |
| type Rep (DataSource a) Source # | |
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 # | |
Defined in RigelViz Methods (==) :: LayerMetadata a -> LayerMetadata a -> Bool # (/=) :: LayerMetadata a -> LayerMetadata a -> Bool # | |
| Show a => Show (LayerMetadata a) Source # | |
Defined in RigelViz Methods showsPrec :: Int -> LayerMetadata a -> ShowS # show :: LayerMetadata a -> String # showList :: [LayerMetadata a] -> ShowS # | |
| Generic (LayerMetadata a) Source # | |
Defined in RigelViz Associated Types type Rep (LayerMetadata a) :: Type -> Type # Methods from :: LayerMetadata a -> Rep (LayerMetadata a) x # to :: Rep (LayerMetadata a) x -> LayerMetadata a # | |
| ToJSON a => ToJSON (LayerMetadata a) Source # | |
Defined in RigelViz Methods toJSON :: LayerMetadata a -> Value # toEncoding :: LayerMetadata a -> Encoding # toJSONList :: [LayerMetadata a] -> Value # toEncodingList :: [LayerMetadata a] -> Encoding # | |
| type Rep (LayerMetadata a) Source # | |
Defined in RigelViz | |
Mark
Mark type alternatives
Constructors
| MPoint | "point" |
| MCircle | "circle" |
| MRect | "rect" |
| MSquare | "square" |
| MBar | "bar" |
| MArea | "area" |
| MRule | "rule" |
| MLine | "line" |
Instances
| Eq MarkType Source # | |
| Show MarkType Source # | |
| Generic MarkType Source # | |
| ToJSON MarkType Source # | |
| type Rep MarkType Source # | |
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
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
Arguments
| :: Pos | |
| -> Text | Field in the data source |
| -> EncodingType | |
| -> EncSet |
Position encoding
data EncodingType Source #
encoding type
Constructors
| Nominal | |
| Quantitative | |
| Temporal | |
| Ordinal |