Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
newtype TimeEntryId Source #
Instances
Eq TimeEntryId Source # | |
Defined in Network.Hoggl.Types (==) :: TimeEntryId -> TimeEntryId -> Bool # (/=) :: TimeEntryId -> TimeEntryId -> Bool # | |
Show TimeEntryId Source # | |
Defined in Network.Hoggl.Types showsPrec :: Int -> TimeEntryId -> ShowS # show :: TimeEntryId -> String # showList :: [TimeEntryId] -> ShowS # | |
FromJSON TimeEntryId Source # | |
Defined in Network.Hoggl.Types parseJSON :: Value -> Parser TimeEntryId # parseJSONList :: Value -> Parser [TimeEntryId] # | |
ToHttpApiData TimeEntryId Source # | |
Defined in Network.Hoggl.Types toUrlPiece :: TimeEntryId -> Text # toEncodedUrlPiece :: TimeEntryId -> Builder # toHeader :: TimeEntryId -> ByteString # toQueryParam :: TimeEntryId -> Text # |
Instances
Eq Token Source # | |
Show Token Source # | |
ToHttpApiData Token Source # | |
Defined in Network.Hoggl.Types toUrlPiece :: Token -> Text # toEncodedUrlPiece :: Token -> Builder # toHeader :: Token -> ByteString # toQueryParam :: Token -> Text # |
data HogglError Source #
Instances
Show HogglError Source # | |
Defined in Network.Hoggl.Types showsPrec :: Int -> HogglError -> ShowS # show :: HogglError -> String # showList :: [HogglError] -> ShowS # |
data TimeEntryStart Source #
Instances
Eq TimeEntryStart Source # | |
Defined in Network.Hoggl.Types (==) :: TimeEntryStart -> TimeEntryStart -> Bool # (/=) :: TimeEntryStart -> TimeEntryStart -> Bool # | |
Show TimeEntryStart Source # | |
Defined in Network.Hoggl.Types showsPrec :: Int -> TimeEntryStart -> ShowS # show :: TimeEntryStart -> String # showList :: [TimeEntryStart] -> ShowS # | |
ToJSON TimeEntryStart Source # | |
Defined in Network.Hoggl.Types toJSON :: TimeEntryStart -> Value # toEncoding :: TimeEntryStart -> Encoding # toJSONList :: [TimeEntryStart] -> Value # toEncodingList :: [TimeEntryStart] -> Encoding # |
TimeEntry | |
|
Instances
Eq ISO6801 Source # | |
Ord ISO6801 Source # | |
Show ISO6801 Source # | |
FromJSON ISO6801 Source # | |
ToHttpApiData ISO6801 Source # | |
Defined in Network.Hoggl.Types toUrlPiece :: ISO6801 -> Text # toEncodedUrlPiece :: ISO6801 -> Builder # toHeader :: ISO6801 -> ByteString # toQueryParam :: ISO6801 -> Text # |
newtype ISO6801Date Source #
Instances
Eq ISO6801Date Source # | |
Defined in Network.Hoggl.Types (==) :: ISO6801Date -> ISO6801Date -> Bool # (/=) :: ISO6801Date -> ISO6801Date -> Bool # | |
Ord ISO6801Date Source # | |
Defined in Network.Hoggl.Types compare :: ISO6801Date -> ISO6801Date -> Ordering # (<) :: ISO6801Date -> ISO6801Date -> Bool # (<=) :: ISO6801Date -> ISO6801Date -> Bool # (>) :: ISO6801Date -> ISO6801Date -> Bool # (>=) :: ISO6801Date -> ISO6801Date -> Bool # max :: ISO6801Date -> ISO6801Date -> ISO6801Date # min :: ISO6801Date -> ISO6801Date -> ISO6801Date # | |
Show ISO6801Date Source # | |
Defined in Network.Hoggl.Types showsPrec :: Int -> ISO6801Date -> ShowS # show :: ISO6801Date -> String # showList :: [ISO6801Date] -> ShowS # | |
ToHttpApiData ISO6801Date Source # | |
Defined in Network.Hoggl.Types toUrlPiece :: ISO6801Date -> Text # toEncodedUrlPiece :: ISO6801Date -> Builder # toHeader :: ISO6801Date -> ByteString # toQueryParam :: ISO6801Date -> Text # |
Workspace | |
|
newtype WorkspaceId Source #
Instances
Eq WorkspaceId Source # | |
Defined in Network.Hoggl.Types (==) :: WorkspaceId -> WorkspaceId -> Bool # (/=) :: WorkspaceId -> WorkspaceId -> Bool # | |
Show WorkspaceId Source # | |
Defined in Network.Hoggl.Types showsPrec :: Int -> WorkspaceId -> ShowS # show :: WorkspaceId -> String # showList :: [WorkspaceId] -> ShowS # | |
FromJSON WorkspaceId Source # | |
Defined in Network.Hoggl.Types parseJSON :: Value -> Parser WorkspaceId # parseJSONList :: Value -> Parser [WorkspaceId] # | |
ToHttpApiData WorkspaceId Source # | |
Defined in Network.Hoggl.Types toUrlPiece :: WorkspaceId -> Text # toEncodedUrlPiece :: WorkspaceId -> Builder # toHeader :: WorkspaceId -> ByteString # toQueryParam :: WorkspaceId -> Text # |
data DetailedReport Source #
DetailedReport | |
|
Instances
Eq DetailedReport Source # | |
Defined in Network.Hoggl.Types (==) :: DetailedReport -> DetailedReport -> Bool # (/=) :: DetailedReport -> DetailedReport -> Bool # | |
Show DetailedReport Source # | |
Defined in Network.Hoggl.Types showsPrec :: Int -> DetailedReport -> ShowS # show :: DetailedReport -> String # showList :: [DetailedReport] -> ShowS # | |
FromJSON DetailedReport Source # | |
Defined in Network.Hoggl.Types parseJSON :: Value -> Parser DetailedReport # parseJSONList :: Value -> Parser [DetailedReport] # |
type TogglApi = Current :<|> (Stop :<|> (Start :<|> (Details :<|> (GetEntries :<|> (ListWorkspaces :<|> ListProjects))))) Source #
type ToggleReportApi = GetDetailedReport Source #