| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Graphics.Plotly
Description
Re-exports the Simple interface, the grammar of grpahics interface and parts of the base interface.
Synopsis
- data MarkerLine = MarkerLine {}
- data Sizemode
- data ListOrElem a
- data Symbol
- data Color
- data TraceType
- data Mode
- catColors :: Eq a => [a] -> ListOrElem Value
- data Marker = Marker (Maybe (ListOrElem Value)) (Maybe Value) (Maybe Sizemode) (Maybe (ListOrElem Value)) (Maybe (ListOrElem Value)) (Maybe (ListOrElem Symbol)) (Maybe Double) (Maybe MarkerLine)
- markerlinecolor :: Lens' MarkerLine (Maybe (ListOrElem Value))
- markerlinewidth :: Lens' MarkerLine (Maybe (ListOrElem Double))
- defMarkerLine :: MarkerLine
- data Line = Line {
- _linewidth :: Maybe Double
- _linecolor :: Maybe Color
- _lineshape :: Maybe LineShape
- _dash :: Maybe Dash
- data LineShape
- data Fill
- data Orientation
- data Dash
- markercolor :: Lens' Marker (Maybe (ListOrElem Value))
- markercolors :: Lens' Marker (Maybe (ListOrElem Value))
- markerline :: Lens' Marker (Maybe MarkerLine)
- opacity :: Lens' Marker (Maybe Double)
- sizeMode :: Lens' Marker (Maybe Sizemode)
- sizeref :: Lens' Marker (Maybe Value)
- symbol :: Lens' Marker (Maybe (ListOrElem Symbol))
- defMarker :: Marker
- data Trace = Trace (Maybe [Value]) (Maybe [Value]) (Maybe [Value]) (Maybe [Value]) (Maybe [Text]) (Maybe Value) (Maybe [Mode]) (Maybe Text) (Maybe [Text]) (Maybe TextPosition) TraceType (Maybe Marker) (Maybe Line) (Maybe Fill) (Maybe Orientation) (Maybe Value) (Maybe Bool) (Maybe Text) (Maybe [Value]) (Maybe HoverInfo) (Maybe (ListOrElem Text)) (Maybe [HoverOn]) (Maybe Bool) (Maybe Text) (Maybe Text) (Maybe Bool) (Maybe [Int]) (Maybe [Int]) (Maybe [Int]) (Maybe Color) (Maybe Double) (Maybe Text) (Maybe Text)
- data TextPosition
- data HoverOn
- data HoverMode
- data HoverInfo
- data HoverElem
- dash :: Lens' Line (Maybe Dash)
- linecolor :: Lens' Line (Maybe Color)
- lineshape :: Lens' Line (Maybe LineShape)
- linewidth :: Lens' Line (Maybe Double)
- defLine :: Line
- data Axis = Axis {}
- data AxisType
- connectgaps :: Lens' Trace (Maybe Bool)
- customdata :: Lens' Trace (Maybe [Value])
- fill :: Lens' Trace (Maybe Fill)
- fillcolor :: Lens' Trace (Maybe Text)
- hole :: Lens' Trace (Maybe Value)
- hoverinfo :: Lens' Trace (Maybe HoverInfo)
- hoveron :: Lens' Trace (Maybe [HoverOn])
- hovertext :: Lens' Trace (Maybe (ListOrElem Text))
- i :: Lens' Trace (Maybe [Int])
- j :: Lens' Trace (Maybe [Int])
- k :: Lens' Trace (Maybe [Int])
- labels :: Lens' Trace (Maybe [Text])
- legendgroup :: Lens' Trace (Maybe Text)
- marker :: Lens' Trace (Maybe Marker)
- mode :: Lens' Trace (Maybe [Mode])
- name :: Lens' Trace (Maybe Text)
- orientation :: Lens' Trace (Maybe Orientation)
- sort :: Lens' Trace (Maybe Bool)
- stackgroup :: Lens' Trace (Maybe Text)
- text :: Lens' Trace (Maybe [Text])
- textposition :: Lens' Trace (Maybe TextPosition)
- tracecolor :: Lens' Trace (Maybe Color)
- traceopacity :: Lens' Trace (Maybe Double)
- traceshowlegend :: Lens' Trace (Maybe Bool)
- tracetype :: Lens' Trace TraceType
- tracexaxis :: Lens' Trace (Maybe Text)
- traceyaxis :: Lens' Trace (Maybe Text)
- values :: Lens' Trace (Maybe [Value])
- visible :: Lens' Trace (Maybe Value)
- mkTrace :: TraceType -> Trace
- scatter :: Trace
- scatter3d :: Trace
- bars :: Trace
- box :: Trace
- mesh3d :: Trace
- contour :: Trace
- pie :: Trace
- data Margin = Margin {}
- data Barmode
- axistitle :: Lens' Axis (Maybe Text)
- axistype :: Lens' Axis (Maybe AxisType)
- axisvisible :: Lens' Axis (Maybe Bool)
- domain :: Lens' Axis (Maybe (Double, Double))
- range :: Lens' Axis (Maybe (Double, Double))
- showgrid :: Lens' Axis (Maybe Bool)
- ticktext :: Lens' Axis (Maybe [Text])
- tickvals :: Lens' Axis (Maybe [Value])
- zeroline :: Lens' Axis (Maybe Bool)
- defAxis :: Axis
- data Font = Font {
- _fontfamily :: Maybe Text
- _fontsize :: Maybe Double
- _fontcolor :: Maybe Color
- marginb :: Lens' Margin Int
- marginl :: Lens' Margin Int
- marginpad :: Lens' Margin Int
- marginr :: Lens' Margin Int
- margint :: Lens' Margin Int
- thinMargins :: Margin
- titleMargins :: Margin
- data Annotation = Annotation {
- _annotationvisible :: Maybe Bool
- _annotationtext :: Maybe Text
- _annotationfont :: Maybe Font
- _annotationwidth :: Maybe Double
- _annotationheight :: Maybe Double
- _annotationopacity :: Maybe Double
- _annotationalign :: Maybe Align
- _annotataonbgcolor :: Maybe Color
- _annotationbordercolor :: Maybe Color
- _annotationshowarrow :: Maybe Bool
- _annotationx :: Maybe Value
- _annotationxref :: Maybe Text
- _annotationxshift :: Maybe Double
- _annotationy :: Maybe Value
- _annotationyref :: Maybe Text
- _annotationyshift :: Maybe Double
- data Align
- fontcolor :: Lens' Font (Maybe Color)
- fontfamily :: Lens' Font (Maybe Text)
- fontsize :: Lens' Font (Maybe Double)
- defFont :: Font
- data Layout = Layout {
- _xaxis :: Maybe Axis
- _xaxis2 :: Maybe Axis
- _xaxis3 :: Maybe Axis
- _xaxis4 :: Maybe Axis
- _yaxis :: Maybe Axis
- _yaxis2 :: Maybe Axis
- _yaxis3 :: Maybe Axis
- _yaxis4 :: Maybe Axis
- _zaxis :: Maybe Axis
- _title :: Maybe Text
- _titlefont :: Maybe Font
- _showlegend :: Maybe Bool
- _height :: Maybe Int
- _width :: Maybe Int
- _barmode :: Maybe Barmode
- _hovermode :: Maybe HoverMode
- _margin :: Maybe Margin
- _font :: Maybe Font
- _annotations :: Maybe [Annotation]
- annotataonbgcolor :: Lens' Annotation (Maybe Color)
- annotationalign :: Lens' Annotation (Maybe Align)
- annotationbordercolor :: Lens' Annotation (Maybe Color)
- annotationfont :: Lens' Annotation (Maybe Font)
- annotationheight :: Lens' Annotation (Maybe Double)
- annotationopacity :: Lens' Annotation (Maybe Double)
- annotationshowarrow :: Lens' Annotation (Maybe Bool)
- annotationtext :: Lens' Annotation (Maybe Text)
- annotationvisible :: Lens' Annotation (Maybe Bool)
- annotationwidth :: Lens' Annotation (Maybe Double)
- annotationx :: Lens' Annotation (Maybe Value)
- annotationxref :: Lens' Annotation (Maybe Text)
- annotationxshift :: Lens' Annotation (Maybe Double)
- annotationy :: Lens' Annotation (Maybe Value)
- annotationyref :: Lens' Annotation (Maybe Text)
- annotationyshift :: Lens' Annotation (Maybe Double)
- defAnnotation :: Annotation
- data Plotly = Plotly {}
- annotations :: Lens' Layout (Maybe [Annotation])
- barmode :: Lens' Layout (Maybe Barmode)
- font :: Lens' Layout (Maybe Font)
- height :: Lens' Layout (Maybe Int)
- hovermode :: Lens' Layout (Maybe HoverMode)
- margin :: Lens' Layout (Maybe Margin)
- showlegend :: Lens' Layout (Maybe Bool)
- title :: Lens' Layout (Maybe Text)
- titlefont :: Lens' Layout (Maybe Font)
- width :: Lens' Layout (Maybe Int)
- xaxis :: Lens' Layout (Maybe Axis)
- xaxis2 :: Lens' Layout (Maybe Axis)
- xaxis3 :: Lens' Layout (Maybe Axis)
- xaxis4 :: Lens' Layout (Maybe Axis)
- yaxis :: Lens' Layout (Maybe Axis)
- yaxis2 :: Lens' Layout (Maybe Axis)
- yaxis3 :: Lens' Layout (Maybe Axis)
- yaxis4 :: Lens' Layout (Maybe Axis)
- zaxis :: Lens' Layout (Maybe Axis)
- defLayout :: Layout
- elemid :: Lens' Plotly Text
- layout :: Lens' Plotly Layout
- traces :: Lens' Plotly [Trace]
- plotly :: Text -> [Trace] -> Plotly
- module Graphics.Plotly.Simple
- module Graphics.Plotly.GoG
Documentation
data MarkerLine Source #
Marker line specification
Constructors
| MarkerLine | |
Fields | |
Instances
| ToJSON MarkerLine Source # | |
Defined in Graphics.Plotly.Base Methods toJSON :: MarkerLine -> Value # toEncoding :: MarkerLine -> Encoding # toJSONList :: [MarkerLine] -> Value # toEncodingList :: [MarkerLine] -> Encoding # | |
| Generic MarkerLine Source # | |
Defined in Graphics.Plotly.Base Associated Types type Rep MarkerLine :: Type -> Type # | |
| Eq MarkerLine Source # | |
Defined in Graphics.Plotly.Base | |
| type Rep MarkerLine Source # | |
Defined in Graphics.Plotly.Base type Rep MarkerLine = D1 ('MetaData "MarkerLine" "Graphics.Plotly.Base" "plotlyhs-0.2.3-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))))) | |
data ListOrElem a Source #
Instances
| ToJSON a => ToJSON (ListOrElem a) Source # | |
Defined in Graphics.Plotly.Base Methods toJSON :: ListOrElem a -> Value # toEncoding :: ListOrElem a -> Encoding # toJSONList :: [ListOrElem a] -> Value # toEncodingList :: [ListOrElem a] -> Encoding # | |
| Eq a => Eq (ListOrElem a) Source # | |
Defined in Graphics.Plotly.Base | |
Different types of markers
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 |
What kind of plot type are we building - scatter (inluding line plots) or bars?
How should traces be drawn? (lines or markers)
Marker specification
Constructors
| Marker (Maybe (ListOrElem Value)) (Maybe Value) (Maybe Sizemode) (Maybe (ListOrElem Value)) (Maybe (ListOrElem Value)) (Maybe (ListOrElem Symbol)) (Maybe Double) (Maybe MarkerLine) |
Instances
defMarkerLine :: MarkerLine Source #
default marker line specification
line specification
Constructors
| Line | |
Fields
| |
Instances
| ToJSON Line Source # | |
Defined in Graphics.Plotly.Base | |
| Generic Line Source # | |
| type Rep Line Source # | |
Defined in Graphics.Plotly.Base type Rep Line = D1 ('MetaData "Line" "Graphics.Plotly.Base" "plotlyhs-0.2.3-inplace" 'False) (C1 ('MetaCons "Line" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_linewidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Just "_linecolor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "_lineshape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineShape)) :*: S1 ('MetaSel ('Just "_dash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Dash))))) | |
Are we filling area plots from the zero line or to the next Y value?
data Orientation Source #
Horizontal or Vertical orientation of bars
Constructors
| Horizontal | |
| Vertical |
Instances
| ToJSON Orientation Source # | |
Defined in Graphics.Plotly.Base Methods toJSON :: Orientation -> Value # toEncoding :: Orientation -> Encoding # toJSONList :: [Orientation] -> Value # toEncodingList :: [Orientation] -> Encoding # | |
Dash type specification
markercolor :: Lens' Marker (Maybe (ListOrElem Value)) Source #
markercolors :: Lens' Marker (Maybe (ListOrElem Value)) Source #
markerline :: Lens' Marker (Maybe MarkerLine) Source #
A Trace is the component of a plot. Multiple traces can be superimposed.
Constructors
| Trace (Maybe [Value]) (Maybe [Value]) (Maybe [Value]) (Maybe [Value]) (Maybe [Text]) (Maybe Value) (Maybe [Mode]) (Maybe Text) (Maybe [Text]) (Maybe TextPosition) TraceType (Maybe Marker) (Maybe Line) (Maybe Fill) (Maybe Orientation) (Maybe Value) (Maybe Bool) (Maybe Text) (Maybe [Value]) (Maybe HoverInfo) (Maybe (ListOrElem Text)) (Maybe [HoverOn]) (Maybe Bool) (Maybe Text) (Maybe Text) (Maybe Bool) (Maybe [Int]) (Maybe [Int]) (Maybe [Int]) (Maybe Color) (Maybe Double) (Maybe Text) (Maybe Text) |
Instances
data TextPosition Source #
Constructors
| TopLeft | |
| TopCenter | |
| TopRight | |
| MiddleLeft | |
| MiddleCenter | |
| MiddleRight | |
| BottomLeft | |
| BottomCenter | |
| BottomRight |
Instances
Constructors
| HoverPoints | |
| HoverFills |
Instances
| ToJSON HoverInfo Source # | |
Defined in Graphics.Plotly.Base | |
| Generic HoverInfo Source # | |
| Show HoverInfo Source # | |
| type Rep HoverInfo Source # | |
Defined in Graphics.Plotly.Base type Rep HoverInfo = D1 ('MetaData "HoverInfo" "Graphics.Plotly.Base" "plotlyhs-0.2.3-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))) | |
Instances
| Generic HoverElem Source # | |
| Show HoverElem Source # | |
| type Rep HoverElem Source # | |
Defined in Graphics.Plotly.Base type Rep HoverElem = D1 ('MetaData "HoverElem" "Graphics.Plotly.Base" "plotlyhs-0.2.3-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)))) | |
Options for axes
Constructors
| Axis | |
Instances
orientation :: Lens' Trace (Maybe Orientation) Source #
Options for Margins.
Constructors
| Margin | |
Instances
| ToJSON Margin Source # | |
Defined in Graphics.Plotly.Base | |
| Generic Margin Source # | |
| type Rep Margin Source # | |
Defined in Graphics.Plotly.Base type Rep Margin = D1 ('MetaData "Margin" "Graphics.Plotly.Base" "plotlyhs-0.2.3-inplace" 'False) (C1 ('MetaCons "Margin" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_marginl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_marginr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "_marginb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "_margint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_marginpad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) | |
How different bar traces be superimposed? By grouping or by stacking?
Options for Fonts.
Constructors
| Font | |
Fields
| |
Instances
| ToJSON Font Source # | |
Defined in Graphics.Plotly.Base | |
| Generic Font Source # | |
| type Rep Font Source # | |
Defined in Graphics.Plotly.Base type Rep Font = D1 ('MetaData "Font" "Graphics.Plotly.Base" "plotlyhs-0.2.3-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))))) | |
thinMargins :: Margin Source #
some good values for margins
titleMargins :: Margin Source #
some good values for margins
data Annotation Source #
Options for annotations
Constructors
| Annotation | |
Fields
| |
Instances
Constructors
| AlignLeft | |
| AlignCenter | |
| AlignRight |
Instances
| ToJSON Align Source # | |
Defined in Graphics.Plotly.Base | |
| Generic Align Source # | |
| Show Align Source # | |
| type Rep Align Source # | |
Defined in Graphics.Plotly.Base type Rep Align = D1 ('MetaData "Align" "Graphics.Plotly.Base" "plotlyhs-0.2.3-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))) | |
options for the layout of the whole plot
Constructors
| Layout | |
Fields
| |
Instances
annotationx :: Lens' Annotation (Maybe Value) Source #
annotationy :: Lens' Annotation (Maybe Value) Source #
A helper record which represents the whole plot
Instances
| ToJSON Plotly Source # | |
Defined in Graphics.Plotly.Base | |
| Generic Plotly Source # | |
| ToMarkup Plotly Source # | |
Defined in Graphics.Plotly.Blaze | |
| ToHtml Plotly Source # | |
| type Rep Plotly Source # | |
Defined in Graphics.Plotly.Base type Rep Plotly = D1 ('MetaData "Plotly" "Graphics.Plotly.Base" "plotlyhs-0.2.3-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)))) | |
annotations :: Lens' Layout (Maybe [Annotation]) Source #
module Graphics.Plotly.Simple
module Graphics.Plotly.GoG