plotlyhs-0.2.1: Haskell bindings to Plotly.js

Safe HaskellNone
LanguageHaskell2010

Graphics.Plotly

Description

Re-exports the Simple interface, the grammar of grpahics interface and parts of the base interface.

Synopsis

Documentation

data MarkerLine Source #

Marker line specification

Instances
Eq 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 #

ToJSON 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.1-2ZGExwnnMTN4k6WJswTn5M" 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)))))

data Sizemode Source #

Constructors

Diameter 
Area 
Instances
Eq Sizemode Source # 
Instance details

Defined in Graphics.Plotly.Base

Show Sizemode Source # 
Instance details

Defined in Graphics.Plotly.Base

ToJSON Sizemode Source # 
Instance details

Defined in Graphics.Plotly.Base

data ListOrElem a Source #

Constructors

List [a] 
All a 
Instances
Eq a => Eq (ListOrElem a) Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

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

Defined in Graphics.Plotly.Base

data Symbol Source #

Different types of markers

Instances
Eq Symbol Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

Show Symbol Source # 
Instance details

Defined in Graphics.Plotly.Base

ToJSON Symbol 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
Eq Color Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

ToJSON Color 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 
Mesh3D 
Pie 
Contour 

data Mode Source #

How should traces be drawn? (lines or markers)

Constructors

Markers 
Lines 
ModeText 
Instances
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

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

Assign colors based on any categorical value

data Marker Source #

Marker specification

Instances
Eq Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

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

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

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 #

ToJSON Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Marker Source # 
Instance details

Defined in Graphics.Plotly.Base

defMarkerLine :: MarkerLine Source #

default marker line specification

data Line Source #

line specification

Instances
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 #

ToJSON Line Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Line 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
Show Fill Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Fill -> ShowS #

show :: Fill -> String #

showList :: [Fill] -> ShowS #

ToJSON Fill Source # 
Instance details

Defined in Graphics.Plotly.Base

data Orientation Source #

Horizontal or Vertical orientation of bars

Constructors

Horizontal 
Vertical 

data Dash Source #

Dash type specification

Constructors

Solid 
Dashdot 
Dot 
Instances
Show Dash Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Dash -> ShowS #

show :: Dash -> String #

showList :: [Dash] -> ShowS #

ToJSON Dash Source # 
Instance details

Defined in Graphics.Plotly.Base

defMarker :: Marker Source #

default marker specification

data Trace Source #

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

Instances
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 #

ToJSON Trace Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Trace Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Trace = D1 (MetaData "Trace" "Graphics.Plotly.Base" "plotlyhs-0.2.1-2ZGExwnnMTN4k6WJswTn5M" 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 "_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))))))))

data TextPosition Source #

Instances
Show 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 #

ToJSON 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.1-2ZGExwnnMTN4k6WJswTn5M" 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 HoverOn Source #

Constructors

HoverPoints 
HoverFills 
Instances
Show HoverOn Source # 
Instance details

Defined in Graphics.Plotly.Base

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 #

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.1-2ZGExwnnMTN4k6WJswTn5M" False) (C1 (MetaCons "HoverPoints" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HoverFills" PrefixI False) (U1 :: Type -> Type))

data HoverInfo Source #

Instances
Show 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 #

ToJSON 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.1-2ZGExwnnMTN4k6WJswTn5M" 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 HoverElem Source #

Instances
Show HoverElem Source # 
Instance details

Defined in Graphics.Plotly.Base

Generic HoverElem Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep HoverElem :: Type -> Type #

type Rep HoverElem Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep HoverElem = D1 (MetaData "HoverElem" "Graphics.Plotly.Base" "plotlyhs-0.2.1-2ZGExwnnMTN4k6WJswTn5M" 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 Axis Source #

Options for axes

Instances
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 #

ToJSON Axis Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Axis Source # 
Instance details

Defined in Graphics.Plotly.Base

data AxisType Source #

Constructors

Log 
Date 
Category 

scatter :: Trace Source #

an empty scatter plot

scatter3d :: Trace Source #

an empty 3D scatter plot

bars :: Trace Source #

an empty bar 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 Margin Source #

Options for Margins.

Constructors

Margin 
Instances
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 #

ToJSON Margin Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Margin Source # 
Instance details

Defined in Graphics.Plotly.Base

data Barmode Source #

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

Constructors

Stack 
Group 
Instances
Show Barmode Source # 
Instance details

Defined in Graphics.Plotly.Base

ToJSON Barmode Source # 
Instance details

Defined in Graphics.Plotly.Base

data Font Source #

Options for Fonts.

Instances
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 #

ToJSON Font Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Font Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Font = D1 (MetaData "Font" "Graphics.Plotly.Base" "plotlyhs-0.2.1-2ZGExwnnMTN4k6WJswTn5M" 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)))))

thinMargins :: Margin Source #

some good values for margins

titleMargins :: Margin Source #

some good values for margins

data Annotation Source #

Options for annotations

Instances
Generic Annotation Source # 
Instance details

Defined in Graphics.Plotly.Base

Associated Types

type Rep Annotation :: Type -> Type #

ToJSON Annotation Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Annotation Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Annotation = D1 (MetaData "Annotation" "Graphics.Plotly.Base" "plotlyhs-0.2.1-2ZGExwnnMTN4k6WJswTn5M" 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 Align Source #

Instances
Show Align Source # 
Instance details

Defined in Graphics.Plotly.Base

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

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 #

ToJSON Align Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Align Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Align = D1 (MetaData "Align" "Graphics.Plotly.Base" "plotlyhs-0.2.1-2ZGExwnnMTN4k6WJswTn5M" 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 Layout Source #

options for the layout of the whole plot

Instances
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 #

ToJSON Layout Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Layout Source # 
Instance details

Defined in Graphics.Plotly.Base

type Rep Layout = D1 (MetaData "Layout" "Graphics.Plotly.Base" "plotlyhs-0.2.1-2ZGExwnnMTN4k6WJswTn5M" 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 "_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]))))))))

data Plotly Source #

A helper record which represents the whole plot

Constructors

Plotly 

Fields

Instances
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 #

ToJSON Plotly Source # 
Instance details

Defined in Graphics.Plotly.Base

ToMarkup Plotly Source # 
Instance details

Defined in Graphics.Plotly.Blaze

ToHtml Plotly Source # 
Instance details

Defined in Graphics.Plotly.Lucid

Methods

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

toHtmlRaw :: 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.1-2ZGExwnnMTN4k6WJswTn5M" 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))))

defLayout :: Layout Source #

a defaultlayout

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

helper function for building the plot.