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

Generic Account Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep Account :: Type -> Type #

Methods

from :: Account -> Rep Account x #

to :: Rep Account x -> Account #

ToJSON Account Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Account Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep Account 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

Generic PageList Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep PageList :: Type -> Type #

Methods

from :: PageList -> Rep PageList x #

to :: Rep PageList x -> PageList #

ToJSON PageList Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON PageList Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep PageList Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep PageList = D1 ('MetaData "PageList" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" 'False) (C1 ('MetaCons "PageList" 'PrefixI 'True) (S1 ('MetaSel ('Just "totalCount") 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "pages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Page])))

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 #

Generic Page Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep Page :: Type -> Type #

Methods

from :: Page -> Rep Page x #

to :: Rep Page x -> Page #

ToJSON Page Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Page Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep Page Source # 
Instance details

Defined in Web.Telegraph.Types

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

Generic PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep PageViews :: Type -> Type #

ToJSON PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep PageViews Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep PageViews = D1 ('MetaData "PageViews" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" 'True) (C1 ('MetaCons "PageViews" 'PrefixI 'True) (S1 ('MetaSel ('Just "views") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

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 #

Generic Node Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

ToJSON Node Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Node Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep Node Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep Node = D1 ('MetaData "Node" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" 'False) (C1 ('MetaCons "Content" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Element" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 NodeElement)))

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

type Rep NodeElement Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep NodeElement = D1 ('MetaData "NodeElement" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" '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
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 #

Generic (Result a) Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep (Result a) :: Type -> Type #

Methods

from :: Result a -> Rep (Result a) x #

to :: Rep (Result a) x -> Result a #

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

Defined in Web.Telegraph.Types

type Rep (Result a) Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep (Result a) = D1 ('MetaData "Result" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" 'False) (C1 ('MetaCons "Error" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Result" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))

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 #

Generic Image Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

ToJSON Image Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON Image Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep Image Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep Image = D1 ('MetaData "Image" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" 'True) (C1 ('MetaCons "Image" 'PrefixI 'True) (S1 ('MetaSel ('Just "src") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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

Generic UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

Associated Types

type Rep UploadResult :: Type -> Type #

ToJSON UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

FromJSON UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep UploadResult Source # 
Instance details

Defined in Web.Telegraph.Types

type Rep UploadResult = D1 ('MetaData "UploadResult" "Web.Telegraph.Types" "telegraph-0.1.0-inplace" 'False) (C1 ('MetaCons "UploadError" 'PrefixI 'True) (S1 ('MetaSel ('Just "error") 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Sources" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Image])))

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