Safe Haskell | None |
---|---|
Language | Haskell2010 |
Usually, it makes the most sense to run a Myxine application using the
Page
abstraction in the main module. However, this reactive
model-view-controller approach may not be appropriate for all needs. The
functions below are a one-to-one mapping to the API of the Myxine server.
Like the Myxine server API itself, this interface has a small surface area. You
can send a new page Update
using update
, you can loop over all page
events using events
, and you can evaluate raw JavaScript using
evaluateJs
.
Synopsis
- data PageLocation
- pagePort :: PagePort -> PageLocation
- data PagePort
- pagePath :: PagePath -> PageLocation
- data PagePath
- data Update
- data EventList
- = AllEvents
- | SomeEvents (NonEmpty (Some EventType))
- data PageEvent where
- data Target
- tag :: Target -> Text
- attribute :: Text -> Target -> Maybe Text
- data PageContent
- pageBody :: Text -> PageContent
- pageTitle :: Text -> PageContent
- pageContentBody :: PageContent -> Text
- pageContentTitle :: PageContent -> Maybe Text
- update :: PageLocation -> Update -> IO ()
- events :: PageLocation -> IO (EventList -> IO PageEvent)
- data JavaScript
- evaluateJs :: FromJSON a => PageLocation -> JavaScript -> IO a
- newtype JsException = JsException String
- data ProtocolException
- data Some (tag :: k -> Type) :: forall k. (k -> Type) -> Type where
- module Myxine.Event
Page locations on localhost
data PageLocation Source #
The options for connecting to the Myxine server. This is an opaque
Monoid
: set options by combining pagePort
and/or pagePath
using their
Semigroup
instance.
Instances
pagePort :: PagePort -> PageLocation Source #
Set the port to a non-default port. This is only necessary when Myxine is running on a non-default port also.
A local port at which the server is expected to be running. Create one
using an integer literal or fromInteger
.
pagePath :: PagePath -> PageLocation Source #
Set the path to something other than the default of /
.
A path at "localhost/..." at which to perform some action. Create one using
a string literal or fromString
.
Sending updates to pages and getting events from pages
A full page update as ready-to-send to the Myxine server.
Dynamic | A dynamic page which can be updated live |
Static | A static file which is hosted precisely as specified |
|
A list of event types to listen for: either all events, or a specific list of events.
AllEvents | Listen for all events |
SomeEvents (NonEmpty (Some EventType)) | Listen only for these events |
A PageEvent
is an event that occurred in the browser: a triple of the
EventType
, any associated properties of the event (this varies depending on
the event type), and the list of Target
s of the event, in order from most
to least specific.
A Target
is a description of a single element node in the browser. When
an event fires in the browser, Myxine tracks the path of nodes it touches,
from the most specific element all the way up to the root. Each event handler
is given access to this [
, ordered from most to least specific.Target
]
For any Target
, you can query the value of any of an attribute
, or you
can ask for the tag
of that element.
Instances
Eq Target Source # | |
Ord Target Source # | |
Show Target Source # | |
Generic Target Source # | |
FromJSON Target Source # | |
type Rep Target Source # | |
Defined in Myxine.Target type Rep Target = D1 (MetaData "Target" "Myxine.Target" "myxine-client-0.0.1.2-6kXF4ekqOPD2H2JfgV0YV4" False) (C1 (MetaCons "Target" PrefixI True) (S1 (MetaSel (Just "tagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "attributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text)))) |
tag :: Target -> Text Source #
Get the name of the HTML tag for this Target
. Note that unlike in the
browser itself, Myxine returns tag names in lower case, rather than upper.
attribute :: Text -> Target -> Maybe Text Source #
Get the value, if any, of some named attribute of a Target
.
data PageContent Source #
The view of a page, as rendered in the browser. Create page content with
pageBody
and pageTitle
, and combine content using the Semigroup
instance.
Note: The Semigroup
instance for PageContent
takes the last specified
pageTitle
(if any), and concatenates in order each specified pageBody
.
Instances
pageBody :: Text -> PageContent Source #
Create a rendered PageContent
with an empty title
and the specified
text as its body
.
pageTitle :: Text -> PageContent Source #
Create a rendered PageContent
with an empty body
and the specified
text as its title
.
pageContentBody :: PageContent -> Text Source #
Get the rendered body
of a PageContent
.
pageContentTitle :: PageContent -> Maybe Text Source #
Get the title
of a PageContent
.
:: PageLocation | The location of the page to update |
-> Update | The new content of the page to display |
-> IO () |
:: PageLocation | The location of the page to listen for events from. |
-> IO (EventList -> IO PageEvent) | An action which polls for the next event matching the given list, and blocks until such an event arrives. |
Given a page location and list of events, create an IO action that acts as a "stream" of sequential events matching the event list. The state maintained within the stream is used to coordinate with the server to return a sequential event from each poll of the stream. It is strongly recommended to create only one such "get next" action and to poll it repeatedly.
Calls to the "get next" action returned will block until the next event matching the given description is available. Provided that the "get next" action is polled with sufficient frequency, no events will be missed, as the server maintains an internal fixed-size buffer of events to distribute to lagging clients. However, significantly lagging clients may observe dropped events. It is therefore best practice to eagerly collect events in a separate tight-looping thread and buffer them client-side.
Evaluating raw JavaScript in the context of a page
data JavaScript Source #
A piece of raw JavaScript to evaluate: either an expression or a block of
statements. Expressions need not terminate with a return
statement but
cannot span multiple lines; block need to have an explicit return
, but can
contain multiple statements and lines.
JsExpression Text | A JavaScript expression |
JsBlock Text | A block of JavaScript statements |
Instances
Eq JavaScript Source # | |
Defined in Myxine.Direct (==) :: JavaScript -> JavaScript -> Bool # (/=) :: JavaScript -> JavaScript -> Bool # | |
Ord JavaScript Source # | |
Defined in Myxine.Direct compare :: JavaScript -> JavaScript -> Ordering # (<) :: JavaScript -> JavaScript -> Bool # (<=) :: JavaScript -> JavaScript -> Bool # (>) :: JavaScript -> JavaScript -> Bool # (>=) :: JavaScript -> JavaScript -> Bool # max :: JavaScript -> JavaScript -> JavaScript # min :: JavaScript -> JavaScript -> JavaScript # | |
Show JavaScript Source # | |
Defined in Myxine.Direct showsPrec :: Int -> JavaScript -> ShowS # show :: JavaScript -> String # showList :: [JavaScript] -> ShowS # |
:: FromJSON a | |
=> PageLocation | The location of the page in which to evaluate the JavaScript |
-> JavaScript | The JavaScript to evaluate: either a |
-> IO a |
Evaluate some raw JavaScript in the context of a given page.
Returns either a deserialized Haskell type, or throws a JsException
containing a human-readable string describing any error that occurred.
Possible errors include:
Possible errors, which manifest as JsException
s:
- Any exception in the given JavaScript
- Invalid JSON response for the result type inferred (use
Value
if you don't know what shape of data you're waiting to receive).
Further caveats:
- JavaScript
undefined
is translated tonull
in the results - Return types are limited to those which can be serialized via
JSON.stringify,
which does not work for cyclic objects (like
window
,document
, and all DOM nodes), and may fail to serialize some properties for other non-scalar values. If you want to return a non-scalar value like a list or dictionary, construct it explicitly yourself by copying from the fields of the object you're interested in. - You're evaluating an arbitrary string as JavaScript, which means there are no guarantees about type safety or purity.
- It is possible that you could break the Myxine server code running in the page that makes it update properly, or hang the page by passing a non-terminating piece of code.
- Any modifications you make to the DOM will be immediately overwritten on the next re-draw of the page. Don't do this.
- If there are multiple browser windows pointed at the same page, and the result of your query differs between them, it's nondeterministic which result you get back.
newtype JsException Source #
An exception thrown by evaluating JavaScript. This may be a deserialization error, or an error that occurred in the JavaScript runtime itself.
Instances
Eq JsException Source # | |
Defined in Myxine.Direct (==) :: JsException -> JsException -> Bool # (/=) :: JsException -> JsException -> Bool # | |
Ord JsException Source # | |
Defined in Myxine.Direct compare :: JsException -> JsException -> Ordering # (<) :: JsException -> JsException -> Bool # (<=) :: JsException -> JsException -> Bool # (>) :: JsException -> JsException -> Bool # (>=) :: JsException -> JsException -> Bool # max :: JsException -> JsException -> JsException # min :: JsException -> JsException -> JsException # | |
Show JsException Source # | |
Defined in Myxine.Direct showsPrec :: Int -> JsException -> ShowS # show :: JsException -> String # showList :: [JsException] -> ShowS # | |
Exception JsException Source # | |
Defined in Myxine.Direct |
Exceptions thrown if the server misbehaves
data ProtocolException Source #
If the response from the server cannot be processed appropriately, this exception is thrown. This should never happen in ordinary circumstances; if it does, your version of the client library may mismatch the version of the Myxine server you are running, or there may be a bug in the Myxine server or this library.
If you encounter this exception in the wild, please file a bug report at https://github.com/kwf/myxine/issues/new. Thanks!
MyxineProtocolException String | |
MyxineServerVersionClashException Version | |
MyxineUnknownServerException |
Instances
Eq ProtocolException Source # | |
Defined in Myxine.Direct (==) :: ProtocolException -> ProtocolException -> Bool # (/=) :: ProtocolException -> ProtocolException -> Bool # | |
Ord ProtocolException Source # | |
Defined in Myxine.Direct compare :: ProtocolException -> ProtocolException -> Ordering # (<) :: ProtocolException -> ProtocolException -> Bool # (<=) :: ProtocolException -> ProtocolException -> Bool # (>) :: ProtocolException -> ProtocolException -> Bool # (>=) :: ProtocolException -> ProtocolException -> Bool # max :: ProtocolException -> ProtocolException -> ProtocolException # min :: ProtocolException -> ProtocolException -> ProtocolException # | |
Show ProtocolException Source # | |
Defined in Myxine.Direct showsPrec :: Int -> ProtocolException -> ShowS # show :: ProtocolException -> String # showList :: [ProtocolException] -> ShowS # | |
Exception ProtocolException Source # | |
Defined in Myxine.Direct |
The Some
existential
data Some (tag :: k -> Type) :: forall k. (k -> Type) -> Type where #
Existential. This is type is useful to hide GADTs' parameters.
>>>
data Tag :: * -> * where TagInt :: Tag Int; TagBool :: Tag Bool
>>>
instance GShow Tag where gshowsPrec _ TagInt = showString "TagInt"; gshowsPrec _ TagBool = showString "TagBool"
>>>
classify s = case s of "TagInt" -> [mkGReadResult TagInt]; "TagBool" -> [mkGReadResult TagBool]; _ -> []
>>>
instance GRead Tag where greadsPrec _ s = [ (r, rest) | (con, rest) <- lex s, r <- classify con ]
You can either use PatternSynonyms
(available with GHC >= 8.0)
>>>
let x = Some TagInt
>>>
x
Some TagInt
>>>
case x of { Some TagInt -> "I"; Some TagBool -> "B" } :: String
"I"
or you can use functions
>>>
let y = mkSome TagBool
>>>
y
Some TagBool
>>>
withSome y $ \y' -> case y' of { TagInt -> "I"; TagBool -> "B" } :: String
"B"
The implementation of mapSome
is safe.
>>>
let f :: Tag a -> Tag a; f TagInt = TagInt; f TagBool = TagBool
>>>
mapSome f y
Some TagBool
but you can also use:
>>>
withSome y (mkSome . f)
Some TagBool
>>>
read "Some TagBool" :: Some Tag
Some TagBool
>>>
read "mkSome TagInt" :: Some Tag
Some TagInt
module Myxine.Event