Copyright | (c) Marco Zocca 2019 |
---|---|
License | BSD3 |
Maintainer | ocramz fripost org |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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 (DataJSON
testVs) [layer
MCircle
(posEnc
X
"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
$toJSON
vls1 vls1 :: VLSpec (V3 Double) vls1 = vegaLiteSpec 400 400 (DataJSON dats) [ layerMRect
$ 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 -> DataSource a -> [LayerMetadata] -> VLSpec a
- data VLSpec a
- data DataSource a
- layer :: MarkType -> EncSet -> LayerMetadata
- data LayerMetadata
- 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
:: Int | Plot width |
-> Int | Plot height |
-> DataSource a | Data source |
-> [LayerMetadata] | Plot layer encoding metadata |
-> 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.1.0.0-HOrxoXXdMvrFIi929vBm4i" 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 "vlsData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DataSource a)) :*: S1 (MetaSel (Just "vlsView") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [LayerMetadata])))) |
Data sources
data DataSource a Source #
Data source
Instances
Layer
data LayerMetadata Source #
Layer metadata
Instances
Eq LayerMetadata Source # | |
Defined in RigelViz (==) :: LayerMetadata -> LayerMetadata -> Bool # (/=) :: LayerMetadata -> LayerMetadata -> Bool # | |
Show LayerMetadata Source # | |
Defined in RigelViz showsPrec :: Int -> LayerMetadata -> ShowS # show :: LayerMetadata -> String # showList :: [LayerMetadata] -> ShowS # | |
Generic LayerMetadata Source # | |
Defined in RigelViz type Rep LayerMetadata :: Type -> Type # from :: LayerMetadata -> Rep LayerMetadata x # to :: Rep LayerMetadata x -> LayerMetadata # | |
ToJSON LayerMetadata Source # | |
Defined in RigelViz toJSON :: LayerMetadata -> Value # toEncoding :: LayerMetadata -> Encoding # toJSONList :: [LayerMetadata] -> Value # toEncodingList :: [LayerMetadata] -> Encoding # | |
type Rep LayerMetadata Source # | |
Defined in RigelViz |
Mark
Mark type alternatives
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.1.0.0-HOrxoXXdMvrFIi929vBm4i" 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
data EncodingType Source #
encoding type