| Safe Haskell | None |
|---|
Web.Scottish
Contents
Description
Scotty apps with configuration and states
- data Scottish config globalState localState a
- type Scottish' c s' = Scottish c () s'
- type ScottishM e c s s' = ScottyT e (Scottish c s s')
- type ScottishActionM e c s s' = ActionT e (Scottish c s s')
- type ScottishM' c s' = ScottyT Status (Scottish' c s')
- type ScottishActionM' c s' = ActionT Status (Scottish' c s')
- scottish :: (Default c, Default s, Default s') => Port -> ScottishM e c s s' () -> IO ()
- scottishApp :: (Default c, Default s, Default s') => ScottishM e c s s' () -> IO Application
- scottishOpts :: (Default c, Default s, Default s') => Options -> ScottishM e c s s' () -> IO ()
- scottish' :: (Default c, Default s, Default s') => Port -> ScottishM Status c s s' () -> IO ()
- scottishApp' :: (Default c, Default s, Default s') => ScottishM Status c s s' () -> IO Application
- scottishOpts' :: (Default c, Default s, Default s') => Options -> ScottishM Status c s s' () -> IO ()
- handleRaisedStatus :: ScottishM Status c s s' () -> ScottishM Status c s s' ()
- getConfig :: MonadTrans t => t (Scottish c s s') c
- getGlobalState :: MonadTrans t => t (Scottish c s s') s
- getLocalState :: ScottyError e => ScottishActionM e c s s' s'
- (>$<) :: MonadTrans t => (a -> Scottish c s s' b) -> IdentityT (Scottish c s s') a -> t (Scottish c s s') b
- setLocalState :: ScottyError e => s' -> ScottishActionM e c s s' ()
- modifyLocalState :: ScottyError e => (s' -> s') -> ScottishActionM e c s s' ()
- setConfig :: c -> ScottishM e c s s' ()
- modifyConfig :: (c -> c) -> ScottishM e c s s' ()
- setGlobalState :: s -> ScottishM e c s s' ()
- modifyGlobalState :: (s -> s) -> ScottishM e c s s' ()
Types
data Scottish config globalState localState a Source
config is read-only in ActionT, but read-write in ScottyT for
initialization.
localState is reinitialized to def for every execution of each ActionT.
globalState may be a TVar, or other monadic mutable data types. Normally,
globalState should not be necessary for server apps, as there may be
multiple instance of the server running, even across machines, and you sure
cannot make them share the same state. However, you may be able to do some
process-local caching or user interaction (say in games), with globalState.
type ScottishActionM e c s s' = ActionT e (Scottish c s s')Source
type ScottishM' c s' = ScottyT Status (Scottish' c s')Source
type ScottishActionM' c s' = ActionT Status (Scottish' c s')Source
App runners/converters
scottish :: (Default c, Default s, Default s') => Port -> ScottishM e c s s' () -> IO ()Source
Run a scottish app with warp.
scottishApp :: (Default c, Default s, Default s') => ScottishM e c s s' () -> IO ApplicationSource
Turn a scottish app into a WAI one, which can be run with any WAI handler.
scottishOpts :: (Default c, Default s, Default s') => Options -> ScottishM e c s s' () -> IO ()Source
Run a scottish app with extra options.
scottish' :: (Default c, Default s, Default s') => Port -> ScottishM Status c s s' () -> IO ()Source
Scottish app runner with Status handler installed.
scottishApp' :: (Default c, Default s, Default s') => ScottishM Status c s s' () -> IO ApplicationSource
Scottish app converter with Status handler installed.
scottishOpts' :: (Default c, Default s, Default s') => Options -> ScottishM Status c s s' () -> IO ()Source
Scottish app runner with Status handler installed.
handleRaisedStatus :: ScottishM Status c s s' () -> ScottishM Status c s s' ()Source
Status is a good candidate as an ScottyError instance by itself. Call
this function to install a default handler to report the Status when one is
raised.
Also, you may want to define instances of ScottyError with tuples/records
containing Status, to provide more informative error pages.
Configuratio/State accessors
Shared by ScottyM & ScottyActionM
getConfig :: MonadTrans t => t (Scottish c s s') cSource
getGlobalState :: MonadTrans t => t (Scottish c s s') sSource
getLocalState :: ScottyError e => ScottishActionM e c s s' s'Source
(>$<) :: MonadTrans t => (a -> Scottish c s s' b) -> IdentityT (Scottish c s s') a -> t (Scottish c s s') bSource
Lift a Scottish function to a MonadTrans wrapped Scottish one.
ScottyActionM only
setLocalState :: ScottyError e => s' -> ScottishActionM e c s s' ()Source
modifyLocalState :: ScottyError e => (s' -> s') -> ScottishActionM e c s s' ()Source
ScottyM only
modifyConfig :: (c -> c) -> ScottishM e c s s' ()Source
setGlobalState :: s -> ScottishM e c s s' ()Source
modifyGlobalState :: (s -> s) -> ScottishM e c s s' ()Source