web-rep-0.10.0: representations of a web page
Safe HaskellSafe-Inferred
LanguageHaskell2010

Web.Rep.Socket

Description

A socket between a web page and haskell, based on the box library.

Synopsis

Documentation

socketPage :: Page Source #

Page with all the trimmings for a sharedRep Box

data SocketConfig Source #

Socket configuration

>>> defaultSocketConfig
SocketConfig {host = "127.0.0.1", port = 9160, path = "/"}

Constructors

SocketConfig 

Fields

Instances

Instances details
Generic SocketConfig Source # 
Instance details

Defined in Web.Rep.Socket

Associated Types

type Rep SocketConfig :: Type -> Type #

Show SocketConfig Source # 
Instance details

Defined in Web.Rep.Socket

Eq SocketConfig Source # 
Instance details

Defined in Web.Rep.Socket

type Rep SocketConfig Source # 
Instance details

Defined in Web.Rep.Socket

type Rep SocketConfig = D1 ('MetaData "SocketConfig" "Web.Rep.Socket" "web-rep-0.10.0-14Ea0acHNZAIpwuRPiHk6A" 'False) (C1 ('MetaCons "SocketConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "host") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "port") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

serveSocketBox :: SocketConfig -> Page -> Box IO Text Text -> IO () Source #

bidirectional websocket serving a Box

type CodeBox = Box IO [Code] (Text, Text) 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] (Text, Text)) Source #

Codensity CodeBox

data CodeBoxConfig Source #

Configuration for a CodeBox serving.

Instances

Instances details
Generic CodeBoxConfig Source # 
Instance details

Defined in Web.Rep.Socket

Associated Types

type Rep CodeBoxConfig :: Type -> Type #

type Rep CodeBoxConfig Source # 
Instance details

Defined in Web.Rep.Socket

type Rep CodeBoxConfig = D1 ('MetaData "CodeBoxConfig" "Web.Rep.Socket" "web-rep-0.10.0-14Ea0acHNZAIpwuRPiHk6A" 'False) (C1 ('MetaCons "CodeBoxConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "codeBoxSocket") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SocketConfig) :*: S1 ('MetaSel ('Just "codeBoxPage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Page)) :*: (S1 ('MetaSel ('Just "codeBoxCommitterQueue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Queue [Code])) :*: S1 ('MetaSel ('Just "codeBoxEmitterQueue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Queue (Text, Text))))))

defaultCodeBoxConfig :: CodeBoxConfig Source #

official default config.

codeBox :: CoCodeBox Source #

Turn the default configuration into a live (Codensity) CodeBox

codeBoxWith :: CodeBoxConfig -> CoCodeBox Source #

Turn a configuration into a live (Codensity) CodeBox

serveRep :: SharedRep IO a -> (Html () -> [Code]) -> (Either Text a -> [Code]) -> CodeBoxConfig -> IO () Source #

serve a SharedRep

serveRepWithBox :: SharedRep IO a -> (Html () -> [Code]) -> (Either Text a -> [Code]) -> CodeBox -> IO () Source #

non-codensity sharedRep server.

replaceInput :: Html () -> [Code] Source #

Convert HTML representation to Code, replacing the input section of a page.

replaceOutput :: Show a => Either Text a -> [Code] Source #

Convert (typically parsed representation) to Code, replacing the output section of a page, and appending errors.

replaceOutput_ :: Show a => Either Text 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 (Html ()) -> Committer m (Either Text a) -> Emitter m (Text, Text) -> m () Source #

Stream a SharedRep

data PlayConfig Source #

Configuration to control a (re)play of an emitter with a Gap (timing) element.

Constructors

PlayConfig 

Instances

Instances details
Generic PlayConfig Source # 
Instance details

Defined in Web.Rep.Socket

Associated Types

type Rep PlayConfig :: Type -> Type #

Show PlayConfig Source # 
Instance details

Defined in Web.Rep.Socket

Eq PlayConfig Source # 
Instance details

Defined in Web.Rep.Socket

type Rep PlayConfig Source # 
Instance details

Defined in Web.Rep.Socket

type Rep PlayConfig = D1 ('MetaData "PlayConfig" "Web.Rep.Socket" "web-rep-0.10.0-14Ea0acHNZAIpwuRPiHk6A" 'False) (C1 ('MetaCons "PlayConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "playPause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "playSpeed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "playFrame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (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.

parserJ :: Parser (Text, Text) Source #

{"event":{"element":"textid","value":"abcdees"}}

data Code Source #

Instances

Instances details
Generic Code Source # 
Instance details

Defined in Web.Rep.Socket

Associated Types

type Rep Code :: Type -> Type #

Methods

from :: Code -> Rep Code x #

to :: Rep Code x -> Code #

Read Code Source # 
Instance details

Defined in Web.Rep.Socket

Show Code Source # 
Instance details

Defined in Web.Rep.Socket

Methods

showsPrec :: Int -> Code -> ShowS #

show :: Code -> String #

showList :: [Code] -> ShowS #

Eq Code Source # 
Instance details

Defined in Web.Rep.Socket

Methods

(==) :: Code -> Code -> Bool #

(/=) :: Code -> Code -> Bool #

type Rep Code Source # 
Instance details

Defined in Web.Rep.Socket

replace :: Text -> Text -> Text Source #

replace a container and run any embedded scripts

append :: Text -> Text -> Text Source #

append to a container and run any embedded scripts

webSocket :: RepJs Source #

create a web socket for event data

refreshJsbJs :: RepJs Source #

Event hooks that may need to be reattached given dynamic content creation.

preventEnter :: RepJs Source #

prevent the Enter key from triggering an event

runScriptJs :: RepJs Source #

script injection js.

See https://ghinda.net/article/script-tags/ for why this might be needed.