on-a-horse-0.2: "Haskell on a Horse" - A combinatorial web frameworkSource codeContentsIndex
Web.Horse
Documentation
module Text.Hamlet
type FormOut = Html ()Source
newtype FormIn Source
Constructors
FormIn [(String, String)]
show/hide Instances
type HoH i o = LabeledArrow (ReaderArrow FormIn (Automaton (Kleisli IO))) i oSource
type HoHMay i o = LabeledArrow (ReaderArrow FormIn (MaybeAutomaton (Kleisli IO))) i oSource
type HoHErr ex i o = LabeledArrow (ErrorArrow ex (ReaderArrow FormIn (Automaton (Kleisli IO)))) i oSource
type HoHErrMay ex i o = LabeledArrow (ErrorArrow ex (ReaderArrow FormIn (MaybeAutomaton (Kleisli IO)))) i oSource
noInput :: FormInSource
filterPrefix :: String -> FormIn -> FormInSource
class HasFormOut o whereSource
Methods
getFormOut :: o -> FormOutSource
setFormOut :: FormOut -> o -> oSource
show/hide Instances
getSingle :: FormIn -> Maybe StringSource
withInput :: (ArrowReader FormIn a', ArrowAddLabel a a', ArrowAddAutomaton a1 a' a'1) => a1 (e, String, Maybe String) b -> a e bSource
withInput0 :: (ArrowReader FormIn a', ArrowAddLabel a a') => a' (e, String, Maybe String) b -> a e bSource
catchAuto :: ArrowAddAutomaton a may a' => LabeledArrow (ErrorArrow (LabeledArrow a i o) a) i o -> LabeledArrow a i oSource
catchMayAuto :: ArrowAddAutomaton a may a' => LabeledArrow (ErrorArrow (LabeledArrow a t1 o) may) t1 o -> LabeledArrow may t1 oSource
runHamlet :: Arrow a => a (x -> y) ySource
textField :: String -> Maybe String -> String -> String -> Html ()Source
link :: String -> String -> Html ()Source
select :: String -> [String] -> Int -> String -> Html ()Source
wrapForm :: Html () -> Html ()Source
enumForm :: (ArrowAddAutomaton a1 may a', ArrowAddLabel a may, ArrowReader FormIn may) => String -> [(String, b)] -> a () (Html (), Maybe b)Source
runSubStream :: ArrowChoice a => a i o -> a (Maybe i) (Maybe o)Source
filterDiffs :: (ArrowAddAutomaton a may a', Eq i, ArrowApply a') => a i (Maybe i)Source
staticUrls :: a -> [(String, a)] -> [String] -> aSource
type Url = [String]Source
runHorse1 :: ((Env -> IO Response) -> IO ()) -> MaybeAutomaton (Kleisli IO) Env Response -> IO ()Source
runWeb :: MVar [(String, MVar (Automaton (Kleisli IO) Env Response))] -> MaybeAutomaton (Kleisli IO) Env Response -> Env -> IO ResponseSource
getSessionMVar :: MVar [(String, MVar (Automaton (Kleisli IO) Env Response))] -> Env -> IO (Maybe (MVar (Automaton (Kleisli IO) Env Response)))Source
sessionName :: [Char]Source
simpleReqResp :: Arrow a => a (Url, FormIn) ByteString -> a Env ResponseSource
asResponse :: ByteString -> ResponseSource
module Control.Arrow.Transformer.Automaton.Monad
Produced by Haddock version 2.6.1