Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- module Clckwrks.Acid
- getUserId :: Happstack m => ClckT url m (Maybe UserId)
- module Clckwrks.Monad
- module Clckwrks.ProfileData.API
- module Clckwrks.ProfileData.Types
- module Clckwrks.ProfileData.URL
- module Clckwrks.Types
- module Clckwrks.Unauthorized
- module Clckwrks.URL
- module Clckwrks.JS.URL
- module Control.Applicative
- module Control.Monad
- module Control.Monad.Trans
- newtype UserId = UserId {}
- module Happstack.Server
- data JStat
- = DeclStat Ident (Maybe JLocalType)
- | ReturnStat JExpr
- | IfStat JExpr JStat JStat
- | WhileStat Bool JExpr JStat
- | ForInStat Bool Ident JExpr JStat
- | SwitchStat JExpr [(JExpr, JStat)] JStat
- | TryStat JStat Ident JStat JStat
- | BlockStat [JStat]
- | ApplStat JExpr [JExpr]
- | PPostStat Bool String JExpr
- | AssignStat JExpr JExpr
- | UnsatBlock (IdentSupply JStat)
- | AntiStat String
- | ForeignStat Ident JLocalType
- | LabelStat JsLabel JStat
- | BreakStat (Maybe JsLabel)
- | ContinueStat (Maybe JsLabel)
- jmacroE :: QuasiQuoter
- jmacro :: QuasiQuoter
- data JExpr
- data JVal
- newtype Ident = StrI String
- class JMacro a where
- toJExpr :: ToJExpr a => a -> JExpr
- data JType
- class Generic a
- pathInfoInverse_prop :: (Eq url, PathInfo url) => url -> Bool
- mkSitePI :: PathInfo url => ((url -> [(Text, Maybe Text)] -> Text) -> url -> a) -> Site url a
- fromPathInfoParams :: PathInfo url => ByteString -> Either String (url, [(Text, Maybe Text)])
- fromPathInfo :: PathInfo url => ByteString -> Either String url
- toPathInfoParams :: PathInfo url => url -> [(Text, Maybe Text)] -> Text
- toPathInfo :: PathInfo url => url -> Text
- parseSegments :: URLParser a -> [Text] -> Either String a
- showParseError :: ParseError -> String
- patternParse :: ([Text] -> Either String a) -> URLParser a
- anySegment :: URLParser Text
- segment :: Text -> URLParser Text
- pToken :: tok -> (Text -> Maybe a) -> URLParser a
- stripOverlapBS :: ByteString -> ByteString -> ByteString
- stripOverlapText :: Text -> Text -> Text
- stripOverlap :: Eq a => [a] -> [a] -> [a]
- type URLParser a = GenParser Text () a
- class PathInfo url where
- toPathSegments :: url -> [Text]
- fromPathSegments :: URLParser url
- runSite :: Text -> Site url a -> [Text] -> Either String a
- setDefault :: url -> Site url a -> Site url a
- data Site url a = Site {
- handleSite :: (url -> [(Text, Maybe Text)] -> Text) -> url -> a
- formatPathSegments :: url -> ([Text], [(Text, Maybe Text)])
- parsePathSegments :: [Text] -> Either String url
- showURLParams :: MonadRoute m => URL m -> [(Text, Maybe Text)] -> m Text
- showURL :: MonadRoute m => URL m -> m Text
- askRouteT :: Monad m => RouteT url m (url -> [(Text, Maybe Text)] -> Text)
- liftRouteT :: m a -> RouteT url m a
- withRouteT :: ((url' -> [(Text, Maybe Text)] -> Text) -> url -> [(Text, Maybe Text)] -> Text) -> RouteT url m a -> RouteT url' m a
- mapRouteT :: (m a -> n b) -> RouteT url m a -> RouteT url n b
- runRouteT :: (url -> RouteT url m a) -> (url -> [(Text, Maybe Text)] -> Text) -> url -> m a
- newtype RouteT url (m :: Type -> Type) a = RouteT {}
- class Monad m => MonadRoute (m :: Type -> Type) where
- decodePathInfoParams :: ByteString -> ([Text], [(Text, Maybe Text)])
- decodePathInfo :: ByteString -> [Text]
- encodePathInfo :: [Text] -> [(Text, Maybe Text)] -> Text
- seeOtherURL :: (MonadRoute m, FilterMonad Response m) => URL m -> m Response
Documentation
module Clckwrks.Acid
module Clckwrks.Monad
module Clckwrks.ProfileData.API
module Clckwrks.ProfileData.Types
module Clckwrks.ProfileData.URL
module Clckwrks.Types
module Clckwrks.Unauthorized
module Clckwrks.URL
module Clckwrks.JS.URL
module Control.Applicative
module Control.Monad
module Control.Monad.Trans
a UserId
uniquely identifies a user.
Instances
Enum UserId | |
Defined in Data.UserId | |
Eq UserId | |
Data UserId | |
Defined in Data.UserId gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserId -> c UserId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserId # toConstr :: UserId -> Constr # dataTypeOf :: UserId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UserId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserId) # gmapT :: (forall b. Data b => b -> b) -> UserId -> UserId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r # gmapQ :: (forall d. Data d => d -> u) -> UserId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UserId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserId -> m UserId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserId -> m UserId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserId -> m UserId # | |
Ord UserId | |
Read UserId | |
Show UserId | |
Generic UserId | |
SafeCopy UserId | |
ToJSON UserId | |
Defined in Data.UserId | |
FromJSON UserId | |
Serialize UserId | |
PathInfo UserId | |
Defined in Data.UserId toPathSegments :: UserId -> [Text] # | |
Indexable UserIxs User | |
type Rep UserId | |
Defined in Data.UserId |
module Happstack.Server
Statements
Instances
Eq JStat | |
Data JStat | |
Defined in Language.Javascript.JMacro.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JStat -> c JStat # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JStat # dataTypeOf :: JStat -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JStat) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JStat) # gmapT :: (forall b. Data b => b -> b) -> JStat -> JStat # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JStat -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JStat -> r # gmapQ :: (forall d. Data d => d -> u) -> JStat -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JStat -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JStat -> m JStat # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JStat -> m JStat # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JStat -> m JStat # | |
Ord JStat | |
Show JStat | |
Semigroup JStat | |
Monoid JStat | |
JMacro JStat | |
JsToDoc JStat | |
Defined in Language.Javascript.JMacro.Base | |
ToStat JStat | |
Defined in Language.Javascript.JMacro.Base | |
ToSat JStat | |
Defined in Language.Javascript.JMacro.Base | |
JsToDoc [JStat] | |
Defined in Language.Javascript.JMacro.Base | |
ToStat [JStat] | |
Defined in Language.Javascript.JMacro.Base | |
ToSat [JStat] | |
Defined in Language.Javascript.JMacro.Base |
jmacroE :: QuasiQuoter #
QuasiQuoter for a JMacro expression.
jmacro :: QuasiQuoter #
QuasiQuoter for a block of JMacro statements.
Expressions
Instances
Eq JExpr | |
Data JExpr | |
Defined in Language.Javascript.JMacro.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JExpr -> c JExpr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JExpr # dataTypeOf :: JExpr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JExpr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JExpr) # gmapT :: (forall b. Data b => b -> b) -> JExpr -> JExpr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JExpr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JExpr -> r # gmapQ :: (forall d. Data d => d -> u) -> JExpr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JExpr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JExpr -> m JExpr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JExpr -> m JExpr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JExpr -> m JExpr # | |
Num JExpr | |
Ord JExpr | |
Show JExpr | |
JMacro JExpr | |
JsToDoc JExpr | |
Defined in Language.Javascript.JMacro.Base | |
ToJExpr JExpr | |
Defined in Language.Javascript.JMacro.Base | |
ToStat JExpr | |
Defined in Language.Javascript.JMacro.Base | |
ToSat JExpr | |
Defined in Language.Javascript.JMacro.Base | |
JsToDoc [JExpr] | |
Defined in Language.Javascript.JMacro.Base | |
ToStat [JExpr] | |
Defined in Language.Javascript.JMacro.Base | |
ToSat [JExpr] | |
Defined in Language.Javascript.JMacro.Base |
Values
JVar Ident | |
JList [JExpr] | |
JDouble SaneDouble | |
JInt Integer | |
JStr String | |
JRegEx String | |
JHash (Map String JExpr) | |
JFunc [Ident] JStat | |
UnsatVal (IdentSupply JVal) |
Instances
Eq JVal | |
Data JVal | |
Defined in Language.Javascript.JMacro.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JVal -> c JVal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JVal # dataTypeOf :: JVal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JVal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JVal) # gmapT :: (forall b. Data b => b -> b) -> JVal -> JVal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JVal -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JVal -> r # gmapQ :: (forall d. Data d => d -> u) -> JVal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JVal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JVal -> m JVal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JVal -> m JVal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JVal -> m JVal # | |
Ord JVal | |
Show JVal | |
JMacro JVal | |
JsToDoc JVal | |
Defined in Language.Javascript.JMacro.Base | |
ToJExpr JVal | |
Defined in Language.Javascript.JMacro.Base |
Identifiers
Instances
Eq Ident | |
Data Ident | |
Defined in Language.Javascript.JMacro.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident # dataTypeOf :: Ident -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ident) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) # gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r # gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident # | |
Ord Ident | |
Show Ident | |
JMacro Ident | |
JsToDoc Ident | |
Defined in Language.Javascript.JMacro.Base |
Compos and ops for generic traversal as defined over the JMacro ADT.
Utility class to coerce the ADT into a regular structure.
JTNum | |
JTString | |
JTBool | |
JTStat | |
JTFunc [JType] JType | |
JTList JType | |
JTMap JType | |
JTRecord JType (Map String JType) | |
JTRigid VarRef (Set Constraint) | |
JTImpossible | |
JTFree VarRef | |
JTForall [VarRef] JType |
Instances
Eq JType | |
Data JType | |
Defined in Language.Javascript.JMacro.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JType -> c JType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JType # dataTypeOf :: JType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JType) # gmapT :: (forall b. Data b => b -> b) -> JType -> JType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JType -> r # gmapQ :: (forall d. Data d => d -> u) -> JType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JType -> m JType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JType -> m JType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JType -> m JType # | |
Ord JType | |
Read JType | |
Show JType | |
JsToDoc JType | |
Defined in Language.Javascript.JMacro.Base | |
JsToDoc JLocalType | |
Defined in Language.Javascript.JMacro.Base jsToDoc :: JLocalType -> Doc # |
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
pathInfoInverse_prop :: (Eq url, PathInfo url) => url -> Bool #
test that a PathInfo
instance is valid
Generates Arbitrary
url
values and checks that:
fromPathInfo . toPathInfo == id
fromPathInfoParams :: PathInfo url => ByteString -> Either String (url, [(Text, Maybe Text)]) #
fromPathInfo :: PathInfo url => ByteString -> Either String url #
convert url + params into the path info portion of a URL + a query string
toPathInfo :: PathInfo url => url -> Text #
convert url into the path info portion of a URL
parseSegments :: URLParser a -> [Text] -> Either String a #
run a URLParser
on a list of path segments
returns Left "parse error"
on failure.
returns Right a
on success
showParseError :: ParseError -> String #
show Parsec ParseError
using terms that relevant to parsing a url
patternParse :: ([Text] -> Either String a) -> URLParser a #
apply a function to the remainder of the segments
useful if you want to just do normal pattern matching: > > foo ["foo", "bar"] = Right (Foo Bar) > foo ["baz"] = Right Baz > foo _ = Left "parse error"
patternParse foo
anySegment :: URLParser Text #
match on any string
stripOverlapBS :: ByteString -> ByteString -> ByteString #
stripOverlapText :: Text -> Text -> Text #
stripOverlap :: Eq a => [a] -> [a] -> [a] #
Simple parsing and rendering for a type to and from URL path segments.
If you're using GHC 7.2 or later, you can use DeriveGeneric
to derive
instances of this class:
{-# LANGUAGE DeriveGeneric #-} data Sitemap = Home | BlogPost Int deriving Generic instance PathInfo Sitemap
This results in the following instance:
instance PathInfo Sitemap where toPathSegments Home = ["home"] toPathSegments (BlogPost x) = "blog-post" : toPathSegments x fromPathSegments = Home <$ segment "home" <|> BlogPost <$ segment "blog-post" <*> fromPathSegments
And here it is in action:
>>>
toPathInfo (BlogPost 123)
"/blog-post/123">>>
fromPathInfo "/blog-post/123" :: Either String Sitemap
Right (BlogPost 123)
To instead derive instances using TemplateHaskell
, see
web-routes-th.
Nothing
toPathSegments :: url -> [Text] #
fromPathSegments :: URLParser url #
Instances
:: Text | application root, with trailing slash |
-> Site url a | |
-> [Text] | path info, (call |
-> Either String a |
Retrieve the application to handle a given request.
NOTE: use decodePathInfo
to convert a ByteString
url to a properly decoded list of path segments
setDefault :: url -> Site url a -> Site url a #
Override the "default" URL, ie the result of parsePathSegments
[].
A site groups together the three functions necesary to make an application:
- A function to convert from the URL type to path segments.
- A function to convert from path segments to the URL, if possible.
- A function to return the application for a given URL.
There are two type parameters for Site: the first is the URL datatype, the second is the application datatype. The application datatype will depend upon your server backend.
Site | |
|
showURLParams :: MonadRoute m => URL m -> [(Text, Maybe Text)] -> m Text #
showURL :: MonadRoute m => URL m -> m Text #
liftRouteT :: m a -> RouteT url m a #
withRouteT :: ((url' -> [(Text, Maybe Text)] -> Text) -> url -> [(Text, Maybe Text)] -> Text) -> RouteT url m a -> RouteT url' m a #
Execute a computation in a modified environment
mapRouteT :: (m a -> n b) -> RouteT url m a -> RouteT url n b #
Transform the computation inside a RouteT
.
newtype RouteT url (m :: Type -> Type) a #
monad transformer for generating URLs
Instances
class Monad m => MonadRoute (m :: Type -> Type) where #
Instances
Monad m => MonadRoute (RouteT url m) | |
Monad m => MonadRoute (ClckT url m) Source # | |
decodePathInfoParams :: ByteString -> ([Text], [(Text, Maybe Text)]) #
Returns path segments as well as possible query string components
For example:
decodePathInfoParams "/home?q=1"
(["home"],[("q",Just "1")])
decodePathInfo :: ByteString -> [Text] #
Performs the inverse operation of encodePathInfo
.
In particular, this function:
- Splits a string at each occurence of a forward slash.
- Percent-decodes the individual pieces.
- UTF-8 decodes the resulting data.
This utilizes decodeString
from the utf8-string library, and thus all UTF-8
decoding errors are handled as per that library.
In general, you will want to strip the leading slash from a pathinfo before passing it to this function. For example:
decodePathInfo \"\"
[]
decodePathInfo \"\/\"
- ""
Note that while function accepts a Text
value, it is expected that Text
will only contain the subset of characters which are allowed to appear in a URL.
encodePathInfo :: [Text] -> [(Text, Maybe Text)] -> Text #
Encodes a list of path segments into a valid URL fragment.
This function takes the following three steps:
- UTF-8 encodes the characters.
- Performs percent encoding on all unreserved characters, as well as :@=+$,
- Intercalates with a slash.
For example:
encodePathInfo [\"foo\", \"bar\", \"baz\"]
"foo/bar/baz"
encodePathInfo [\"foo bar\", \"baz\/bin\"]
"foo%20bar/baz%2Fbin"
encodePathInfo [\"שלום\"]
"%D7%A9%D7%9C%D7%95%D7%9D"
seeOtherURL :: (MonadRoute m, FilterMonad Response m) => URL m -> m Response #