| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Grafana
Documentation
Constructors
| ColorDisabled | |
| ColorCell | |
| ColorValue | |
| ColorRow |
data ColumnSort Source #
Constructors
| ColumnSort !Int !SortOrder |
Instances
data ColumnStyles Source #
Constructors
| ColumnStyles | |
Fields
| |
Instances
| Eq ColumnStyles Source # | |
Defined in Grafana | |
| Show ColumnStyles Source # | |
Defined in Grafana Methods showsPrec :: Int -> ColumnStyles -> ShowS # show :: ColumnStyles -> String # showList :: [ColumnStyles] -> ShowS # | |
| ToJSON ColumnStyles Source # | |
Defined in Grafana Methods toJSON :: ColumnStyles -> Value # toEncoding :: ColumnStyles -> Encoding # toJSONList :: [ColumnStyles] -> Value # toEncodingList :: [ColumnStyles] -> Encoding # | |
Constructors
| Dashboard | |
Fields
| |
data GraphiteQuery Source #
Constructors
Instances
| Eq GraphiteQuery Source # | |
Defined in Grafana Methods (==) :: GraphiteQuery -> GraphiteQuery -> Bool # (/=) :: GraphiteQuery -> GraphiteQuery -> Bool # | |
| Read GraphiteQuery Source # | |
Defined in Grafana Methods readsPrec :: Int -> ReadS GraphiteQuery # readList :: ReadS [GraphiteQuery] # | |
| Show GraphiteQuery Source # | |
Defined in Grafana Methods showsPrec :: Int -> GraphiteQuery -> ShowS # show :: GraphiteQuery -> String # showList :: [GraphiteQuery] -> ShowS # | |
Constructors
| Gauge | |
Fields
| |
Instances
| Eq Gauge Source # | |
| Read Gauge Source # | |
| Show Gauge Source # | |
| Generic Gauge Source # | |
| ToJSON Gauge Source # | |
| type Rep Gauge Source # | |
Defined in Grafana type Rep Gauge = D1 (MetaData "Gauge" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) (C1 (MetaCons "Gauge" PrefixI True) ((S1 (MetaSel (Just "minValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "maxValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "thresholdMarkers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "thresholdLabels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))) | |
Constructors
| Graph | |
Fields | |
Constructors
| GridPos | |
Fields
| |
Instances
| Eq GridPos Source # | |
| Read GridPos Source # | |
| Show GridPos Source # | |
| Generic GridPos Source # | |
| ToJSON GridPos Source # | |
| type Rep GridPos Source # | |
Defined in Grafana type Rep GridPos = D1 (MetaData "GridPos" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) (C1 (MetaCons "GridPos" PrefixI True) ((S1 (MetaSel (Just "panelWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "panelHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "panelXPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "panelYPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))) | |
Constructors
| Heatmap | |
Fields
| |
data NullPointMode Source #
Constructors
| Connected |
Instances
| ToJSON NullPointMode Source # | |
Defined in Grafana Methods toJSON :: NullPointMode -> Value # toEncoding :: NullPointMode -> Encoding # toJSONList :: [NullPointMode] -> Value # toEncodingList :: [NullPointMode] -> Encoding # | |
Constructors
| Panel | |
Fields | |
Instances
| Eq Panel Source # | |
| Read Panel Source # | |
| Show Panel Source # | |
| Generic Panel Source # | |
| ToJSON Panel Source # | |
| type Rep Panel Source # | |
Defined in Grafana type Rep Panel = D1 (MetaData "Panel" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) (C1 (MetaCons "Panel" PrefixI True) (S1 (MetaSel (Just "panelObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PanelConfig) :*: S1 (MetaSel (Just "panelGridPos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GridPos))) | |
type PanelConfig = [(Text, Value)] Source #
data PathComponent a Source #
Instances
Instances
data Singlestat Source #
Constructors
| Singlestat | |
Fields
| |
Instances
| Eq Singlestat Source # | |
Defined in Grafana | |
| Show Singlestat Source # | |
Defined in Grafana Methods showsPrec :: Int -> Singlestat -> ShowS # show :: Singlestat -> String # showList :: [Singlestat] -> ShowS # | |
Constructors
| Ascending | |
| Descending |
Instances
| Eq Sparkline Source # | |
| Read Sparkline Source # | |
| Show Sparkline Source # | |
| Generic Sparkline Source # | |
| ToJSON Sparkline Source # | |
| type Rep Sparkline Source # | |
Defined in Grafana type Rep Sparkline = D1 (MetaData "Sparkline" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) (C1 (MetaCons "Sparkline" PrefixI True) (S1 (MetaSel (Just "fillColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RGBA) :*: (S1 (MetaSel (Just "full") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "lineColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RGBA)))) | |
newtype StyleThresholds a Source #
Constructors
| StyleThresholds [a] |
Instances
Constructors
| Table | |
Fields
| |
data TableTransform Source #
Instances
| Eq TableTransform Source # | |
Defined in Grafana Methods (==) :: TableTransform -> TableTransform -> Bool # (/=) :: TableTransform -> TableTransform -> Bool # | |
| Show TableTransform Source # | |
Defined in Grafana Methods showsPrec :: Int -> TableTransform -> ShowS # show :: TableTransform -> String # showList :: [TableTransform] -> ShowS # | |
| ToJSON TableTransform Source # | |
Defined in Grafana Methods toJSON :: TableTransform -> Value # toEncoding :: TableTransform -> Encoding # toJSONList :: [TableTransform] -> Value # toEncodingList :: [TableTransform] -> Encoding # | |
Instances
| Eq Target Source # | |
| Read Target Source # | |
| Show Target Source # | |
| Generic Target Source # | |
| ToJSON Target Source # | |
| type Rep Target Source # | |
Defined in Grafana type Rep Target = D1 (MetaData "Target" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) (C1 (MetaCons "Target" PrefixI True) (S1 (MetaSel (Just "refId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "targetVal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) | |
data Templating Source #
Constructors
| Templating | |
Fields
| |
Instances
| Eq Templating Source # | |
Defined in Grafana | |
| Read Templating Source # | |
Defined in Grafana Methods readsPrec :: Int -> ReadS Templating # readList :: ReadS [Templating] # readPrec :: ReadPrec Templating # readListPrec :: ReadPrec [Templating] # | |
| Show Templating Source # | |
Defined in Grafana Methods showsPrec :: Int -> Templating -> ShowS # show :: Templating -> String # showList :: [Templating] -> ShowS # | |
| ToJSON Templating Source # | |
Defined in Grafana Methods toJSON :: Templating -> Value # toEncoding :: Templating -> Encoding # toJSONList :: [Templating] -> Value # toEncodingList :: [Templating] -> Encoding # | |
data TimeAmount Source #
Instances
Constructors
| TimeRange | |
Fields
| |
Instances
| Eq TimeRange Source # | |
| Read TimeRange Source # | |
| Show TimeRange Source # | |
| Generic TimeRange Source # | |
| ToJSON TimeRange Source # | |
| type Rep TimeRange Source # | |
Defined in Grafana type Rep TimeRange = D1 (MetaData "TimeRange" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) (C1 (MetaCons "TimeRange" PrefixI True) (S1 (MetaSel (Just "rangeFrom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TimeAmount) :*: S1 (MetaSel (Just "rangeTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TimeAmount)))) | |
Instances
| Eq TimeUnit Source # | |
| Read TimeUnit Source # | |
| Show TimeUnit Source # | |
| Generic TimeUnit Source # | |
| type Rep TimeUnit Source # | |
Defined in Grafana type Rep TimeUnit = D1 (MetaData "TimeUnit" "Grafana" "grafana-0.2-6cH4Y6aeeikKs5Pi0cOTrR" False) ((C1 (MetaCons "Seconds" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Minutes" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Hours" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Days" PrefixI False) (U1 :: Type -> Type))) | |
data UnitFormat Source #
Constructors
| PercentUnitFormat | |
| PercentFormat | |
| DBmFormat | |
| DbFormat | |
| SecondsFormat | |
| MillisecondsFormat | |
| BpsFormat | |
| ShortFormat | |
| NoFormat | |
| OtherFormat Text |
Instances
defaultGauge :: Gauge Source #
defaultGraph :: Graph Source #
defaultTable :: Table Source #
makeTargets :: [GraphiteQuery] -> [Target] Source #
row :: Row -> PanelConfig Source #
graph :: Graph -> PanelConfig Source #
heatmap :: Heatmap -> PanelConfig Source #
table :: Table -> PanelConfig Source #
text :: TextPanel -> PanelConfig Source #
serializeQuery :: GraphiteQuery -> Text Source #
singlestat :: Singlestat -> PanelConfig Source #
singlestatPanel :: Singlestat -> GridPos -> Panel Source #