Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Config
- data ConfigSSL = ConfigSSL {}
- defaultConfig :: Config
- startGUI :: Config -> (Window -> UI ()) -> IO ()
- loadFile :: String -> FilePath -> UI String
- loadDirectory :: FilePath -> UI String
- data UI a
- runUI :: Window -> UI a -> IO a
- class Monad m => MonadUI m where
- askWindow :: UI Window
- liftIOLater :: IO () -> UI ()
- module Control.Monad.IO.Class
- module Control.Monad.Fix
- data Window
- title :: WriteAttr Window String
- data Element
- getWindow :: Element -> IO Window
- mkElement :: String -> UI Element
- mkElementNamespace :: Maybe String -> String -> UI Element
- delete :: Element -> UI ()
- string :: String -> UI Element
- getHead :: Window -> UI Element
- getBody :: Window -> UI Element
- (#+) :: UI Element -> [UI Element] -> UI Element
- children :: WriteAttr Element [Element]
- text :: WriteAttr Element String
- html :: WriteAttr Element String
- attr :: String -> WriteAttr Element String
- style :: WriteAttr Element [(String, String)]
- value :: Attr Element String
- getElementsByTagName :: Window -> String -> UI [Element]
- getElementById :: Window -> String -> UI (Maybe Element)
- getElementsByClassName :: Window -> String -> UI [Element]
- grid :: [[UI Element]] -> UI Element
- row :: [UI Element] -> UI Element
- column :: [UI Element] -> UI Element
- type EventData = Value
- domEvent :: String -> Element -> Event EventData
- unsafeFromJSON :: FromJSON a => EventData -> a
- disconnect :: Window -> Event ()
- on :: (element -> Event a) -> element -> (a -> UI void) -> UI ()
- onEvent :: Event a -> (a -> UI void) -> UI (UI ())
- onChanges :: Behavior a -> (a -> UI void) -> UI ()
- (<$) :: Functor f => a -> f b -> f a
- class Functor f => Applicative (f :: Type -> Type) where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- class Applicative f => Alternative (f :: Type -> Type) where
- newtype ZipList a = ZipList {
- getZipList :: [a]
- newtype WrappedMonad (m :: Type -> Type) a = WrapMonad {
- unwrapMonad :: m a
- newtype WrappedArrow (a :: Type -> Type -> Type) b c = WrapArrow {
- unwrapArrow :: a b c
- optional :: Alternative f => f a -> f (Maybe a)
- newtype Const a (b :: k) = Const {
- getConst :: a
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- liftA :: Applicative f => (a -> b) -> f a -> f b
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- data Tidings a
- type Handler a = a -> IO ()
- data Behavior a
- data Event a
- newEvent :: IO (Event a, Handler a)
- newEventsNamed :: Ord name => Handler (name, Event a, Handler a) -> IO (name -> Event a)
- register :: Event a -> Handler a -> IO (IO ())
- currentValue :: MonadIO m => Behavior a -> m a
- unsafeMapIO :: (a -> IO b) -> Event a -> Event b
- never :: Event a
- filterJust :: Event (Maybe a) -> Event a
- unionWith :: (a -> a -> a) -> Event a -> Event a -> Event a
- apply :: Behavior (a -> b) -> Event a -> Event b
- (<@>) :: Behavior (a -> b) -> Event a -> Event b
- (<@) :: Behavior a -> Event b -> Event a
- accumB :: MonadIO m => a -> Event (a -> a) -> m (Behavior a)
- stepper :: MonadIO m => a -> Event a -> m (Behavior a)
- accumE :: MonadIO m => a -> Event (a -> a) -> m (Event a)
- filterE :: (a -> Bool) -> Event a -> Event a
- filterApply :: Behavior (a -> Bool) -> Event a -> Event a
- whenE :: Behavior Bool -> Event a -> Event a
- split :: Event (Either a b) -> (Event a, Event b)
- unions :: [Event a] -> Event [a]
- concatenate :: [a -> a] -> a -> a
- mapAccum :: MonadIO m => acc -> Event (acc -> (x, acc)) -> m (Event x, Behavior acc)
- tidings :: Behavior a -> Event a -> Tidings a
- (#) :: a -> (a -> b) -> b
- (#.) :: UI Element -> String -> UI Element
- type Attr x a = ReadWriteAttr x a a
- type WriteAttr x i = ReadWriteAttr x i ()
- type ReadAttr x o = ReadWriteAttr x () o
- data ReadWriteAttr x i o = ReadWriteAttr {}
- set :: ReadWriteAttr x i o -> i -> UI x -> UI x
- sink :: ReadWriteAttr x i o -> Behavior i -> UI x -> UI x
- get :: ReadWriteAttr x i o -> x -> UI o
- mkReadWriteAttr :: (x -> UI o) -> (i -> x -> UI ()) -> ReadWriteAttr x i o
- mkWriteAttr :: (i -> x -> UI ()) -> WriteAttr x i
- mkReadAttr :: (x -> UI o) -> ReadAttr x o
- bimapAttr :: (i' -> i) -> (o -> o') -> ReadWriteAttr x i o -> ReadWriteAttr x i' o'
- fromObjectProperty :: (FromJS a, ToJS a) => String -> Attr Element a
- class Widget w where
- getElement :: w -> Element
- element :: MonadIO m => Widget w => w -> m Element
- widget :: Widget w => w -> UI w
- debug :: String -> UI ()
- timestamp :: UI ()
- class ToJS a
- class FFI a
- data JSFunction a
- ffi :: FFI a => String -> a
- runFunction :: JSFunction () -> UI ()
- callFunction :: JSFunction a -> UI a
- data CallBufferMode
- setCallBufferMode :: CallBufferMode -> UI ()
- flushCallBuffer :: UI ()
- ffiExport :: IsHandler a => a -> UI JSObject
- toJSObject :: Element -> JSObject
- liftJSWindow :: (Window -> IO a) -> UI a
- fromJQueryProp :: String -> (Value -> a) -> (a -> Value) -> Attr Element a
Synopsis
Core functionality of the Threepenny GUI library.
Server
To display the user interface, you have to start a server using startGUI
.
Then, visit the URL http://localhost:8023/ in your browser
(assuming that you use the default server configuration defaultConfig
,
or have set the port number to jsPort=Just 8023
.)
The server is multithreaded. FFI calls can be made concurrently, but events are handled sequentially.
FFI calls can be buffered,
so in some circumstances, it may happen that you manipulate the browser window,
but the effect is not immediately visible.
See CallBufferMode
for more information.
Static configuration for a Foreign.JavaScript server.
This is a record type which has the following fields:
jsPort :: Maybe Int
Port number.
Nothing
means that the port number is read from the environment variablePORT
. Alternatively, port8023
is used if this variable is not set.jsAddr :: Maybe ByteString
Bind address.
Nothing
means that the bind address is read from the environment variableADDR
. Alternatively, address127.0.0.1
is used if this variable is not set.jsCustomHTML :: Maybe FilePath
Custom HTML file to replace the default one.
jsStatic :: Maybe FilePath
Directory that is served under
/static
.jsLog :: ByteString -> IO ()
Function to print a single log message.
jsWindowReloadOnDisconnect :: Bool
Reload the browser window if the connection to the server was dropped accidentally, for instance because the computer was put to sleep and awoken again.
jsCallBufferMode :: CallBufferMode
The initial
CallBufferMode
to use forrunFunction
. It can be changed at any time withsetCallBufferMode
.jsUseSSLBind :: Maybe ConfigSSL
Whether to serve on a HTTPS connection instead of HTTP for improved security.
(For reasons of forward compatibility, the constructor is not exported.)
Static configuration for the SSL version of the Foreign.JavaScript server.
This is a record type which has the following fields:
jsSSLBind :: ByteString
Bind address.
jsSSLCert :: FilePath
Path to SSL certificate file. Example:
cert.pem
.jsSSLChainCert :: Bool
If it is SSL chain certificate file.
jsSSLKey :: FilePath
Path to SSL key file. Example:
key.pem
.jsSSLPort :: ByteString
Port number. Example: 443.
defaultConfig :: Config Source #
Default configuration.
Port from environment variable or 8023
, listening on localhost
,
no custom HTML, no static directory,
logging to stderr,
do reload on disconnect,
buffer FFI calls.
:: Config | Server configuration. |
-> (Window -> UI ()) | Action to run whenever a client browser connects. |
-> IO () |
Start server for GUI sessions.
:: String | MIME type |
-> FilePath | Local path to the file |
-> UI String | Relative URI under which this file is now accessible |
Begin to serve a local file with a given MimeType
under a relative URI.
loadDirectory :: FilePath -> UI String Source #
Make a local directory available under a relative URI.
UI monad
User interface elements are created and manipulated in the UI
monad.
This monad is essentially just a thin wrapper around the familiar IO
monad.
Use the liftIO
function to access IO
operations like reading
and writing from files.
There are several subtle reasons why Threepenny
uses a custom UI
monad instead of the standard IO
monad:
- More convenience when calling JavaScript.
The monad keeps track of a browser
Window
context in which JavaScript function calls are executed. - Recursion for functional reactive programming.
Instances
module Control.Monad.IO.Class
module Control.Monad.Fix
Browser Window
DOM elements
Create and manipulate DOM elements.
mkElementNamespace :: Maybe String -> String -> UI Element Source #
Make a new DOM element with a namespace and a given tag name.
A namespace Nothing
corresponds to the default HTML namespace.
delete :: Element -> UI () Source #
Delete the given element.
This operation removes the element from the browser window DOM and marks it for garbage collection on the Haskell side. The element is unusable afterwards.
NOTE: If you wish to temporarily remove an element from the DOM tree,
change the children
property of its parent element instead.
(#+) :: UI Element -> [UI Element] -> UI Element infixl 8 Source #
Append DOM elements as children to a given element.
value :: Attr Element String Source #
Value attribute of an element.
Particularly relevant for control widgets like input
.
Get all elements of the given tag name.
Get an element by a particular ID.
getElementsByClassName Source #
Get a list of elements by particular class.
Layout
Combinators for quickly creating layouts. They can be adjusted with CSS later on.
grid :: [[UI Element]] -> UI Element Source #
Align given elements in a rectangular grid.
Layout is achieved by using the CSS display:table
property.
The following element tree will be generated
<div class="table"> <div class="table-row"> <div class="table-cell"> ... </div> <div class="table-cell"> ... </div> </div> <div class="table-row"> ... </div> ... </div>
You can customatize the actual layout by assigning an id
to the element
and changing the .table
, .table-row
and table-column
classes in a custom CSS file.
column :: [UI Element] -> UI Element Source #
Align given elements in a column. Special case of grid
.
Events
For a list of predefined events, see Graphics.UI.Threepenny.Events.
type EventData = Value Source #
Events may carry data. At the moment, they may return a single JSON value, as defined in the Data.Aeson module.
:: String | Event name. A full list can be found at
http://www.w3schools.com/jsref/dom_obj_event.asp.
Note that the |
-> Element | Element where the event is to occur. |
-> Event EventData |
Obtain DOM event for a given element.
unsafeFromJSON :: FromJSON a => EventData -> a Source #
Convert event data to a Haskell value. Throws an exception when the data cannot be converted.
disconnect :: Window -> Event () Source #
Event that occurs whenever the client has disconnected, be it by closing the browser window or by exception.
Note: DOM Elements in a browser window that has been closed can no longer be manipulated.
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- Identity
pure
id
<*>
v = v- Composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- Homomorphism
pure
f<*>
pure
x =pure
(f x)- Interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
Example
Used in combination with (
, <$>
)(
can be used to build a record.<*>
)
>>>
data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>>
produceFoo :: Applicative f => f Foo
>>>
produceBar :: Applicative f => f Bar
>>>
produceBaz :: Applicative f => f Baz
>>>
mkState :: Applicative f => f MyState
>>>
mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
liftA2 :: (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*>
and fmap
.
Example
>>>
liftA2 (,) (Just 3) (Just 5)
Just (3,5)
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
Examples
If used in conjunction with the Applicative instance for Maybe
,
you can chain Maybe computations, with a possible "early return"
in case of Nothing
.
>>>
Just 2 *> Just 3
Just 3
>>>
Nothing *> Just 3
Nothing
Of course a more interesting use case would be to have effectful computations instead of just returning pure values.
>>>
import Data.Char
>>>
import Text.ParserCombinators.ReadP
>>>
let p = string "my name is " *> munch1 isAlpha <* eof
>>>
readP_to_S p "my name is Simon"
[("Simon","")]
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Instances
Applicative IResult | |
Applicative Parser | |
Applicative Result | |
Applicative Concurrently | |
Defined in Control.Concurrent.Async pure :: a -> Concurrently a # (<*>) :: Concurrently (a -> b) -> Concurrently a -> Concurrently b # liftA2 :: (a -> b -> c) -> Concurrently a -> Concurrently b -> Concurrently c # (*>) :: Concurrently a -> Concurrently b -> Concurrently b # (<*) :: Concurrently a -> Concurrently b -> Concurrently a # | |
Applicative ZipList | f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: base-2.1 |
Applicative Identity | Since: base-4.8.0.0 |
Applicative First | Since: base-4.8.0.0 |
Applicative Last | Since: base-4.8.0.0 |
Applicative Down | Since: base-4.11.0.0 |
Applicative First | Since: base-4.9.0.0 |
Applicative Last | Since: base-4.9.0.0 |
Applicative Max | Since: base-4.9.0.0 |
Applicative Min | Since: base-4.9.0.0 |
Applicative Dual | Since: base-4.8.0.0 |
Applicative Product | Since: base-4.8.0.0 |
Applicative Sum | Since: base-4.8.0.0 |
Applicative STM | Since: base-4.8.0.0 |
Applicative Par1 | Since: base-4.9.0.0 |
Applicative P | Since: base-4.5.0.0 |
Applicative ReadP | Since: base-4.6.0.0 |
Applicative ReadPrec | Since: base-4.6.0.0 |
Applicative Put | |
Applicative Seq | Since: containers-0.5.4 |
Applicative Tree | |
Applicative DNonEmpty | |
Applicative DList | |
Applicative IO | Since: base-2.1 |
Applicative Array | |
Applicative SmallArray | |
Defined in Data.Primitive.SmallArray pure :: a -> SmallArray a # (<*>) :: SmallArray (a -> b) -> SmallArray a -> SmallArray b # liftA2 :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c # (*>) :: SmallArray a -> SmallArray b -> SmallArray b # (<*) :: SmallArray a -> SmallArray b -> SmallArray a # | |
Applicative Snap | |
Applicative Q | |
Applicative UI Source # | |
Applicative Behavior Source # | |
Applicative Tidings Source # | The applicative instance combines |
Applicative Vector | |
Applicative Id | |
Applicative Stream | |
Applicative NonEmpty | Since: base-4.9.0.0 |
Applicative Maybe | Since: base-2.1 |
Applicative Solo | Since: base-4.15 |
Applicative [] | Since: base-2.1 |
Applicative (Parser i) | |
Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
Arrow a => Applicative (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
Applicative (ST s) | Since: base-2.1 |
Applicative (Either e) | Since: base-3.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Applicative (ST s) | Since: base-4.4.0.0 |
Semigroup a => Applicative (These a) | |
Semigroup a => Applicative (These a) | |
Applicative m => Applicative (ListT m) | |
(Functor m, Monad m) => Applicative (MaybeT m) | |
Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: base-2.1 |
Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
Applicative m => Applicative (Kleisli m a) | Since: base-4.14.0.0 |
Defined in Control.Arrow | |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
Applicative f => Applicative (Rec1 f) | Since: base-4.9.0.0 |
(Applicative f, Monad f) => Applicative (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal pure :: a -> WhenMissing f x a # (<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b # liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c # (*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # (<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a # | |
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) | |
Defined in GHC.Generics.Generically pure :: a -> Generically1 f a # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a # | |
Applicative (Tagged s) | |
(Monoid w, Functor m, Monad m) => Applicative (AccumT w m) | |
Defined in Control.Monad.Trans.Accum | |
(Functor m, Monad m) => Applicative (ErrorT e m) | |
Defined in Control.Monad.Trans.Error | |
(Functor m, Monad m) => Applicative (ExceptT e m) | |
Defined in Control.Monad.Trans.Except | |
Applicative m => Applicative (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
Applicative m => Applicative (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
(Functor m, Monad m) => Applicative (SelectT r m) | |
Defined in Control.Monad.Trans.Select | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, Monad m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.CPS | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict | |
(Monoid a, Monoid b) => Applicative ((,,) a b) | Since: base-4.14.0.0 |
(Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0 |
Monoid c => Applicative (K1 i c :: Type -> Type) | Since: base-4.12.0.0 |
(Monad f, Applicative f) => Applicative (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal pure :: a -> WhenMatched f x y a # (<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c # (*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # (<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Applicative (WhenMissing f k x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal pure :: a -> WhenMissing f k x a # (<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c # (*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # (<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a # | |
Applicative (ContT r m) | |
(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) | Since: base-4.14.0.0 |
Defined in GHC.Base | |
Applicative ((->) r) | Since: base-2.1 |
(Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Applicative f, Applicative g) => Applicative (f :.: g) | Since: base-4.9.0.0 |
Applicative f => Applicative (M1 i c f) | Since: base-4.9.0.0 |
(Monad f, Applicative f) => Applicative (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal pure :: a -> WhenMatched f k x y a # (<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c # (*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # (<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a # | |
(Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.CPS | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Strict |
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an
Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
Lists, but with an Applicative
functor based on zipping.
ZipList | |
|
Instances
Foldable ZipList | Since: base-4.9.0.0 |
Defined in Control.Applicative fold :: Monoid m => ZipList m -> m # foldMap :: Monoid m => (a -> m) -> ZipList a -> m # foldMap' :: Monoid m => (a -> m) -> ZipList a -> m # foldr :: (a -> b -> b) -> b -> ZipList a -> b # foldr' :: (a -> b -> b) -> b -> ZipList a -> b # foldl :: (b -> a -> b) -> b -> ZipList a -> b # foldl' :: (b -> a -> b) -> b -> ZipList a -> b # foldr1 :: (a -> a -> a) -> ZipList a -> a # foldl1 :: (a -> a -> a) -> ZipList a -> a # elem :: Eq a => a -> ZipList a -> Bool # maximum :: Ord a => ZipList a -> a # minimum :: Ord a => ZipList a -> a # | |
Traversable ZipList | Since: base-4.9.0.0 |
Alternative ZipList | Since: base-4.11.0.0 |
Applicative ZipList | f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: base-2.1 |
Functor ZipList | Since: base-2.1 |
NFData1 ZipList | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Generic1 ZipList | |
IsList (ZipList a) | Since: base-4.15.0.0 |
Generic (ZipList a) | |
Read a => Read (ZipList a) | Since: base-4.7.0.0 |
Show a => Show (ZipList a) | Since: base-4.7.0.0 |
NFData a => NFData (ZipList a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (ZipList a) | Since: base-4.7.0.0 |
Ord a => Ord (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Rep1 ZipList | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Item (ZipList a) | |
type Rep (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative |
newtype WrappedMonad (m :: Type -> Type) a #
WrapMonad | |
|
Instances
newtype WrappedArrow (a :: Type -> Type -> Type) b c #
WrapArrow | |
|
Instances
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
It is useful for modelling any computation that is allowed to fail.
Examples
Using the Alternative
instance of Control.Monad.Except, the following functions:
>>>
import Control.Monad.Except
>>>
canFail = throwError "it failed" :: Except String Int
>>>
final = return 42 :: Except String Int
Can be combined by allowing the first function to fail:
>>>
runExcept $ canFail *> final
Left "it failed">>>
runExcept $ optional canFail *> final
Right 42
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | |
Unbox a => Vector Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s (Const a b) -> ST s (Vector (Const a b)) # basicUnsafeThaw :: Vector (Const a b) -> ST s (Mutable Vector s (Const a b)) # basicLength :: Vector (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) # basicUnsafeIndexM :: Vector (Const a b) -> Int -> Box (Const a b) # basicUnsafeCopy :: Mutable Vector s (Const a b) -> Vector (Const a b) -> ST s () # | |
Unbox a => MVector MVector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Const a b) -> MVector s (Const a b) # basicOverlaps :: MVector s (Const a b) -> MVector s (Const a b) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Const a b)) # basicInitialize :: MVector s (Const a b) -> ST s () # basicUnsafeReplicate :: Int -> Const a b -> ST s (MVector s (Const a b)) # basicUnsafeRead :: MVector s (Const a b) -> Int -> ST s (Const a b) # basicUnsafeWrite :: MVector s (Const a b) -> Int -> Const a b -> ST s () # basicClear :: MVector s (Const a b) -> ST s () # basicSet :: MVector s (Const a b) -> Const a b -> ST s () # basicUnsafeCopy :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () # basicUnsafeMove :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () # basicUnsafeGrow :: MVector s (Const a b) -> Int -> ST s (MVector s (Const a b)) # | |
FromJSON2 (Const :: Type -> Type -> Type) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON2 (Const :: Type -> TYPE LiftedRep -> Type) | |
Defined in Data.Aeson.Types.ToJSON liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Const a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Const a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Const a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Const a b] -> Encoding # | |
Bifoldable (Const :: Type -> TYPE LiftedRep -> Type) | Since: base-4.10.0.0 |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Eq2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Ord2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] # | |
Show2 (Const :: Type -> TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
NFData2 (Const :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 (Const :: Type -> Type -> Type) | |
Defined in Data.Hashable.Class | |
FromJSON a => FromJSON1 (Const a :: Type -> Type) | |
ToJSON a => ToJSON1 (Const a :: TYPE LiftedRep -> Type) | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Const a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Const a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Const a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Const a a0] -> Encoding # | |
Foldable (Const m :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show a => Show1 (Const a :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
NFData a => NFData1 (Const a :: TYPE LiftedRep -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Const a :: Type -> Type) | |
Defined in Data.Hashable.Class | |
FromJSON a => FromJSON (Const a b) | |
(FromJSON a, FromJSONKey a) => FromJSONKey (Const a b) | |
Defined in Data.Aeson.Types.FromJSON fromJSONKey :: FromJSONKeyFunction (Const a b) # fromJSONKeyList :: FromJSONKeyFunction [Const a b] # | |
ToJSON a => ToJSON (Const a b) | |
Defined in Data.Aeson.Types.ToJSON | |
(ToJSON a, ToJSONKey a) => ToJSONKey (Const a b) | |
Defined in Data.Aeson.Types.ToJSON toJSONKey :: ToJSONKeyFunction (Const a b) # toJSONKeyList :: ToJSONKeyFunction [Const a b] # | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
Generic (Const a b) | |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int # inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
Prim a => Prim (Const a b) | Since: primitive-0.6.5.0 |
Defined in Data.Primitive.Types sizeOf# :: Const a b -> Int# # alignment# :: Const a b -> Int# # indexByteArray# :: ByteArray# -> Int# -> Const a b # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Const a b #) # writeByteArray# :: MutableByteArray# s -> Int# -> Const a b -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Const a b -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Const a b # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Const a b #) # writeOffAddr# :: Addr# -> Int# -> Const a b -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Const a b -> State# s -> State# s # | |
Unbox a => Unbox (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
newtype MVector s (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
newtype Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base |
asum :: (Foldable t, Alternative f) => t (f a) -> f a #
The sum of a collection of actions, generalizing concat
.
asum
is just like msum
, but generalised to Alternative
.
Examples
Basic usage:
>>>
asum [Just "Hello", Nothing, Just "World"]
Just "Hello"
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
Lift a ternary function to actions.
liftA :: Applicative f => (a -> b) -> f a -> f b #
Lift a function to actions.
Equivalent to Functor's fmap
but implemented using only Applicative
's methods:
`liftA f a = pure f * a`
As such this function may be used to implement a Functor
instance from an Applicative
one.
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 #
A variant of <*>
with the arguments reversed.
type Handler a = a -> IO () Source #
An event handler is a function that takes an event value and performs some computation.
Behavior a
represents a value that varies in time. Think of it as
type Behavior a = Time -> a
Event a
represents a stream of events as they occur in time.
Semantically, you can think of Event a
as an infinite list of values
that are tagged with their corresponding time of occurence,
type Event a = [(Time,a)]
newEvent :: IO (Event a, Handler a) Source #
Create a new event. Also returns a function that triggers an event occurrence.
:: Ord name | |
=> Handler (name, Event a, Handler a) | Initialization procedure. |
-> IO (name -> Event a) | Series of events. |
Create a series of events with delayed initialization.
For each name, the initialization handler will be called exactly once when the event is first "brought to life", e.g. when an event handler is registered to it.
register :: Event a -> Handler a -> IO (IO ()) Source #
Register an event Handler
for an Event
.
All registered handlers will be called whenever the event occurs.
When registering an event handler, you will also be given an action that unregisters this handler again.
do unregisterMyHandler <- register event myHandler
FIXME: Unregistering event handlers does not work yet.
filterJust :: Event (Maybe a) -> Event a Source #
Return all event occurrences that are Just
values, discard the rest.
Think of it as
filterJust es = [(time,a) | (time,Just a) <- es]
unionWith :: (a -> a -> a) -> Event a -> Event a -> Event a Source #
Merge two event streams of the same type. In case of simultaneous occurrences, the event values are combined with the binary function. Think of it as
unionWith f ((timex,x):xs) ((timey,y):ys) | timex == timey = (timex,f x y) : unionWith f xs ys | timex < timey = (timex,x) : unionWith f xs ((timey,y):ys) | timex > timey = (timey,y) : unionWith f ((timex,x):xs) ys
apply :: Behavior (a -> b) -> Event a -> Event b Source #
Apply a time-varying function to a stream of events. Think of it as
apply bf ex = [(time, bf time x) | (time, x) <- ex]
accumB :: MonadIO m => a -> Event (a -> a) -> m (Behavior a) Source #
The accumB
function is similar to a strict left fold, foldl'
.
It starts with an initial value and combines it with incoming events.
For example, think
accumB "x" [(time1,(++"y")),(time2,(++"z"))] = stepper "x" [(time1,"xy"),(time2,"xyz")]
Note that the value of the behavior changes "slightly after" the events occur. This allows for recursive definitions.
stepper :: MonadIO m => a -> Event a -> m (Behavior a) Source #
Construct a time-varying function from an initial value and a stream of new values. Think of it as
stepper x0 ex = return $ \time -> last (x0 : [x | (timex,x) <- ex, timex < time])
Note that the smaller-than-sign in the comparison timex < time
means
that the value of the behavior changes "slightly after"
the event occurrences. This allows for recursive definitions.
filterE :: (a -> Bool) -> Event a -> Event a Source #
Return all event occurrences that fulfill the predicate, discard the rest.
filterApply :: Behavior (a -> Bool) -> Event a -> Event a Source #
Return all event occurrences that fulfill the time-varying predicate,
discard the rest. Generalization of filterE
.
whenE :: Behavior Bool -> Event a -> Event a Source #
Return event occurrences only when the behavior is True
.
Variant of filterApply
.
concatenate :: [a -> a] -> a -> a Source #
Apply a list of functions in succession.
Useful in conjunction with unions
.
concatenate [f,g,h] = f . g . h
tidings :: Behavior a -> Event a -> Tidings a Source #
Smart constructor. Combine facts and rumors into Tidings
.
Attributes
For a list of predefined attributes, see Graphics.UI.Threepenny.Attributes.
(#) :: a -> (a -> b) -> b infixl 8 Source #
Reverse function application. Allows convenient notation for setting properties.
Example usage.
mkElement "div" # set style [("color","#CCAABB")] # set draggable True # set children otherElements
(#.) :: UI Element -> String -> UI Element infixl 8 Source #
Convenient combinator for setting the CSS class on element creation.
type WriteAttr x i = ReadWriteAttr x i () Source #
Attribute that only supports the set
operation.
type ReadAttr x o = ReadWriteAttr x () o Source #
Attribute that only supports the get
operation.
data ReadWriteAttr x i o Source #
Generalized attribute with different types for getting and setting.
Instances
Functor (ReadWriteAttr x i) Source # | |
Defined in Graphics.UI.Threepenny.Core fmap :: (a -> b) -> ReadWriteAttr x i a -> ReadWriteAttr x i b # (<$) :: a -> ReadWriteAttr x i b -> ReadWriteAttr x i a # |
sink :: ReadWriteAttr x i o -> Behavior i -> UI x -> UI x Source #
Set the value of an attribute to a Behavior
, that is a time-varying value.
Note: For reasons of efficiency, the attribute is only updated when the value changes.
get :: ReadWriteAttr x i o -> x -> UI o Source #
Get attribute value.
:: (x -> UI o) | Getter. |
-> (i -> x -> UI ()) | Setter. |
-> ReadWriteAttr x i o |
Build an attribute from a getter and a setter.
mkWriteAttr :: (i -> x -> UI ()) -> WriteAttr x i Source #
Build attribute from a setter.
mkReadAttr :: (x -> UI o) -> ReadAttr x o Source #
Build attribute from a getter.
bimapAttr :: (i' -> i) -> (o -> o') -> ReadWriteAttr x i o -> ReadWriteAttr x i' o' Source #
Map input and output type of an attribute.
fromObjectProperty :: (FromJS a, ToJS a) => String -> Attr Element a Source #
Turn a JavaScript object property .prop = ...
into an attribute.
Widgets
Widgets are data types that have a visual representation.
getElement :: w -> Element Source #
Instances
Widget Element Source # | |
Defined in Graphics.UI.Threepenny.Core getElement :: Element -> Element Source # | |
Widget TextEntry Source # | |
Defined in Graphics.UI.Threepenny.Widgets getElement :: TextEntry -> Element Source # | |
Widget (ListBox a) Source # | |
Defined in Graphics.UI.Threepenny.Widgets getElement :: ListBox a -> Element Source # |
JavaScript FFI
Direct interface to JavaScript in the browser window.
debug :: String -> UI () Source #
Print a message on the client console if the client has debugging enabled.
Print a timestamp and the difference to the previous timestamp on the client console if the client has debugging enabled.
Helper class for rendering Haskell values as JavaScript expressions.
Helper class for making ffi
a variable argument function.
fancy
Instances
FromJS b => FFI (JSFunction b) Source # | |
Defined in Foreign.JavaScript.Marshal fancy :: ([JSCode] -> IO JSCode) -> JSFunction b | |
(ToJS a, FFI b) => FFI (a -> b) Source # | |
Defined in Foreign.JavaScript.Marshal |
data JSFunction a Source #
A JavaScript function with a given output type a
.
Instances
Functor JSFunction Source # | Change the output type of a |
Defined in Foreign.JavaScript.Marshal fmap :: (a -> b) -> JSFunction a -> JSFunction b # (<$) :: a -> JSFunction b -> JSFunction a # | |
FromJS b => FFI (JSFunction b) Source # | |
Defined in Foreign.JavaScript.Marshal fancy :: ([JSCode] -> IO JSCode) -> JSFunction b |
ffi :: FFI a => String -> a Source #
Simple JavaScript FFI with string substitution.
Inspired by the Fay language. https://github.com/faylang/fay/wiki
example :: String -> Int -> JSFunction String example = ffi "$(%1).prop('checked',%2)"
The ffi
function takes a string argument representing the JavaScript
code to be executed on the client.
Occurrences of the substrings %1
to %9
will be replaced by
subequent arguments.
The substring %%
in the original will be replaced by %
(character escape).
Note: Always specify a type signature! The types automate
how values are marshalled between Haskell and JavaScript.
The class instances for the FFI
class show which conversions are supported.
runFunction :: JSFunction () -> UI () Source #
Run a JavaScript function, but do not wait for a result.
The client window uses JavaScript's eval()
function to run the code.
NOTE: The JavaScript function need not be executed immediately,
it can be buffered and sent to the browser window at a later time.
See setCallBufferMode
and flushCallBuffer
for more.
callFunction :: JSFunction a -> UI a Source #
Call a JavaScript function and wait for the result.
The client window uses JavaScript's eval()
function to run the code.
data CallBufferMode Source #
Specification of how JavaScript functions should be called.
NoBuffering | When |
BufferRun | When |
FlushOften | The same as |
FlushPeriodically | The same as |
setCallBufferMode :: CallBufferMode -> UI () Source #
Set the call buffering mode for the browser window.
flushCallBuffer :: UI () Source #
Flush the call buffer, i.e. send all outstanding JavaScript to the client in one single message.
ffiExport :: IsHandler a => a -> UI JSObject Source #
Export the given Haskell function so that it can be called from JavaScript code.
NOTE: At the moment, the JSObject
representing the exported function
will be referenced by the browser Window
in which it was created,
preventing garbage collection until this browser Window
is disconnected.
This makes it possible to use it as an event handler on the JavaScript side, but it also means that the Haskell runtime has no way to detect early when it is no longer needed.
In contrast, if you use the function domEvent
to register an
event handler to an Element
,
then the handler will be garbage collected
as soon as the associated Element
is garbage collected.
Internals
toJSObject :: Element -> JSObject Source #
Access to the primitive JSObject
for roll-your-own foreign calls.
liftJSWindow :: (Window -> IO a) -> UI a Source #
Access to the primitive Window
object,
for roll-your-own JS foreign calls.