VKHS-1.9: Provides access to Vkontakte social network via public API

Safe HaskellNone
LanguageHaskell98

Web.VKHS.Client

Contents

Description

This module mainly contains HTTP wrappers required to operate VK monad

Synopsis

Documentation

data Error Source #

Constructors

ErrorParseURL 

Fields

ErrorSetURL 

Fields

Instances

Eq Error Source # 

Methods

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

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

Show Error Source # 

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

MonadVK (t (R t x)) (R t x) => EnsureVK t (R t x) (Either Error URL) URL Source # 

Methods

ensure :: t (R t x) (Either Error URL) -> t (R t x) URL Source #

MonadVK (t (R t x)) (R t x) => EnsureVK t (R t x) (Either Error Request) Request Source # 

Methods

ensure :: t (R t x) (Either Error Request) -> t (R t x) Request Source #

class (MonadIO m, MonadState s m, ToClientState s) => MonadClient m s | m -> s Source #

Instances

newtype URL_Query Source #

Constructors

URL_Query 

Fields

newtype URL_Host Source #

Constructors

URL_Host 

Fields

newtype URL_Port Source #

Constructors

URL_Port 

Fields

newtype URL_Path Source #

Constructors

URL_Path 

Fields

newtype URL Source #

Constructors

URL 

Fields

Instances

Eq URL Source # 

Methods

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

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

Show URL Source # 

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

MonadVK (t (R t x)) (R t x) => EnsureVK t (R t x) (Either Error URL) URL Source # 

Methods

ensure :: t (R t x) (Either Error URL) -> t (R t x) URL Source #

FIXME Pack Text to ByteStrings, not to String

splitFragments :: String -> String -> String -> [(String, String)] Source #

  • FIXME Convert to ByteString / Text

urlFragments :: URL -> [(String, String)] Source #

  • FIXME Convert to ByteString / Text

data Cookies Source #

Constructors

Cookies 

Fields

data Request Source #

Constructors

Request 

Fields

Instances

MonadVK (t (R t x)) (R t x) => EnsureVK t (R t x) (Either Error Request) Request Source # 

Methods

ensure :: t (R t x) (Either Error Request) -> t (R t x) Request Source #

requestCreateGet :: MonadClient m s => URL -> Cookies -> m (Either Error Request) Source #

Create HTTP(S) GET request

requestCreatePost :: MonadClient m s => FilledForm -> Cookies -> m (Either Error Request) Source #

Create HTTP(S) POST request

requestUploadPhoto :: MonadClient m s => Text -> ByteString -> m (Either Error Request) Source #

Upload the bytestring data bs to the server text_url

  • FIXME This function is not working. Looks like VK requires some other FIXME method rather than urlEncodedBody.
  • FIXME Use URL rather than Text

downloadFileWith :: MonadClient m s => URL -> (ByteString -> IO ()) -> m () Source #

Download helper