Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
A socket between a web page and haskell, based on the box library.
Synopsis
- socketPage :: Page
- defaultSocketPage :: Page
- data SocketConfig = SocketConfig {}
- defaultSocketConfig :: SocketConfig
- serveSocketBox :: SocketConfig -> Page -> Box IO Text Text -> IO ()
- type CodeBox = Box IO [Code] (ByteString, ByteString)
- type CoCodeBox = Codensity IO (Box IO [Code] (ByteString, ByteString))
- data CodeBoxConfig = CodeBoxConfig {}
- defaultCodeBoxConfig :: CodeBoxConfig
- codeBox :: CoCodeBox
- codeBoxWith :: CodeBoxConfig -> CoCodeBox
- serveRep :: SharedRep IO a -> (Markup -> [Code]) -> (Either ByteString a -> [Code]) -> CodeBoxConfig -> IO ()
- serveRepWithBox :: SharedRep IO a -> (Markup -> [Code]) -> (Either ByteString a -> [Code]) -> CodeBox -> IO ()
- replaceInput :: Markup -> [Code]
- replaceOutput :: Show a => Either ByteString a -> [Code]
- replaceOutput_ :: Show a => Either ByteString a -> [Code]
- sharedStream :: Monad m => SharedRep m a -> Committer m Markup -> Committer m (Either ByteString a) -> Emitter m (ByteString, ByteString) -> m ()
- data PlayConfig = PlayConfig {}
- defaultPlayConfig :: PlayConfig
- repPlayConfig :: PlayConfig -> SharedRep IO PlayConfig
- servePlayStream :: PlayConfig -> CodeBoxConfig -> CoEmitter IO (Gap, [Code]) -> IO ()
- servePlayStreamWithBox :: PlayConfig -> CoEmitter IO (Gap, [Code]) -> CodeBox -> IO ()
- data Code
- code :: Code -> ByteString
- console :: ByteString -> ByteString
- val :: ByteString -> ByteString
- replace :: ByteString -> ByteString -> ByteString
- append :: ByteString -> ByteString -> ByteString
- clean :: ByteString -> ByteString
- webSocket :: Js
- refreshJsbJs :: Js
- preventEnter :: Js
- runScriptJs :: Js
Documentation
socketPage :: Page Source #
Page with all the trimmings for a sharedRep Box
defaultSocketPage :: Page Source #
Bootstrapped base page for a web socket.
data SocketConfig Source #
Socket configuration
>>>
defaultSocketConfig
SocketConfig {host = "127.0.0.1", port = 9160, path = "/"}
Instances
defaultSocketConfig :: SocketConfig Source #
official default
serveSocketBox :: SocketConfig -> Page -> Box IO Text Text -> IO () Source #
bidirectional websocket serving a Box
type CodeBox = Box IO [Code] (ByteString, ByteString) Source #
A common Box pattern. [Code] is typically committed to the websocket and key-value elements, representing changes to the shared objects that are in the Dom are emitted.
type CoCodeBox = Codensity IO (Box IO [Code] (ByteString, ByteString)) Source #
Codensity CodeBox
data CodeBoxConfig Source #
Configuration for a CodeBox serving.
Instances
Generic CodeBoxConfig Source # | |
Defined in Web.Rep.Socket type Rep CodeBoxConfig :: Type -> Type # from :: CodeBoxConfig -> Rep CodeBoxConfig x # to :: Rep CodeBoxConfig x -> CodeBoxConfig # | |
type Rep CodeBoxConfig Source # | |
Defined in Web.Rep.Socket type Rep CodeBoxConfig = D1 ('MetaData "CodeBoxConfig" "Web.Rep.Socket" "web-rep-0.12.3.0-E5Upzoz1WN63xERmXwdVK2" 'False) (C1 ('MetaCons "CodeBoxConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "codeBoxSocket") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SocketConfig) :*: S1 ('MetaSel ('Just "codeBoxPage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Page)) :*: (S1 ('MetaSel ('Just "codeBoxCommitterQueue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Queue [Code])) :*: S1 ('MetaSel ('Just "codeBoxEmitterQueue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Queue (ByteString, ByteString)))))) |
defaultCodeBoxConfig :: CodeBoxConfig Source #
official default config.
codeBoxWith :: CodeBoxConfig -> CoCodeBox Source #
Turn a configuration into a live (Codensity) CodeBox
serveRep :: SharedRep IO a -> (Markup -> [Code]) -> (Either ByteString a -> [Code]) -> CodeBoxConfig -> IO () Source #
serve a SharedRep
serveRepWithBox :: SharedRep IO a -> (Markup -> [Code]) -> (Either ByteString a -> [Code]) -> CodeBox -> IO () Source #
non-codensity sharedRep server.
replaceInput :: Markup -> [Code] Source #
Convert HTML representation to Code, replacing the input section of a page.
replaceOutput :: Show a => Either ByteString a -> [Code] Source #
Convert (typically parsed representation) to Code, replacing the output section of a page, and appending errors.
replaceOutput_ :: Show a => Either ByteString a -> [Code] Source #
Convert (typically parsed representation) to Code, replacing the output section of a page, and throwing away errors.
sharedStream :: Monad m => SharedRep m a -> Committer m Markup -> Committer m (Either ByteString a) -> Emitter m (ByteString, ByteString) -> m () Source #
Stream a SharedRep
data PlayConfig Source #
Configuration to control a (re)play of an emitter with a Gap (timing) element.
Instances
Generic PlayConfig Source # | |
Defined in Web.Rep.Socket type Rep PlayConfig :: Type -> Type # from :: PlayConfig -> Rep PlayConfig x # to :: Rep PlayConfig x -> PlayConfig # | |
Show PlayConfig Source # | |
Defined in Web.Rep.Socket showsPrec :: Int -> PlayConfig -> ShowS # show :: PlayConfig -> String # showList :: [PlayConfig] -> ShowS # | |
Eq PlayConfig Source # | |
Defined in Web.Rep.Socket (==) :: PlayConfig -> PlayConfig -> Bool # (/=) :: PlayConfig -> PlayConfig -> Bool # | |
type Rep PlayConfig Source # | |
Defined in Web.Rep.Socket type Rep PlayConfig = D1 ('MetaData "PlayConfig" "Web.Rep.Socket" "web-rep-0.12.3.0-E5Upzoz1WN63xERmXwdVK2" 'False) (C1 ('MetaCons "PlayConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "playPause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "playSpeed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "playFrame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) |
defaultPlayConfig :: PlayConfig Source #
Start on pause at normal speed and at frame 0.
repPlayConfig :: PlayConfig -> SharedRep IO PlayConfig Source #
representation of a PlayConfig
servePlayStream :: PlayConfig -> CodeBoxConfig -> CoEmitter IO (Gap, [Code]) -> IO () Source #
Serve an emitter controlled by a PlayConfig representation.
servePlayStreamWithBox :: PlayConfig -> CoEmitter IO (Gap, [Code]) -> CodeBox -> IO () Source #
Serve an emitter controlled by a PlayConfig representation, with an explicit CodeBox.
A simple schema for code that communicates changes to a Html page via JS code.
Replace ByteString ByteString | |
Append ByteString ByteString | |
Console ByteString | |
Eval ByteString | |
Val ByteString |
Instances
code :: Code -> ByteString Source #
Convert Code
to a ByteString
console :: ByteString -> ByteString Source #
write to the console
val :: ByteString -> ByteString Source #
send arbitrary byestrings.
replace :: ByteString -> ByteString -> ByteString Source #
replace a container and run any embedded scripts
append :: ByteString -> ByteString -> ByteString Source #
append to a container and run any embedded scripts
clean :: ByteString -> ByteString Source #
Double backslash newline and single quotes.
refreshJsbJs :: Js Source #
Event hooks that may need to be reattached given dynamic content creation.
preventEnter :: Js Source #
prevent the Enter key from triggering an event
runScriptJs :: Js Source #
script injection js.
See https://ghinda.net/article/script-tags/ for why this might be needed.