telegraph-0.1.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 Telegraph Source #

Constructors

Telegraph 

Instances

Instances details
Eq Telegraph Source # 
Instance details

Defined in Web.Telegraph.API

Show Telegraph Source # 
Instance details

Defined in Web.Telegraph.API

Generic Telegraph Source # 
Instance details

Defined in Web.Telegraph.API

Associated Types

type Rep Telegraph :: Type -> Type #

type Rep Telegraph Source # 
Instance details

Defined in Web.Telegraph.API

type Rep Telegraph = D1 ('MetaData "Telegraph" "Web.Telegraph.API" "telegraph-0.1.0-inplace" 'False) (C1 ('MetaCons "Telegraph" '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))))

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-0.1.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))))

Interpreting MonadTelegraph

newtype TelegraphT m a Source #

Constructors

TelegraphT 

Instances

Instances details
MonadTrans TelegraphT Source # 
Instance details

Defined in Web.Telegraph.API

Methods

lift :: Monad m => m a -> TelegraphT m a #

MonadBase b m => MonadBase b (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

liftBase :: b α -> TelegraphT m α #

MonadBaseControl b m => MonadBaseControl b (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Associated Types

type StM (TelegraphT m) a #

Methods

liftBaseWith :: (RunInBase (TelegraphT m) b -> b a) -> TelegraphT m a #

restoreM :: StM (TelegraphT m) a -> TelegraphT m a #

MonadReader r m => MonadReader r (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

ask :: TelegraphT m r #

local :: (r -> r) -> TelegraphT m a -> TelegraphT m a #

reader :: (r -> a) -> TelegraphT m a #

Monad m => Monad (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

(>>=) :: TelegraphT m a -> (a -> TelegraphT m b) -> TelegraphT m b #

(>>) :: TelegraphT m a -> TelegraphT m b -> TelegraphT m b #

return :: a -> TelegraphT m a #

Functor m => Functor (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

fmap :: (a -> b) -> TelegraphT m a -> TelegraphT m b #

(<$) :: a -> TelegraphT m b -> TelegraphT m a #

Applicative m => Applicative (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

pure :: a -> TelegraphT m a #

(<*>) :: TelegraphT m (a -> b) -> TelegraphT m a -> TelegraphT m b #

liftA2 :: (a -> b -> c) -> TelegraphT m a -> TelegraphT m b -> TelegraphT m c #

(*>) :: TelegraphT m a -> TelegraphT m b -> TelegraphT m b #

(<*) :: TelegraphT m a -> TelegraphT m b -> TelegraphT m a #

MonadIO m => MonadIO (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

liftIO :: IO a -> TelegraphT m a #

MonadThrow m => MonadThrow (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

throwM :: Exception e => e -> TelegraphT m a #

MonadCatch m => MonadCatch (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

catch :: Exception e => TelegraphT m a -> (e -> TelegraphT m a) -> TelegraphT m a #

MonadMask m => MonadMask (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

Methods

mask :: ((forall a. TelegraphT m a -> TelegraphT m a) -> TelegraphT m b) -> TelegraphT m b #

uninterruptibleMask :: ((forall a. TelegraphT m a -> TelegraphT m a) -> TelegraphT m b) -> TelegraphT m b #

generalBracket :: TelegraphT m a -> (a -> ExitCase b -> TelegraphT m c) -> (a -> TelegraphT m b) -> TelegraphT m (b, c) #

(MonadThrow m, MonadIO m) => MonadTelegraph (TelegraphT m) Source # 
Instance details

Defined in Web.Telegraph.API

type StM (TelegraphT m) a Source # 
Instance details

Defined in Web.Telegraph.API

type StM (TelegraphT m) a = StM (ReaderT (MVar Telegraph) m) a

runTelegraph :: HasHttpCap env m => Text -> TelegraphT m a -> m a Source #

interprets TelegraphT using the access token of an existing account

runTelegraph' :: HasHttpCap env m => AccountInfo -> TelegraphT m a -> m a Source #

Create a new account and interprets TelegraphT using that account

Type Synonyms

type HasHttpCap env m = (MonadIO m, HasHttpManager env, MonadReader env m) Source #

Account related APIs

editAccountInfo :: (HasHttpCap env m, MonadTelegraph m, MonadMask m) => AccountInfo -> m () Source #

Use this method to update information about this Telegraph account

getAccountInfo :: (HasHttpCap env m, MonadTelegraph m) => m Account Source #

Use this method to get information about this Telegraph account

revokeAccessToken :: (HasHttpCap env m, MonadTelegraph m, MonadMask m) => m Account Source #

Use this method to revoke access_token and generate a new one

createPage Source #

Arguments

:: (HasHttpCap env m, MonadTelegraph m) 
=> Text

title

-> [Node]

content

-> m Page 

Use this method to create a new Telegraph page

editPage Source #

Arguments

:: (HasHttpCap env m, MonadTelegraph m) 
=> Text

path

-> Text

title

-> [Node]

content

-> m Page 

Use this method to edit an existing Telegraph page

getPageList Source #

Arguments

:: (HasHttpCap env m, MonadTelegraph 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 :: HasHttpCap env m => AccountInfo -> m (Result Account) Source #

Use this method to create a new Telegraph account

getPage :: HasHttpCap env m => Text -> m (Result Page) Source #

Use this method to get a Telegraph page

getTotalViews :: HasHttpCap env m => Text -> m (Result PageViews) Source #

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

Image uploading API

uploadImageFromFile :: (HasHttpCap env m, MonadMask m) => FilePath -> m UploadResult Source #

Upload a image from a filepath to Telegraph

uploadImageFromFiles :: (HasHttpCap env m, MonadMask 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 :: HasHttpCap env m => ImgStream -> m UploadResult Source #

Upload a image stream to Telegraph

uploadImagesStreaming :: HasHttpCap env m => [ImgStream] -> m UploadResult Source #

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