Safe Haskell | None |
---|---|
Language | Haskell2010 |
An EDSL designed to make writing deadpan applications easy!
This DSL is a simple decoration of some application specific functions arround a ReaderT monad instance.
A core cabal of functions are exported from this module which are then put to use in web.ddp.deadpan to create an expressive dsl for creating ddp applications.
The main functions exported are...
TODO: Ensure these are up to date...
- rundeadpan
- sethandler
- deletehandler
- setdefaulthandler
- senddata
- sendmessage
these allow you to...
- run a deadpan application with some initial set of callbacks
- set new values for response handlers
- delete existing response handlers
- set a handler to act when no existing handler matches the incomming message
- send an ejsonvalue to the server (low-level)
- send messages to be interpreted as rpc calls
... respectively.
There is also a `control.lens.lens` collections
provided into a single ejsonvalue.
This can be used to...
- Retrieve any current collection data
- Set collection data manually
- Perform actions on collection data in callbacks
- data LookupItem a = LI {}
- ident :: forall a. Lens' (LookupItem a) GUID
- body :: forall a a. Lens (LookupItem a) (LookupItem a) a a
- type Lookup a = Seq (LookupItem a)
- data AppState cb = AppState {}
- connection :: forall cb. Lens' (AppState cb) Connection
- collections :: forall cb. Lens' (AppState cb) EJsonValue
- callbackSet :: forall cb cb. Lens (AppState cb) (AppState cb) (Lookup cb) (Lookup cb)
- type Callback = EJsonValue -> DeadpanApp ()
- newtype DeadpanApp a = DeadpanApp {}
- deadpanApp :: forall a a. Iso (DeadpanApp a) (DeadpanApp a) (ReaderT (TVar (AppState Callback)) IO a) (ReaderT (TVar (AppState Callback)) IO a)
- data Version
- version2string :: Version -> EJsonValue
- reverseVersions :: [EJsonValue]
- runDeadpan :: DeadpanApp a -> TVar (AppState Callback) -> IO a
- newID :: DeadpanApp GUID
- addHandler :: LookupItem Callback -> DeadpanApp ()
- setHandler :: GUID -> Callback -> DeadpanApp GUID
- onMatches :: EJsonValue -> Callback -> Callback
- setMatchHandler :: EJsonValue -> Callback -> DeadpanApp GUID
- setIdHandler :: GUID -> Callback -> DeadpanApp GUID
- setMsgHandler :: Text -> Callback -> DeadpanApp GUID
- setCatchAllHandler :: Callback -> DeadpanApp GUID
- deleteHandlerID :: GUID -> DeadpanApp ()
- modifyAppState :: (AppState Callback -> AppState Callback) -> DeadpanApp ()
- getAppState :: DeadpanApp (AppState Callback)
- getAppStateL :: Prism' (AppState Callback) x -> DeadpanApp (Maybe x)
- getCollections :: DeadpanApp EJsonValue
- sendData :: EJsonValue -> DeadpanApp ()
- sendMessage :: Text -> EJsonValue -> DeadpanApp ()
- connectVersion :: Version -> DeadpanApp ()
- connect :: DeadpanApp ()
- fork :: DeadpanApp a -> DeadpanApp ThreadId
- fetchMessagesThenExit :: DeadpanApp a -> DeadpanApp a
- fetchMessages :: DeadpanApp ThreadId
- getServerMessage :: DeadpanApp (Maybe EJsonValue)
- respondToMessage :: Lookup Callback -> Maybe EJsonValue -> DeadpanApp ()
- module Data.EJson
- module Web.DDP.Deadpan.GUID
- data Text :: *
- pack :: String -> Text
Documentation
data LookupItem a Source
The LookupItem data-type is used to store a set of callbacks.
_ident is a reference to the callback, not the expected message id.
ident :: forall a. Lens' (LookupItem a) GUID Source
body :: forall a a. Lens (LookupItem a) (LookupItem a) a a Source
type Lookup a = Seq (LookupItem a) Source
AppState | |
|
connection :: forall cb. Lens' (AppState cb) Connection Source
collections :: forall cb. Lens' (AppState cb) EJsonValue Source
type Callback = EJsonValue -> DeadpanApp () Source
newtype DeadpanApp a Source
deadpanApp :: forall a a. Iso (DeadpanApp a) (DeadpanApp a) (ReaderT (TVar (AppState Callback)) IO a) (ReaderT (TVar (AppState Callback)) IO a) Source
runDeadpan :: DeadpanApp a -> TVar (AppState Callback) -> IO a Source
The order of these args match that of runReaderT
addHandler :: LookupItem Callback -> DeadpanApp () Source
setHandler :: GUID -> Callback -> DeadpanApp GUID Source
onMatches :: EJsonValue -> Callback -> Callback Source
setMatchHandler :: EJsonValue -> Callback -> DeadpanApp GUID Source
setIdHandler :: GUID -> Callback -> DeadpanApp GUID Source
setMsgHandler :: Text -> Callback -> DeadpanApp GUID Source
deleteHandlerID :: GUID -> DeadpanApp () Source
modifyAppState :: (AppState Callback -> AppState Callback) -> DeadpanApp () Source
getAppState :: DeadpanApp (AppState Callback) Source
Get the raw app state. Reads the value out of the TVar container.
getAppStateL :: Prism' (AppState Callback) x -> DeadpanApp (Maybe x) Source
Get the app state in conjunction with a Prism, allowing for more succing state access
sendData :: EJsonValue -> DeadpanApp () Source
A low-level function intended to be able to send any arbitrary data to the server.
Given that all messages to the server are intended to fit the "message" format,
You should probably use sendMessage
instead.
sendMessage :: Text -> EJsonValue -> DeadpanApp () Source
Send a particular type of message (indicated by the key) to the server. This should be the primary means of [client -> server] communication by a client application.
connectVersion :: Version -> DeadpanApp () Source
Send a connection message to the server and specify the DDP API version that you wish to use.
connect :: DeadpanApp () Source
Send a generic connection message to the server.
fork :: DeadpanApp a -> DeadpanApp ThreadId Source
Provides a way to fork a background thread running the app provided
fetchMessagesThenExit :: DeadpanApp a -> DeadpanApp a Source
Runs fetchMessages and kills the thread when the supplied app finishes.
Note: Any DeadpanApp calls made after this one will not be able to interact with server-sent messages.
fetchMessages :: DeadpanApp ThreadId Source
Continuously pull down messages from the server in a background thread and respond to each message with the callback set. Returns a ThreadId so that this can be killed explicitly before the program exits in order to avoid the "recv: invalid argument (Bad file descriptor)" error.
respondToMessage :: Lookup Callback -> Maybe EJsonValue -> DeadpanApp () Source
Loop through all callbacks
Each callback is responsible for discarding messages that it doesn't care about...
module Data.EJson
module Web.DDP.Deadpan.GUID
data Text :: *
A space efficient, packed, unboxed Unicode text type.