ltiv1p1-1.0.0.3: Partial implementation of a service provider for LTI 1.1.

Copyright(c) Artem Chirkin
LicenseMIT
MaintainerArtem Chirkin <chirkin@arch.ethz.ch>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Web.LTI

Contents

Description

Provide services to LTI 1.1 consumers, such as edX.

Synopsis

Data types

data LTIProvider Source #

LTI 1.1 Service provider

Instances

ltiOAuth :: LTIProvider -> OAuth Source #

OAuth credentials of provider

newLTIProvider :: ByteString -> ByteString -> LTIProvider Source #

Create a new default LTIProvider with given provider token and secret

data LTIException Source #

Either LTI or OAuth exception

Instances

Eq LTIException Source # 
Data LTIException Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LTIException -> c LTIException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LTIException #

toConstr :: LTIException -> Constr #

dataTypeOf :: LTIException -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LTIException) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LTIException) #

gmapT :: (forall b. Data b => b -> b) -> LTIException -> LTIException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LTIException -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LTIException -> r #

gmapQ :: (forall d. Data d => d -> u) -> LTIException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LTIException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LTIException -> m LTIException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LTIException -> m LTIException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LTIException -> m LTIException #

Show LTIException Source # 
Exception LTIException Source # 

simplifiers

gradeRequest Source #

Arguments

:: MonadIO m 
=> LTIProvider 
-> (LTIProvider -> request -> ExceptT LTIException m (Map ByteString ByteString))

processRequest or processWaiRequest

-> request

request value (e.g. from Network.HTTP.Client or Network.Wai)

-> ExceptT LTIException m (Double -> Manager -> m (Response ByteString), Map ByteString ByteString)

returns a grading function and a request parameter map

Being supplied with processRequest function creates a proper grade response to the service consumer.

Incoming requests

processRequest :: MonadIO m => LTIProvider -> Request -> ExceptT LTIException m (Map ByteString ByteString) Source #

Get url encoded data from Network.HTTP.Client.Request

processWaiRequest :: MonadIO m => LTIProvider -> Request -> ExceptT LTIException m (Map ByteString ByteString) Source #

Get url encoded data from Network.Wai.Request

processYesodRequest :: (MonadIO m, MonadHandler m) => LTIProvider -> YesodRequest -> ExceptT LTIException m (Map ByteString ByteString) Source #

Get url encoded data from Network.Wai.Request

Outgoing requests

replaceResultRequest Source #

Arguments

:: MonadIO m 
=> LTIProvider 
-> String

url of service consumer

-> Text

sourcedId (student id)

-> Double

resultScore (grade between 0.0 and 1.0)

-> Maybe Text

resultData (not sure if edX stores it though)

-> m Request 

Create a replaceResult request to send it to an LTI consumer