Safe Haskell | None |
---|---|
Language | Haskell98 |
- stripOverlap :: Eq a => [a] -> [a] -> [a]
- stripOverlapBS :: ByteString -> ByteString -> ByteString
- stripOverlapText :: Text -> Text -> Text
- type URLParser a = GenParser Text () a
- pToken :: tok -> (Text -> Maybe a) -> URLParser a
- segment :: Text -> URLParser Text
- anySegment :: URLParser Text
- patternParse :: ([Text] -> Either String a) -> URLParser a
- parseSegments :: URLParser a -> [Text] -> Either String a
- class PathInfo url where
- toPathSegments :: url -> [Text]
- fromPathSegments :: URLParser url
- toPathInfo :: PathInfo url => url -> Text
- toPathInfoParams :: PathInfo url => url -> [(Text, Maybe Text)] -> Text
- fromPathInfo :: PathInfo url => ByteString -> Either String url
- mkSitePI :: PathInfo url => ((url -> [(Text, Maybe Text)] -> Text) -> url -> a) -> Site url a
- showParseError :: ParseError -> String
- class Generic a
Documentation
stripOverlap :: Eq a => [a] -> [a] -> [a] Source
stripOverlapBS :: ByteString -> ByteString -> ByteString Source
stripOverlapText :: Text -> Text -> Text Source
anySegment :: URLParser Text Source
match on any string
patternParse :: ([Text] -> Either String a) -> URLParser a Source
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
parseSegments :: URLParser a -> [Text] -> Either String a Source
run a URLParser
on a list of path segments
returns Left "parse error"
on failure.
returns Right a
on success
class PathInfo url where Source
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] Source
fromPathSegments :: URLParser url Source
toPathInfo :: PathInfo url => url -> Text Source
convert url into the path info portion of a URL
convert url + params into the path info portion of a URL + a query string
fromPathInfo :: PathInfo url => ByteString -> Either String url Source
showParseError :: ParseError -> String Source
show Parsec ParseError
using terms that relevant to parsing a url
Re-exported for convenience
class Generic a
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Generic Bool | |
Generic Char | |
Generic Double | |
Generic Float | |
Generic Int | |
Generic Ordering | |
Generic () | |
Generic All | |
Generic Any | |
Generic Arity | |
Generic Fixity | |
Generic Associativity | |
Generic [a] | |
Generic (U1 p) | |
Generic (Par1 p) | |
Generic (ZipList a) | |
Generic (Dual a) | |
Generic (Endo a) | |
Generic (Sum a) | |
Generic (Product a) | |
Generic (First a) | |
Generic (Last a) | |
Generic (Maybe a) | |
Generic (Either a b) | |
Generic (Rec1 f p) | |
Generic (a, b) | |
Generic (Const a b) | |
Generic (WrappedMonad m a) | |
Generic (Proxy * t) | |
Generic (K1 i c p) | |
Generic ((:+:) f g p) | |
Generic ((:*:) f g p) | |
Generic ((:.:) f g p) | |
Generic (a, b, c) | |
Generic (WrappedArrow a b c) | |
Generic (M1 i c f p) | |
Generic (a, b, c, d) | |
Generic (a, b, c, d, e) | |
Generic (a, b, c, d, e, f) | |
Generic (a, b, c, d, e, f, g) |