telegraph-1.0.0: Binding to the telegraph API
Safe HaskellNone
LanguageHaskell2010

Web.Telegraph.API

Description

The telegraph API. Every function that runs in MonadTelegraph might throw a TelegraphError.

Synopsis

Types

data AccountInfo Source #

Constructors

AccountInfo 

Instances

Instances details
Eq AccountInfo Source # 
Instance details

Defined in Web.Telegraph.API

Show AccountInfo Source # 
Instance details

Defined in Web.Telegraph.API

Generic AccountInfo Source # 
Instance details

Defined in Web.Telegraph.API

Associated Types

type Rep AccountInfo :: Type -> Type #

ToJSON AccountInfo Source # 
Instance details

Defined in Web.Telegraph.API

FromJSON AccountInfo Source # 
Instance details

Defined in Web.Telegraph.API

type Rep AccountInfo Source # 
Instance details

Defined in Web.Telegraph.API

type Rep AccountInfo = D1 ('MetaData "AccountInfo" "Web.Telegraph.API" "telegraph-1.0.0-inplace" 'False) (C1 ('MetaCons "AccountInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "shortName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "authorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "authorUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data TS Source #

Telegraph state

Constructors

TS 

Instances

Instances details
Eq TS Source # 
Instance details

Defined in Control.Effect.Telegraph

Methods

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

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

Show TS Source # 
Instance details

Defined in Control.Effect.Telegraph

Methods

showsPrec :: Int -> TS -> ShowS #

show :: TS -> String #

showList :: [TS] -> ShowS #

Generic TS Source # 
Instance details

Defined in Control.Effect.Telegraph

Associated Types

type Rep TS :: Type -> Type #

Methods

from :: TS -> Rep TS x #

to :: Rep TS x -> TS #

type Rep TS Source # 
Instance details

Defined in Control.Effect.Telegraph

type Rep TS = D1 ('MetaData "TS" "Control.Effect.Telegraph" "telegraph-1.0.0-inplace" 'False) (C1 ('MetaCons "TS" 'PrefixI 'True) ((S1 ('MetaSel ('Just "accessToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "shortName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "authorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "authorUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

Effects

data Telegraph :: Effect where Source #

Constructors

TakeTS :: Telegraph m TS 
ReadTS :: Telegraph m TS 
PutTS :: TS -> Telegraph m () 

Instances

Instances details
Effs '[Embed IO, Reader (MVar TS)] m => Handler TelegraphH Telegraph m Source # 
Instance details

Defined in Control.Effect.Telegraph

data Http :: Effect where Source #

Instances

Instances details
Effs '[Embed IO, Reader Manager] m => Handler HttpH Http m Source # 
Instance details

Defined in Control.Effect.Telegraph

Interpreters

Error Interpreters

errorToIO' :: (Exception e, Eff (Embed IO) m, MonadCatch m) => ErrorToIOC e m a -> m (Either e a) Source #

Account related APIs

editAccountInfo :: Effs '[Telegraph', Bracket, Throw TelegraphError] m => AccountInfo -> m () Source #

Use this method to update information about this Telegraph account

getAccountInfo :: Effs '[Telegraph', Throw TelegraphError] m => m Account Source #

Use this method to get information about this Telegraph account

revokeAccessToken :: Effs '[Telegraph', Bracket, Error TelegraphError] m => m Account Source #

Use this method to revoke access_token and generate a new one

createPage Source #

Arguments

:: Effs '[Telegraph', Error TelegraphError] m 
=> Text

title

-> [Node]

content

-> m Page 

Use this method to create a new Telegraph page

editPage Source #

Arguments

:: Effs '[Telegraph', Throw TelegraphError] m 
=> Text

path

-> Text

title

-> [Node]

content

-> m Page 

Use this method to edit an existing Telegraph page

getPageList Source #

Arguments

:: Effs '[Telegraph', Throw TelegraphError] m 
=> Int

offset

-> Int

limit (0 - 200)

-> m PageList 

Use this method to get a list of pages belonging to this Telegraph account

Account independent APIs

createAccount :: Eff Http' m => AccountInfo -> m (Result Account) Source #

Use this method to create a new Telegraph account

getPage :: Eff Http' m => Text -> m (Result Page) Source #

Use this method to get a Telegraph page

getTotalViews :: Eff Http' m => Text -> m (Result PageViews) Source #

Use this method to get the total number of views for a Telegraph article

Image uploading API

uploadImageFromFile :: Effs '[Telegraph', Bracket, Embed IO] m => FilePath -> m UploadResult Source #

Upload a image from a filepath to Telegraph

uploadImageFromFiles :: Effs '[Telegraph', Bracket, Embed IO] m => [FilePath] -> m UploadResult Source #

Upload a list of images to Telegraph. The resulting list of images will be in the same order

data ImgStream Source #

Constructors

ImgStream 

Fields

uploadImageStreaming :: Eff Telegraph' m => ImgStream -> m UploadResult Source #

Upload a image stream to Telegraph

uploadImagesStreaming :: Eff Telegraph' m => [ImgStream] -> m UploadResult Source #

Upload a list of image streams to Telegraph. The resulting list of images

Interpreter primitives

data TelegraphH Source #

Instances

Instances details
Effs '[Embed IO, Reader (MVar TS)] m => Handler TelegraphH Telegraph m Source # 
Instance details

Defined in Control.Effect.Telegraph

data HttpH Source #

Instances

Instances details
Effs '[Embed IO, Reader Manager] m => Handler HttpH Http m Source # 
Instance details

Defined in Control.Effect.Telegraph

telegraph :: Effs '[Embed IO, Reader (MVar TS)] m => TelegraphC m a -> m a Source #

http :: Effs '[Embed IO, Reader Manager] m => HttpC m a -> m a Source #