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

Web.Telegraph.Types

Description

Type definitions, note that all fields are strict

Synopsis

Documentation

data Account Source #

A Telegraph account

Constructors

Account 

Fields

  • shortName :: Text

    Account name, helps users with several accounts remember which they are currently using

    Displayed to the user above the "Edit/Publish" button on Telegra.ph, other users don't see this name

  • authorName :: Text

    Default author name used when creating new articles

  • authorUrl :: Text

    Profile link, opened when users click on the author's name below the title

    Can be any link, not necessarily to a Telegram profile or channel

  • accessToken :: Maybe Text

    Access token of the Telegraph account

  • authUrl :: Maybe Text

    URL to authorize a browser on telegra.ph and connect it to a Telegraph account

    This URL is valid for only one use and for 5 minutes only

  • pageCount :: Maybe Int

    Number of pages belonging to the Telegraph account

Instances

Instances details
Eq Account Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

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

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

Show Account Source # 
Instance details

Defined in Web.Telegraph.Types

ToJSON Account Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Account Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "accessToken" k Account Account a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "authUrl" k Account Account a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "authorName" k Account Account a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "authorUrl" k Account Account a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Maybe Int, b ~ Maybe Int) => LabelOptic "pageCount" k Account Account a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "shortName" k Account Account a b Source # 
Instance details

Defined in Web.Telegraph.Types

data PageList Source #

A list of Telegraph articles belonging to an account

Most recently created articles first

Constructors

PageList 

Fields

  • totalCount :: Int

    Total number of pages belonging to the target Telegraph account

  • pages :: [Page]

    Requested pages of the target Telegraph account

Instances

Instances details
Eq PageList Source # 
Instance details

Defined in Web.Telegraph.Types

Show PageList Source # 
Instance details

Defined in Web.Telegraph.Types

ToJSON PageList Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON PageList Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ [Page], b ~ [Page]) => LabelOptic "pages" k PageList PageList a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Int, b ~ Int) => LabelOptic "totalCount" k PageList PageList a b Source # 
Instance details

Defined in Web.Telegraph.Types

data Page Source #

A page on Telegraph

Constructors

Page 

Fields

Instances

Instances details
Eq Page Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

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

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

Show Page Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

ToJSON Page Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Page Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "authorName" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "authorUrl" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Maybe Bool, b ~ Maybe Bool) => LabelOptic "canEdit" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Maybe [Node], b ~ Maybe [Node]) => LabelOptic "content" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "description" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Maybe Text, b ~ Maybe Text) => LabelOptic "imageUrl" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "path" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "title" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "url" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

(k ~ A_Lens, a ~ Int, b ~ Int) => LabelOptic "views" k Page Page a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Page Page a b #

newtype PageViews Source #

The number of page views for a Telegraph article

Constructors

PageViews 

Fields

Instances

Instances details
Eq PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

Show PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

ToJSON PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ An_Iso, a ~ Int, b ~ Int) => LabelOptic "views" k PageViews PageViews a b Source # 
Instance details

Defined in Web.Telegraph.Types

data Node Source #

A DOM Node

Instances

Instances details
Eq Node Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

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

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

Show Node Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

ToJSON Node Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Node Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Prism, a ~ Text, b ~ Text) => LabelOptic "_Content" k Node Node a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Node Node a b #

(k ~ A_Prism, a ~ NodeElement, b ~ NodeElement) => LabelOptic "_Element" k Node Node a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Node Node a b #

data NodeElement Source #

A DOM elemen node

Constructors

NodeElement 

Fields

  • tag :: Text

    Name of the DOM element

    Available tags: a, aside, b, blockquote, br, code, em, figcaption, figure, h3, h4, hr, i, iframe, img, li, ol, p, pre, s, strong, u, ul, video

  • attrs :: [(Text, [Text])]

    Attributes of the DOM element

    Key of object represents name of attribute, value represents value of attribute

    Available attributes: href, src

  • children :: [Node]

    List of child nodes for the DOM element

Instances

Instances details
Eq NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

Show NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

Generic NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep NodeElement :: Type -> Type #

ToJSON NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ [(Text, [Text])], b ~ [(Text, [Text])]) => LabelOptic "attrs" k NodeElement NodeElement a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ [Node], b ~ [Node]) => LabelOptic "children" k NodeElement NodeElement a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Lens, a ~ Text, b ~ Text) => LabelOptic "tag" k NodeElement NodeElement a b Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep NodeElement = D1 ('MetaData "NodeElement" "Web.Telegraph.Types" "telegraph-1.2.0-1GoZkpi2CtkFqjtACPJlam" 'False) (C1 ('MetaCons "NodeElement" 'PrefixI 'True) (S1 ('MetaSel ('Just "tag") 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "attrs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(Text, [Text])]) :*: S1 ('MetaSel ('Just "children") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node]))))

data Result a Source #

The result of an API call

Constructors

Error Text 
Result a 

Instances

Instances details
(k ~ A_Prism, a1 ~ Text, b ~ Text) => LabelOptic "_Error" k (Result a2) (Result a2) a1 b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx (Result a2) (Result a2) a1 b #

(k ~ A_Prism, a1 ~ a2, b ~ a3) => LabelOptic "_Result" k (Result a2) (Result a3) a1 b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx (Result a2) (Result a3) a1 b #

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

Defined in Web.Telegraph.Types

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

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

Defined in Web.Telegraph.Types

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

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

Defined in Web.Telegraph.Types

newtype Image Source #

An image uploaded to Telegraph

Constructors

Image 

Fields

Instances

Instances details
Eq Image Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

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

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

Show Image Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

ToJSON Image Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Image Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ An_Iso, a ~ Text, b ~ Text) => LabelOptic "src" k Image Image a b Source # 
Instance details

Defined in Web.Telegraph.Types

Methods

labelOptic :: Optic k NoIx Image Image a b #

data UploadResult Source #

The result of an image upload

Constructors

UploadError 

Fields

Sources [Image] 

Instances

Instances details
Eq UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

Show UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

ToJSON UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Prism, a ~ [Image], b ~ [Image]) => LabelOptic "_Sources" k UploadResult UploadResult a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ A_Prism, a ~ Text, b ~ Text) => LabelOptic "_UploadError" k UploadResult UploadResult a b Source # 
Instance details

Defined in Web.Telegraph.Types

(k ~ An_AffineTraversal, a ~ Text, b ~ Text) => LabelOptic "error" k UploadResult UploadResult a b Source # 
Instance details

Defined in Web.Telegraph.Types

newtype TelegraphError Source #

Constructors

APICallFailure Text

An api call has failed, we cannot distinguish between minor errors (such as illformed author urls) and much serious errors, such as invalid accessTokens, so we always throw exceptions