plotlyhs-0.2.2: Haskell bindings to Plotly.js
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Plotly.Base

Description

This module defines datatypes that can be used to generate Plotly.js plots via their JSON values. The interface encourages the use of lenses. Every trace on a plot is defined by a Trace type value, the construction of which is the central goal of this module.

Example scatter plot of the Iris dataset:

import Graphics.Plotly
import Numeric.Dataset.Iris

tr :: Trace
tr = scatter & x ?~ map sepalLength iris
             & y ?~ map sepalWidth iris
             & marker ?~ (defMarker & markercolor ?~ catColors (map irisClass irisd))
             & mode ?~ [Markers]

Horizontal bars:

hbarData :: [(Text, Double)]
hbarData = [("Simon", 14.5), ("Joe", 18.9), ("Dorothy", 16.2)]

hbarsTrace :: Trace
hbarsTrace = bars & ytext ?~ map fst hbarData
                  & x ?~ map snd hbarData
                  & orientation ?~ Horizontal

see Graphics.Plotly.Lucid for helper functions that turn traces into HTML.

Synopsis

Traces

data Mode Source #

How should traces be drawn? (lines or markers)

Constructors

Markers 
Lines 
ModeText 

Instances

Instances details
Show Mode Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

ToJSON [Mode] Source # 
Instance details

Defined in Graphics.Plotly.Base

data TraceType Source #

What kind of plot type are we building - scatter (inluding line plots) or bars?

Constructors

Scatter 
Scatter3D 
Bar 
Box 
Mesh3D 
Pie 
Contour 

Instances

Instances details
ToJSON TraceType Source # 
Instance details

Defined in Graphics.Plotly.Base

Show TraceType Source # 
Instance details

Defined in Graphics.Plotly.Base

data Color Source #

A color specification, either as a concrete RGB/RGBA value or a color per point.

Constructors

ColRGBA Int Int Int Int

use this RGBA color for every point in the trace

ColRGB Int Int Int

use this RGB color for every point in the trace

ColIx Int

use a different color index for each point

Instances

Instances details
ToJSON Color Source # 
Instance details

Defined in Graphics.Plotly.Base

Eq Color Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

catColors :: Eq a => [a] -> ListOrElem Value Source #

Assign colors based on any categorical value

data Symbol Source #

Different types of markers

Instances

Instances details
ToJSON Symbol Source # 
Instance details

Defined in Graphics.Plotly.Base

Show Symbol Source # 
Instance details

Defined in Graphics.Plotly.Base

Eq Symbol Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

data ListOrElem a Source #

Constructors

List [a] 
All a 

Instances

Instances details
ToJSON a => ToJSON (ListOrElem a) Source # 
Instance details

Defined in Graphics.Plotly.Base

Eq a => Eq (ListOrElem a) Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

data Sizemode Source #

Constructors

Diameter 
Area 

Instances

Instances details
ToJSON Sizemode Source # 
Instance details

Defined in Graphics.Plotly.Base

Show Sizemode Source # 
Instance details

Defined in Graphics.Plotly.Base

Eq Sizemode Source # 
Instance details

Defined in Graphics.Plotly.Base

data MarkerLine Source #

Marker line specification

Instances

Instances details
ToJSON MarkerLine Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic MarkerLine Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep MarkerLine :: Type -> Type #

Eq MarkerLine Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep MarkerLine Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep MarkerLine = D1 ('MetaData "MarkerLine" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "MarkerLine" 'PrefixI 'True) (S1 ('MetaSel ('Just "_markerlinewidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ListOrElem Double))) :*: S1 ('MetaSel ('Just "_markerlinecolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ListOrElem Value)))))

defMarkerLine :: MarkerLine Source #

default marker line specification

data Marker Source #

Marker specification

Instances

Instances details
ToJSON Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Marker :: Type -> Type #

Methods

from :: Marker -> Rep Marker x #

to :: Rep Marker x -> Marker #

Eq Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

type Rep Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

defMarker :: Marker Source #

default marker specification

data Dash Source #

Dash type specification

Constructors

Solid 
Dashdot 
Dot 

Instances

Instances details
ToJSON Dash Source # 
Instance details

Defined in Graphics.Plotly.Base

Show Dash Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Dash -> ShowS #

show :: Dash -> String #

showList :: [Dash] -> ShowS #

data Orientation Source #

Horizontal or Vertical orientation of bars

Constructors

Horizontal 
Vertical 

Instances

Instances details
ToJSON Orientation Source # 
Instance details

Defined in Graphics.Plotly.Base

data Fill Source #

Are we filling area plots from the zero line or to the next Y value?

Instances

Instances details
ToJSON Fill Source # 
Instance details

Defined in Graphics.Plotly.Base

Show Fill Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Fill -> ShowS #

show :: Fill -> String #

showList :: [Fill] -> ShowS #

data LineShape Source #

Constructors

Linear 
Spline 
Hv 
Hvh 
Vh 
Vhv 

Instances

Instances details
ToJSON LineShape Source # 
Instance details

Defined in Graphics.Plotly.Base

Show LineShape Source # 
Instance details

Defined in Graphics.Plotly.Base

data Line Source #

line specification

Instances

Instances details
ToJSON Line Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Line Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Line :: Type -> Type #

Methods

from :: Line -> Rep Line x #

to :: Rep Line x -> Line #

type Rep Line Source # 
Instance details

Defined in Graphics.Plotly.Base

data HoverElem Source #

Instances

Instances details
Generic HoverElem Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep HoverElem :: Type -> Type #

Show HoverElem Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverElem Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverElem = D1 ('MetaData "HoverElem" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) ((C1 ('MetaCons "HoverX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoverY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HoverZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HoverText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoverName" 'PrefixI 'False) (U1 :: Type -> Type))))

data HoverInfo Source #

Instances

Instances details
ToJSON HoverInfo Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic HoverInfo Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep HoverInfo :: Type -> Type #

Show HoverInfo Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverInfo Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverInfo = D1 ('MetaData "HoverInfo" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) ((C1 ('MetaCons "HoverPlus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HoverElem])) :+: C1 ('MetaCons "HoverAll" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HoverNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoverSkip" 'PrefixI 'False) (U1 :: Type -> Type)))

data HoverMode Source #

Constructors

X 
Y 
Closest 
False 
XUnified 
YUnified 

Instances

Instances details
ToJSON HoverMode Source # 
Instance details

Defined in Graphics.Plotly.Base

data HoverOn Source #

Constructors

HoverPoints 
HoverFills 

Instances

Instances details
Generic HoverOn Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep HoverOn :: Type -> Type #

Methods

from :: HoverOn -> Rep HoverOn x #

to :: Rep HoverOn x -> HoverOn #

Show HoverOn Source # 
Instance details

Defined in Graphics.Plotly.Base

ToJSON [HoverOn] Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverOn Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverOn = D1 ('MetaData "HoverOn" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "HoverPoints" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HoverFills" 'PrefixI 'False) (U1 :: Type -> Type))

data TextPosition Source #

Instances

Instances details
ToJSON TextPosition Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic TextPosition Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep TextPosition :: Type -> Type #

Show TextPosition Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep TextPosition Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep TextPosition = D1 ('MetaData "TextPosition" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (((C1 ('MetaCons "TopLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TopCenter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TopRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MiddleLeft" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MiddleCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MiddleRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BottomLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BottomCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BottomRight" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Trace Source #

A Trace is the component of a plot. Multiple traces can be superimposed.

Constructors

Trace 

Fields

Instances

Instances details
ToJSON Trace Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Trace Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Trace :: Type -> Type #

Methods

from :: Trace -> Rep Trace x #

to :: Rep Trace x -> Trace #

type Rep Trace Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Trace = D1 ('MetaData "Trace" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "Trace" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "_x") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Value])) :*: S1 ('MetaSel ('Just "_y") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Value]))) :*: (S1 ('MetaSel ('Just "_z") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Value])) :*: S1 ('MetaSel ('Just "_values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Value])))) :*: ((S1 ('MetaSel ('Just "_labels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "_hole") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value))) :*: (S1 ('MetaSel ('Just "_mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Mode])) :*: S1 ('MetaSel ('Just "_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: (((S1 ('MetaSel ('Just "_text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "_textposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TextPosition))) :*: (S1 ('MetaSel ('Just "_tracetype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TraceType) :*: S1 ('MetaSel ('Just "_marker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Marker)))) :*: ((S1 ('MetaSel ('Just "_line") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Line)) :*: S1 ('MetaSel ('Just "_fill") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Fill))) :*: (S1 ('MetaSel ('Just "_orientation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Orientation)) :*: S1 ('MetaSel ('Just "_visible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)))))) :*: ((((S1 ('MetaSel ('Just "_traceshowlegend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_legendgroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "_customdata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Value])) :*: S1 ('MetaSel ('Just "_hoverinfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HoverInfo)))) :*: ((S1 ('MetaSel ('Just "_hovertext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ListOrElem Text))) :*: S1 ('MetaSel ('Just "_hoveron") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [HoverOn]))) :*: (S1 ('MetaSel ('Just "_connectgaps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_stackgroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: (((S1 ('MetaSel ('Just "_fillcolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_sort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "_i") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Int])) :*: S1 ('MetaSel ('Just "_j") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Int])))) :*: ((S1 ('MetaSel ('Just "_k") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Int])) :*: S1 ('MetaSel ('Just "_tracecolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "_traceopacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: (S1 ('MetaSel ('Just "_tracexaxis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_traceyaxis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))))))

scatter :: Trace Source #

an empty scatter plot

scatter3d :: Trace Source #

an empty 3D scatter plot

bars :: Trace Source #

an empty bar plot

box :: Trace Source #

an empty box plot

mesh3d :: Trace Source #

an empty 3D mesh plot

contour :: Trace Source #

an empty 3D mesh plot

pie :: Trace Source #

an empty pie chart

data AxisType Source #

Constructors

Log 
Date 
Category 

Instances

Instances details
ToJSON AxisType Source # 
Instance details

Defined in Graphics.Plotly.Base

Show AxisType Source # 
Instance details

Defined in Graphics.Plotly.Base

data Axis Source #

Options for axes

Instances

Instances details
ToJSON Axis Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Axis Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Axis :: Type -> Type #

Methods

from :: Axis -> Rep Axis x #

to :: Rep Axis x -> Axis #

type Rep Axis Source # 
Instance details

Defined in Graphics.Plotly.Base

Layouts

data Barmode Source #

How different bar traces be superimposed? By grouping or by stacking?

Constructors

Stack 
Group 

Instances

Instances details
ToJSON Barmode Source # 
Instance details

Defined in Graphics.Plotly.Base

Show Barmode Source # 
Instance details

Defined in Graphics.Plotly.Base

data Margin Source #

Options for Margins.

Constructors

Margin 

Instances

Instances details
ToJSON Margin Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Margin Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Margin :: Type -> Type #

Methods

from :: Margin -> Rep Margin x #

to :: Rep Margin x -> Margin #

type Rep Margin Source # 
Instance details

Defined in Graphics.Plotly.Base

thinMargins :: Margin Source #

some good values for margins

titleMargins :: Margin Source #

some good values for margins

data Font Source #

Options for Fonts.

Instances

Instances details
ToJSON Font Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Font Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Font :: Type -> Type #

Methods

from :: Font -> Rep Font x #

to :: Rep Font x -> Font #

type Rep Font Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Font = D1 ('MetaData "Font" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "Font" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fontfamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "_fontsize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Just "_fontcolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))))

data Align Source #

Instances

Instances details
ToJSON Align Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Align Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Align :: Type -> Type #

Methods

from :: Align -> Rep Align x #

to :: Rep Align x -> Align #

Show Align Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

type Rep Align Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Align = D1 ('MetaData "Align" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "AlignLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlignCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlignRight" 'PrefixI 'False) (U1 :: Type -> Type)))

data Annotation Source #

Options for annotations

Instances

Instances details
ToJSON Annotation Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Annotation Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Annotation :: Type -> Type #

type Rep Annotation Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Annotation = D1 ('MetaData "Annotation" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "Annotation" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "_annotationvisible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_annotationtext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "_annotationfont") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Font)) :*: S1 ('MetaSel ('Just "_annotationwidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)))) :*: ((S1 ('MetaSel ('Just "_annotationheight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Just "_annotationopacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double))) :*: (S1 ('MetaSel ('Just "_annotationalign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Align)) :*: S1 ('MetaSel ('Just "_annotataonbgcolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))))) :*: (((S1 ('MetaSel ('Just "_annotationbordercolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "_annotationshowarrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "_annotationx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)) :*: S1 ('MetaSel ('Just "_annotationxref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "_annotationxshift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Just "_annotationy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value))) :*: (S1 ('MetaSel ('Just "_annotationyref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_annotationyshift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)))))))

data Layout Source #

options for the layout of the whole plot

Instances

Instances details
ToJSON Layout Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Layout Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Layout :: Type -> Type #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

type Rep Layout Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Layout = D1 ('MetaData "Layout" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "Layout" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "_xaxis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)) :*: S1 ('MetaSel ('Just "_xaxis2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis))) :*: (S1 ('MetaSel ('Just "_xaxis3") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)) :*: S1 ('MetaSel ('Just "_xaxis4") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)))) :*: ((S1 ('MetaSel ('Just "_yaxis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)) :*: S1 ('MetaSel ('Just "_yaxis2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis))) :*: (S1 ('MetaSel ('Just "_yaxis3") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)) :*: (S1 ('MetaSel ('Just "_yaxis4") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)) :*: S1 ('MetaSel ('Just "_zaxis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Axis)))))) :*: (((S1 ('MetaSel ('Just "_title") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_titlefont") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Font))) :*: (S1 ('MetaSel ('Just "_showlegend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "_height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "_width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))) :*: ((S1 ('MetaSel ('Just "_barmode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Barmode)) :*: S1 ('MetaSel ('Just "_hovermode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HoverMode))) :*: (S1 ('MetaSel ('Just "_margin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Margin)) :*: (S1 ('MetaSel ('Just "_font") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Font)) :*: S1 ('MetaSel ('Just "_annotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Annotation]))))))))

Plotly

data Plotly Source #

A helper record which represents the whole plot

Constructors

Plotly 

Fields

Instances

Instances details
ToJSON Plotly Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic Plotly Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Plotly :: Type -> Type #

Methods

from :: Plotly -> Rep Plotly x #

to :: Rep Plotly x -> Plotly #

ToMarkup Plotly Source # 
Instance details

Defined in Graphics.Plotly.Blaze

ToHtml Plotly Source # 
Instance details

Defined in Graphics.Plotly.Lucid

Methods

toHtml :: forall (m :: Type -> Type). Monad m => Plotly -> HtmlT m () #

toHtmlRaw :: forall (m :: Type -> Type). Monad m => Plotly -> HtmlT m () #

type Rep Plotly Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Plotly = D1 ('MetaData "Plotly" "Graphics.Plotly.Base" "plotlyhs-0.2.2-inplace" 'False) (C1 ('MetaCons "Plotly" 'PrefixI 'True) (S1 ('MetaSel ('Just "_elemid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_traces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Trace]) :*: S1 ('MetaSel ('Just "_layout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Layout))))

plotly :: Text -> [Trace] -> Plotly Source #

helper function for building the plot.