Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Client
- newClient :: Config -> IO Client
- data Config = Config {}
- newtype Exception = JsonException String
- class FromParameter a where
- fromParameter :: String -> Maybe a
- fromParameter' :: FromParameter a => String -> a
- class ToParameter a where
- toParameter :: a -> String
- type Token = String
- type UserName = String
- data Agreement
- data Majority
- type GraphId = String
- type GraphName = String
- type GraphUnit = String
- data GraphType
- data GraphColor
- type DateFormat = String
- data DisplayMode
- type Url = String
- type Date = Day
- type Quantity = String
- data WebhookType
- type WebhookHash = String
- createUser :: Agreement -> Majority -> Client -> IO ()
- updateToken :: Token -> Client -> IO ()
- deleteUser :: Client -> IO ()
- createGraph :: GraphId -> GraphName -> GraphUnit -> GraphType -> GraphColor -> Client -> IO ()
- getGraphs :: Client -> IO Value
- getGraphsBSL :: Client -> IO ByteString
- getGraph :: GraphId -> Maybe DateFormat -> DisplayMode -> Client -> IO ByteString
- updateGraph :: GraphId -> Maybe GraphName -> Maybe GraphUnit -> Maybe GraphColor -> [Url] -> Client -> IO ()
- deleteGraph :: GraphId -> Client -> IO ()
- setQuantity :: GraphId -> Date -> Quantity -> Client -> IO ()
- getQuantity :: GraphId -> Date -> Client -> IO Value
- getQuantityBSL :: GraphId -> Date -> Client -> IO ByteString
- updateQuantity :: GraphId -> Date -> Quantity -> Client -> IO ()
- incrementQuantity :: GraphId -> Client -> IO ()
- decrementQuantity :: GraphId -> Client -> IO ()
- deleteQuantity :: GraphId -> Date -> Client -> IO ()
- createWebhook :: GraphId -> WebhookType -> Client -> IO Text
- getWebhooks :: Client -> IO Value
- getWebhooksBSL :: Client -> IO ByteString
- invokeWebhook :: WebhookHash -> Client -> IO ()
- deleteWebhook :: WebhookHash -> Client -> IO ()
Types
Pixela client.
import Web.Pixela import Data.Default (def) main :: IO main = do _client <- newClient def pure ()
Client configuration.
Config | |
|
Instances
Eq Exception Source # | |
Show Exception Source # | |
Exception Exception Source # | |
Defined in Web.Pixela toException :: Exception -> SomeException # fromException :: SomeException -> Maybe Exception # displayException :: Exception -> String # |
class FromParameter a where Source #
A type class to create a value from String
.
fromParameter :: String -> Maybe a Source #
If you know this does not fail, you can use fromParameter'
.
Instances
FromParameter WebhookType Source # | |
Defined in Web.Pixela fromParameter :: String -> Maybe WebhookType Source # | |
FromParameter DisplayMode Source # | |
Defined in Web.Pixela fromParameter :: String -> Maybe DisplayMode Source # | |
FromParameter GraphColor Source # | |
Defined in Web.Pixela fromParameter :: String -> Maybe GraphColor Source # | |
FromParameter GraphType Source # | |
Defined in Web.Pixela |
fromParameter' :: FromParameter a => String -> a Source #
Create value from String
.
This function is unsafe, applys error
if fails.
fromParameter
is safe.
class ToParameter a where Source #
A type class to convert a value to String
.
toParameter :: a -> String Source #
Instances
ToParameter WebhookType Source # | |
Defined in Web.Pixela toParameter :: WebhookType -> String Source # | |
ToParameter DisplayMode Source # | |
Defined in Web.Pixela toParameter :: DisplayMode -> String Source # | |
ToParameter GraphColor Source # | |
Defined in Web.Pixela toParameter :: GraphColor -> String Source # | |
ToParameter GraphType Source # | |
Defined in Web.Pixela toParameter :: GraphType -> String Source # |
Which to agree terms of service or not.
Major (adult) or minor (child).
data GraphColor Source #
Instances
Eq GraphColor Source # | |
Defined in Web.Pixela (==) :: GraphColor -> GraphColor -> Bool # (/=) :: GraphColor -> GraphColor -> Bool # | |
Read GraphColor Source # | |
Defined in Web.Pixela readsPrec :: Int -> ReadS GraphColor # readList :: ReadS [GraphColor] # readPrec :: ReadPrec GraphColor # readListPrec :: ReadPrec [GraphColor] # | |
Show GraphColor Source # | |
Defined in Web.Pixela showsPrec :: Int -> GraphColor -> ShowS # show :: GraphColor -> String # showList :: [GraphColor] -> ShowS # | |
ToParameter GraphColor Source # | |
Defined in Web.Pixela toParameter :: GraphColor -> String Source # | |
FromParameter GraphColor Source # | |
Defined in Web.Pixela fromParameter :: String -> Maybe GraphColor Source # |
type DateFormat = String Source #
data DisplayMode Source #
Instances
Eq DisplayMode Source # | |
Defined in Web.Pixela (==) :: DisplayMode -> DisplayMode -> Bool # (/=) :: DisplayMode -> DisplayMode -> Bool # | |
Read DisplayMode Source # | |
Defined in Web.Pixela readsPrec :: Int -> ReadS DisplayMode # readList :: ReadS [DisplayMode] # readPrec :: ReadPrec DisplayMode # readListPrec :: ReadPrec [DisplayMode] # | |
Show DisplayMode Source # | |
Defined in Web.Pixela showsPrec :: Int -> DisplayMode -> ShowS # show :: DisplayMode -> String # showList :: [DisplayMode] -> ShowS # | |
ToParameter DisplayMode Source # | |
Defined in Web.Pixela toParameter :: DisplayMode -> String Source # | |
FromParameter DisplayMode Source # | |
Defined in Web.Pixela fromParameter :: String -> Maybe DisplayMode Source # |
data WebhookType Source #
Instances
Eq WebhookType Source # | |
Defined in Web.Pixela (==) :: WebhookType -> WebhookType -> Bool # (/=) :: WebhookType -> WebhookType -> Bool # | |
Read WebhookType Source # | |
Defined in Web.Pixela readsPrec :: Int -> ReadS WebhookType # readList :: ReadS [WebhookType] # readPrec :: ReadPrec WebhookType # readListPrec :: ReadPrec [WebhookType] # | |
Show WebhookType Source # | |
Defined in Web.Pixela showsPrec :: Int -> WebhookType -> ShowS # show :: WebhookType -> String # showList :: [WebhookType] -> ShowS # | |
ToParameter WebhookType Source # | |
Defined in Web.Pixela toParameter :: WebhookType -> String Source # | |
FromParameter WebhookType Source # | |
Defined in Web.Pixela fromParameter :: String -> Maybe WebhookType Source # |
type WebhookHash = String Source #
User functions
createUser :: Agreement -> Majority -> Client -> IO () Source #
Create a user. https://pixe.la/#api-detail-post-users
updateToken :: Token -> Client -> IO () Source #
Update user token. https://pixe.la/#api-detail-put-user
deleteUser :: Client -> IO () Source #
Delete the user. https://pixe.la/#api-detail-delete-user
Graph functions
createGraph :: GraphId -> GraphName -> GraphUnit -> GraphType -> GraphColor -> Client -> IO () Source #
Create a graph. https://pixe.la/#api-detail-post-graphs
getGraphs :: Client -> IO Value Source #
Get the list of infomation of graphs. https://pixe.la/#api-detail-get-graphs
getGraphsBSL :: Client -> IO ByteString Source #
Get the list of infomation of graphs. https://pixe.la/#api-detail-get-graphs
getGraph :: GraphId -> Maybe DateFormat -> DisplayMode -> Client -> IO ByteString Source #
Get the graph. https://pixe.la/#api-detail-get-graph
updateGraph :: GraphId -> Maybe GraphName -> Maybe GraphUnit -> Maybe GraphColor -> [Url] -> Client -> IO () Source #
Update the graph. https://pixe.la/#api-detail-put-graph
deleteGraph :: GraphId -> Client -> IO () Source #
Delete the graph. https://pixe.la/#api-detail-delete-graph
Quantity funcitons
setQuantity :: GraphId -> Date -> Quantity -> Client -> IO () Source #
Set quantity pixel. https://pixe.la/#api-detail-post-pixels
getQuantity :: GraphId -> Date -> Client -> IO Value Source #
Get quantity pixel. https://pixe.la/#api-detail-get-pixel
getQuantityBSL :: GraphId -> Date -> Client -> IO ByteString Source #
Get quantity pixel. https://pixe.la/#api-detail-get-pixel
updateQuantity :: GraphId -> Date -> Quantity -> Client -> IO () Source #
Update quantity pixel. https://pixe.la/#api-detail-put-pixel
incrementQuantity :: GraphId -> Client -> IO () Source #
Increment quantity pixel. https://pixe.la/#api-detail-pixel-increment
decrementQuantity :: GraphId -> Client -> IO () Source #
Decrement quantity pixel. https://pixe.la/#api-detail-pixel-decrement
deleteQuantity :: GraphId -> Date -> Client -> IO () Source #
Delete quantity pixel. https://pixe.la/#api-detail-delete-pixel
Webhook functions
createWebhook :: GraphId -> WebhookType -> Client -> IO Text Source #
Create a webhook. https://pixe.la/#api-detail-post-webhooks
getWebhooks :: Client -> IO Value Source #
Get the webhook. https://pixe.la/#api-detail-get-webhooks
getWebhooksBSL :: Client -> IO ByteString Source #
Get the webhook. https://pixe.la/#api-detail-get-webhooks
invokeWebhook :: WebhookHash -> Client -> IO () Source #
Invoke the webhook. https://pixe.la/#api-detail-post-webhook
deleteWebhook :: WebhookHash -> Client -> IO () Source #
Delete the webhook. https://pixe.la/#api-detail-delete-webhook