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

Safe HaskellNone
LanguageHaskell98

Web.VKHS

Synopsis

Documentation

data State Source #

Main state of the VK monad stack. Consists of lesser states plus a copy of generic options provided by the caller.

Constructors

State 

type Guts x m r a = ReaderT (r -> x r r) (ContT r m) a Source #

newtype VK r a Source #

Main VK monad able to track errors, track full state State, set early exit by the means of continuation monad. VK encodes a coroutine which has entry points defined by Result datatype.

See also runVK and defaultSupervisor.

  • FIXME Re-write using modern Free

Constructors

VK 

Fields

Instances

MonadAPI VK r State Source # 
MonadState State (VK r) Source # 

Methods

get :: VK r State #

put :: State -> VK r () #

state :: (State -> (a, State)) -> VK r a #

Monad (VK r) Source # 

Methods

(>>=) :: VK r a -> (a -> VK r b) -> VK r b #

(>>) :: VK r a -> VK r b -> VK r b #

return :: a -> VK r a #

fail :: String -> VK r a #

Functor (VK r) Source # 

Methods

fmap :: (a -> b) -> VK r a -> VK r b #

(<$) :: a -> VK r b -> VK r a #

Applicative (VK r) Source # 

Methods

pure :: a -> VK r a #

(<*>) :: VK r (a -> b) -> VK r a -> VK r b #

(*>) :: VK r a -> VK r b -> VK r b #

(<*) :: VK r a -> VK r b -> VK r a #

MonadIO (VK r) Source # 

Methods

liftIO :: IO a -> VK r a #

MonadCont (VK r) Source # 

Methods

callCC :: ((a -> VK r b) -> VK r a) -> VK r a #

MonadClient (VK r) State Source # 
MonadVK (VK r) r Source # 
MonadLogin (VK r) r State Source # 
MonadReader (r -> VK r r) (VK r) Source # 

Methods

ask :: VK r (r -> VK r r) #

local :: ((r -> VK r r) -> r -> VK r r) -> VK r a -> VK r a #

reader :: ((r -> VK r r) -> a) -> VK r a #

stepVK :: VK r r -> StateT State (ExceptT Text IO) r Source #

Run the VK coroutine till next return. Consider using runVK for full spinup.

defaultSupervisor :: Show a => VK (R VK a) (R VK a) -> StateT State (ExceptT Text IO) a Source #

Run VK monad m and handle continuation requests using default algorithm. defaultSupervisor would relogin on invalid access token condition, ask for missing form fields (typically - an email/password)

See also runVK

  • FIXME Store known answers in external DB (in file?) instead of LoginState FIXME dictionary
  • FIXME Handle capthas (offer running standalone apps)

runLogin :: GenericOptions -> ExceptT Text IO AccessToken Source #

Run login procedure using defaultSupervisor. Return AccessToken on success

runAPI :: Show b => GenericOptions -> VK (R VK b) b -> ExceptT Text IO b Source #

Run the VK monad m using generic options go and defaultSupervisor. Perform login procedure if needed. This is an mid-layer runner, consider using runVK instead.

runVK :: Show a => GenericOptions -> VK (R VK a) a -> IO (Either Text a) Source #

Run the VK monad m using generic options go and defaultSupervisor

runVK_ :: Show a => GenericOptions -> VK (R VK a) a -> IO () Source #

A version of runVK with unit return.