grafana-0.1: grafana datatypes for dashboards

Safe HaskellNone
LanguageHaskell2010

Grafana

Documentation

data ColumnSort Source #

Constructors

ColumnSort !Int !SortOrder 
Instances
Eq ColumnSort Source # 
Instance details

Defined in Grafana

Read ColumnSort Source # 
Instance details

Defined in Grafana

Show ColumnSort Source # 
Instance details

Defined in Grafana

Generic ColumnSort Source # 
Instance details

Defined in Grafana

Associated Types

type Rep ColumnSort :: Type -> Type #

ToJSON ColumnSort Source # 
Instance details

Defined in Grafana

type Rep ColumnSort Source # 
Instance details

Defined in Grafana

data Dashboard Source #

Instances
Eq Dashboard Source # 
Instance details

Defined in Grafana

Read Dashboard Source # 
Instance details

Defined in Grafana

Show Dashboard Source # 
Instance details

Defined in Grafana

Generic Dashboard Source # 
Instance details

Defined in Grafana

Associated Types

type Rep Dashboard :: Type -> Type #

ToJSON Dashboard Source # 
Instance details

Defined in Grafana

type Rep Dashboard Source # 
Instance details

Defined in Grafana

data Gauge Source #

Constructors

Gauge 
Instances
Eq Gauge Source # 
Instance details

Defined in Grafana

Methods

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

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

Read Gauge Source # 
Instance details

Defined in Grafana

Show Gauge Source # 
Instance details

Defined in Grafana

Methods

showsPrec :: Int -> Gauge -> ShowS #

show :: Gauge -> String #

showList :: [Gauge] -> ShowS #

Generic Gauge Source # 
Instance details

Defined in Grafana

Associated Types

type Rep Gauge :: Type -> Type #

Methods

from :: Gauge -> Rep Gauge x #

to :: Rep Gauge x -> Gauge #

ToJSON Gauge Source # 
Instance details

Defined in Grafana

type Rep Gauge Source # 
Instance details

Defined in Grafana

data Sparkline Source #

Constructors

Sparkline 

Fields

Instances
Eq Sparkline Source # 
Instance details

Defined in Grafana

Read Sparkline Source # 
Instance details

Defined in Grafana

Show Sparkline Source # 
Instance details

Defined in Grafana

Generic Sparkline Source # 
Instance details

Defined in Grafana

Associated Types

type Rep Sparkline :: Type -> Type #

ToJSON Sparkline Source # 
Instance details

Defined in Grafana

type Rep Sparkline Source # 
Instance details

Defined in Grafana

type Rep Sparkline = D1 (MetaData "Sparkline" "Grafana" "grafana-0.1-Bem3Myei2QP77MQ0WCS4y6" 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))))

data UnitFormat Source #

Instances
Eq UnitFormat Source # 
Instance details

Defined in Grafana

Read UnitFormat Source # 
Instance details

Defined in Grafana

Show UnitFormat Source # 
Instance details

Defined in Grafana

Generic UnitFormat Source # 
Instance details

Defined in Grafana

Associated Types

type Rep UnitFormat :: Type -> Type #

ToJSON UnitFormat Source # 
Instance details

Defined in Grafana

type Rep UnitFormat Source # 
Instance details

Defined in Grafana

type Rep UnitFormat = D1 (MetaData "UnitFormat" "Grafana" "grafana-0.1-Bem3Myei2QP77MQ0WCS4y6" False) ((C1 (MetaCons "PercentUnitFormat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PercentFormat" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DBmFormat" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SecondsFormat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MillisecondsFormat" PrefixI False) (U1 :: Type -> Type))))

data Panel Source #

Instances
Eq Panel Source # 
Instance details

Defined in Grafana

Methods

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

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

Read Panel Source # 
Instance details

Defined in Grafana

Show Panel Source # 
Instance details

Defined in Grafana

Methods

showsPrec :: Int -> Panel -> ShowS #

show :: Panel -> String #

showList :: [Panel] -> ShowS #

Generic Panel Source # 
Instance details

Defined in Grafana

Associated Types

type Rep Panel :: Type -> Type #

Methods

from :: Panel -> Rep Panel x #

to :: Rep Panel x -> Panel #

ToJSON Panel Source # 
Instance details

Defined in Grafana

type Rep Panel Source # 
Instance details

Defined in Grafana

type Rep Panel

data PanelStyles Source #

Instances
Eq PanelStyles Source # 
Instance details

Defined in Grafana

Read PanelStyles Source # 
Instance details

Defined in Grafana

Show PanelStyles Source # 
Instance details

Defined in Grafana

Generic PanelStyles Source # 
Instance details

Defined in Grafana

Associated Types

type Rep PanelStyles :: Type -> Type #

ToJSON PanelStyles Source # 
Instance details

Defined in Grafana

type Rep PanelStyles Source # 
Instance details

Defined in Grafana

data PathComponent a Source #

Constructors

Anything 
Variable !Text 
Literal a 
OneOf [a] 
Instances
Functor PathComponent Source # 
Instance details

Defined in Grafana

Methods

fmap :: (a -> b) -> PathComponent a -> PathComponent b #

(<$) :: a -> PathComponent b -> PathComponent a #

Foldable PathComponent Source # 
Instance details

Defined in Grafana

Methods

fold :: Monoid m => PathComponent m -> m #

foldMap :: Monoid m => (a -> m) -> PathComponent a -> m #

foldr :: (a -> b -> b) -> b -> PathComponent a -> b #

foldr' :: (a -> b -> b) -> b -> PathComponent a -> b #

foldl :: (b -> a -> b) -> b -> PathComponent a -> b #

foldl' :: (b -> a -> b) -> b -> PathComponent a -> b #

foldr1 :: (a -> a -> a) -> PathComponent a -> a #

foldl1 :: (a -> a -> a) -> PathComponent a -> a #

toList :: PathComponent a -> [a] #

null :: PathComponent a -> Bool #

length :: PathComponent a -> Int #

elem :: Eq a => a -> PathComponent a -> Bool #

maximum :: Ord a => PathComponent a -> a #

minimum :: Ord a => PathComponent a -> a #

sum :: Num a => PathComponent a -> a #

product :: Num a => PathComponent a -> a #

Traversable PathComponent Source # 
Instance details

Defined in Grafana

Methods

traverse :: Applicative f => (a -> f b) -> PathComponent a -> f (PathComponent b) #

sequenceA :: Applicative f => PathComponent (f a) -> f (PathComponent a) #

mapM :: Monad m => (a -> m b) -> PathComponent a -> m (PathComponent b) #

sequence :: Monad m => PathComponent (m a) -> m (PathComponent a) #

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

Defined in Grafana

Ord a => Ord (PathComponent a) Source # 
Instance details

Defined in Grafana

Read a => Read (PathComponent a) Source # 
Instance details

Defined in Grafana

Show a => Show (PathComponent a) Source # 
Instance details

Defined in Grafana

data RGBA Source #

Constructors

RGBA !Word8 !Word8 !Word8 !Double 
RGB !Word8 !Word8 !Word8 
Instances
Eq RGBA Source # 
Instance details

Defined in Grafana

Methods

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

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

Read RGBA Source # 
Instance details

Defined in Grafana

Show RGBA Source # 
Instance details

Defined in Grafana

Methods

showsPrec :: Int -> RGBA -> ShowS #

show :: RGBA -> String #

showList :: [RGBA] -> ShowS #

Generic RGBA Source # 
Instance details

Defined in Grafana

Associated Types

type Rep RGBA :: Type -> Type #

Methods

from :: RGBA -> Rep RGBA x #

to :: Rep RGBA x -> RGBA #

ToJSON RGBA Source # 
Instance details

Defined in Grafana

type Rep RGBA Source # 
Instance details

Defined in Grafana

data SortOrder Source #

Constructors

Ascending 
Descending 
Instances
Eq SortOrder Source # 
Instance details

Defined in Grafana

Read SortOrder Source # 
Instance details

Defined in Grafana

Show SortOrder Source # 
Instance details

Defined in Grafana

Generic SortOrder Source # 
Instance details

Defined in Grafana

Associated Types

type Rep SortOrder :: Type -> Type #

type Rep SortOrder Source # 
Instance details

Defined in Grafana

type Rep SortOrder = D1 (MetaData "SortOrder" "Grafana" "grafana-0.1-Bem3Myei2QP77MQ0WCS4y6" False) (C1 (MetaCons "Ascending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Descending" PrefixI False) (U1 :: Type -> Type))

newtype StyleThresholds a Source #

Constructors

StyleThresholds [a] 
Instances
Functor StyleThresholds Source # 
Instance details

Defined in Grafana

Methods

fmap :: (a -> b) -> StyleThresholds a -> StyleThresholds b #

(<$) :: a -> StyleThresholds b -> StyleThresholds a #

Foldable StyleThresholds Source # 
Instance details

Defined in Grafana

Methods

fold :: Monoid m => StyleThresholds m -> m #

foldMap :: Monoid m => (a -> m) -> StyleThresholds a -> m #

foldr :: (a -> b -> b) -> b -> StyleThresholds a -> b #

foldr' :: (a -> b -> b) -> b -> StyleThresholds a -> b #

foldl :: (b -> a -> b) -> b -> StyleThresholds a -> b #

foldl' :: (b -> a -> b) -> b -> StyleThresholds a -> b #

foldr1 :: (a -> a -> a) -> StyleThresholds a -> a #

foldl1 :: (a -> a -> a) -> StyleThresholds a -> a #

toList :: StyleThresholds a -> [a] #

null :: StyleThresholds a -> Bool #

length :: StyleThresholds a -> Int #

elem :: Eq a => a -> StyleThresholds a -> Bool #

maximum :: Ord a => StyleThresholds a -> a #

minimum :: Ord a => StyleThresholds a -> a #

sum :: Num a => StyleThresholds a -> a #

product :: Num a => StyleThresholds a -> a #

Traversable StyleThresholds Source # 
Instance details

Defined in Grafana

Methods

traverse :: Applicative f => (a -> f b) -> StyleThresholds a -> f (StyleThresholds b) #

sequenceA :: Applicative f => StyleThresholds (f a) -> f (StyleThresholds a) #

mapM :: Monad m => (a -> m b) -> StyleThresholds a -> m (StyleThresholds b) #

sequence :: Monad m => StyleThresholds (m a) -> m (StyleThresholds a) #

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

Defined in Grafana

Read a => Read (StyleThresholds a) Source # 
Instance details

Defined in Grafana

Show a => Show (StyleThresholds a) Source # 
Instance details

Defined in Grafana

Generic (StyleThresholds a) Source # 
Instance details

Defined in Grafana

Associated Types

type Rep (StyleThresholds a) :: Type -> Type #

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

Defined in Grafana

FromJSON a => FromJSON (StyleThresholds a) Source # 
Instance details

Defined in Grafana

type Rep (StyleThresholds a) Source # 
Instance details

Defined in Grafana

type Rep (StyleThresholds a) = D1 (MetaData "StyleThresholds" "Grafana" "grafana-0.1-Bem3Myei2QP77MQ0WCS4y6" True) (C1 (MetaCons "StyleThresholds" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a])))

data TimeAmount Source #

Constructors

Interval !Int !TimeUnit 
Instances
Eq TimeAmount Source # 
Instance details

Defined in Grafana

Read TimeAmount Source # 
Instance details

Defined in Grafana

Show TimeAmount Source # 
Instance details

Defined in Grafana

Generic TimeAmount Source # 
Instance details

Defined in Grafana

Associated Types

type Rep TimeAmount :: Type -> Type #

ToJSON TimeAmount Source # 
Instance details

Defined in Grafana

type Rep TimeAmount Source # 
Instance details

Defined in Grafana

data TimeRange Source #

Constructors

TimeRange 
Instances
Eq TimeRange Source # 
Instance details

Defined in Grafana

Read TimeRange Source # 
Instance details

Defined in Grafana

Show TimeRange Source # 
Instance details

Defined in Grafana

Generic TimeRange Source # 
Instance details

Defined in Grafana

Associated Types

type Rep TimeRange :: Type -> Type #

ToJSON TimeRange Source # 
Instance details

Defined in Grafana

type Rep TimeRange Source # 
Instance details

Defined in Grafana

type Rep TimeRange = D1 (MetaData "TimeRange" "Grafana" "grafana-0.1-Bem3Myei2QP77MQ0WCS4y6" 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))))

data TimeUnit Source #

Constructors

Seconds 
Minutes 
Hours 
Days 
Instances
Eq TimeUnit Source # 
Instance details

Defined in Grafana

Read TimeUnit Source # 
Instance details

Defined in Grafana

Show TimeUnit Source # 
Instance details

Defined in Grafana

Generic TimeUnit Source # 
Instance details

Defined in Grafana

Associated Types

type Rep TimeUnit :: Type -> Type #

Methods

from :: TimeUnit -> Rep TimeUnit x #

to :: Rep TimeUnit x -> TimeUnit #

type Rep TimeUnit Source # 
Instance details

Defined in Grafana

type Rep TimeUnit = D1 (MetaData "TimeUnit" "Grafana" "grafana-0.1-Bem3Myei2QP77MQ0WCS4y6" 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)))

columns :: [Text] -> [Column] Source #

graph :: Text -> [GraphiteQuery] -> QueryPanel Source #

layoutUniformPanels :: Int -> Int -> Int -> Int -> [QueryPanel] -> [Panel] Source #

move :: Int -> Int -> Panel -> Panel Source #

panelAt :: Int -> Int -> Int -> Int -> QueryPanel -> [Panel] Source #

row :: Text -> QueryPanel Source #

table :: PanelStyles -> Text -> [Column] -> ColumnSort -> [GraphiteQuery] -> QueryPanel Source #

htmlPanel :: Text -> QueryPanel Source #