Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype JavaScript = JavaScript Text
- class Command f
- internalCommand :: Command f => JavaScript -> f ()
- internalConstructor :: Command f => JavaScript -> f (RemoteValue a)
- class Procedure f
- internalProcedure :: (Procedure f, FromJSON a) => JavaScript -> f a
- data Primitive :: * -> * where
- Command :: JavaScript -> Primitive ()
- Procedure :: FromJSON a => JavaScript -> Primitive a
- Constructor :: JavaScript -> Primitive (RemoteValue a)
- newtype RemoteValue a = RemoteValue Int
- var :: RemoteValue a -> JavaScript
- newtype Packet a = Packet (AF Primitive a)
- data AF :: (* -> *) -> * -> * where
- newtype RemoteMonad a = RemoteMonad (M Primitive a)
- evalAF :: Applicative f => (forall x. m x -> f x) -> AF m a -> f a
- concatAF :: (forall x. m x -> Maybe b) -> AF m a -> [b]
- data M :: (* -> *) -> * -> * where
- evalM :: Monad f => (forall x. m x -> f x) -> M m a -> f a
JavaScript
newtype JavaScript Source #
Instances
Show JavaScript Source # | |
Defined in Network.JavaScript.Internal showsPrec :: Int -> JavaScript -> ShowS # show :: JavaScript -> String # showList :: [JavaScript] -> ShowS # | |
IsString JavaScript Source # | |
Defined in Network.JavaScript.Internal fromString :: String -> JavaScript # | |
Semigroup JavaScript Source # | |
Defined in Network.JavaScript.Internal (<>) :: JavaScript -> JavaScript -> JavaScript # sconcat :: NonEmpty JavaScript -> JavaScript # stimes :: Integral b => b -> JavaScript -> JavaScript # | |
Monoid JavaScript Source # | |
Defined in Network.JavaScript.Internal mempty :: JavaScript # mappend :: JavaScript -> JavaScript -> JavaScript # mconcat :: [JavaScript] -> JavaScript # |
Commands
Instances
Command RemoteMonad Source # | |
Defined in Network.JavaScript.Internal internalCommand :: JavaScript -> RemoteMonad () Source # internalConstructor :: JavaScript -> RemoteMonad (RemoteValue a) Source # | |
Command Packet Source # | |
Defined in Network.JavaScript.Internal internalCommand :: JavaScript -> Packet () Source # internalConstructor :: JavaScript -> Packet (RemoteValue a) Source # |
internalCommand :: Command f => JavaScript -> f () Source #
internalConstructor :: Command f => JavaScript -> f (RemoteValue a) Source #
Procedures
Instances
Procedure RemoteMonad Source # | |
Defined in Network.JavaScript.Internal internalProcedure :: FromJSON a => JavaScript -> RemoteMonad a Source # | |
Procedure Packet Source # | |
Defined in Network.JavaScript.Internal internalProcedure :: FromJSON a => JavaScript -> Packet a Source # |
internalProcedure :: (Procedure f, FromJSON a) => JavaScript -> f a Source #
Primitives and (Remote) Values
data Primitive :: * -> * where Source #
Command :: JavaScript -> Primitive () | |
Procedure :: FromJSON a => JavaScript -> Primitive a | |
Constructor :: JavaScript -> Primitive (RemoteValue a) |
newtype RemoteValue a Source #
Instances
var :: RemoteValue a -> JavaScript Source #
generate the text for a RemoteValue. They can be used as assignment targets as well, but exposes the JavaScript scoping semantics.
(Applicative) Packets
The Remote Applicative Packet
Instances
Functor Packet Source # | |
Applicative Packet Source # | |
Procedure Packet Source # | |
Defined in Network.JavaScript.Internal internalProcedure :: FromJSON a => JavaScript -> Packet a Source # | |
Command Packet Source # | |
Defined in Network.JavaScript.Internal internalCommand :: JavaScript -> Packet () Source # internalConstructor :: JavaScript -> Packet (RemoteValue a) Source # |
newtype RemoteMonad a Source #
The Remote Monad
RemoteMonad (M Primitive a) |
Instances
evalAF :: Applicative f => (forall x. m x -> f x) -> AF m a -> f a Source #