on-a-horse-0.1: "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 WithError ex i o = LabeledArrow (ErrorArrow ex (ReaderArrow FormIn (Automaton (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') => a' (e, String, Maybe String) b -> a e bSource
catchAuto :: (ArrowAddAutomaton a a', ArrowApply a', ArrowChoice a', ArrowChoice a) => LabeledArrow (ErrorArrow (LabeledArrow a i o) a) i o -> LabeledArrow a i 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
valForm :: (ArrowReader FormIn a', ArrowAddLabel a a', ArrowApply a'1, ArrowAddAutomaton a' a'1, ArrowChoice a') => String -> a' String (Either String a1) -> String -> a () (Html (), Maybe a1)Source
runSubStream :: ArrowChoice a => a i o -> a (Maybe i) (Maybe o)Source
filterDiffs :: (Eq i, ArrowApply a', ArrowAddAutomaton a a') => a i (Maybe i)Source
keepState :: (ArrowApply a', ArrowAddAutomaton a a') => o -> a (Maybe o) oSource
replaceSecond :: (ArrowAddAutomaton a a', ArrowApply a') => a i o -> a (i, Maybe (a i o)) oSource
once :: (ArrowAddAutomaton a a', ArrowApply a') => a1 -> a i (Maybe a1)Source
auto :: Automaton a i o -> a i (o, Automaton a i o)Source
staticUrls :: a -> [(String, a)] -> [String] -> aSource
type Url = [String]Source
runHorse1 :: ((Env -> IO Response) -> IO ()) -> Automaton (Kleisli IO) Env Response -> IO ()Source
runWeb :: MVar (Map String (MVar (Automaton (Kleisli IO) Env Response))) -> Automaton (Kleisli IO) Env Response -> Env -> IO ResponseSource
getSessionMVar :: MVar (Map String (MVar a)) -> a -> Env -> IO (MVar a, [(String, String)])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