urlpath-0.0.4: Painfully simple URL writing combinators

Safe HaskellSafe-Inferred
LanguageHaskell2010

UrlPath.Types

Synopsis

Documentation

data GETParam Source

A GET parameter encoded in a Url.

Constructors

GETParam 

Fields

key :: !Text

Key for a get parameter.

val :: !Text

Value for the key.

Instances

renderGETParam :: GETParam -> Text Source

Render a GET parameter pair.

data UrlString Source

A Url string - a target page and GET parameters.

Constructors

UrlString 

Fields

target :: !Text

Relative base file - eg) "foo.php" in "foo.php?bar=baz".

params :: [GETParam]

GET Parameters.

renderUrlString :: UrlString -> Text Source

Render a Url String simply - this is equivalent to expandRelative.

(<?>) infixl 9 Source

Arguments

:: Text

Target string

-> (Text, Text)

GET Parameter

-> UrlString 

Lifts a target path with some GET parameter chunks into a UrlString.

(<&>) infixl 8 Source

Arguments

:: UrlString

Old Url

-> (Text, Text)

Additional GET Parameter

-> UrlString 

Adds more GET parameters to a UrlString.

expandRelative :: UrlString -> Text Source

Render the Url String as relative

expandGrounded :: UrlString -> Text Source

Render the Url String as grounded

expandAbsolute :: MonadReader Text m => UrlString -> m Text Source

Render the Url String as absolute - getting the root from a MonadReader.

expandAbsoluteWith :: MonadReader a m => UrlString -> (a -> Text) -> m Text Source

Render the Url String as absolute, but with your own configuration type.

data SiteConfig = SiteConfig { host :: T.Text
                             , cdnHost :: T.Text
                             }
  deriving (Show, Eq)
          
foo :: HtmlT (Reader SiteConfig) ()
foo = do
  url <- lift $ expandAbsoluteWith ("foo.php" <?> ("bar","baz")) host
  script_ [src_ url] ""

bar :: LT.Text 
bar = (runReader (runTextT foo)) $
  SiteConfig "example.com" "cdn.example.com"

newtype RelativeUrlT m a Source

Rendering mode transformer. This isn't an instance of UrlReader - to use, simple lift as many levels as you need:

foo :: Monad m => HtmlT (RelativeUrlT m) ()
foo = do
  url <- lift $ renderUrl $ "foo.php" <?> ("bar","baz")
  script_ [src_ url] ""

When rendering foo, simply use the Transformer's run function to convert it to a reader:

bar :: Monad m => m LT.Text
bar = (runRelativeUrlT (renderTextT foo)) "example.com"

It is generally simpler (but more restrictive) to use the non-transformer variety.

Constructors

RelativeUrlT 

Fields

runRelativeUrlT :: Text -> m a
 

newtype RelativeUrl a Source

Concrete Monad for automatically coercing HtmlT's to use a mode of Url rendering (relative, grounded, or absolute).

foo :: HtmlT RelativeUrl ()
foo = do
  url <- lift $ renderUrl $ "foo.php" <?> ("bar","baz")
  script_ [src_ url] ""

when rendering these simple monads for automatic conversion via coercion, use the runUrlReader member function of the UrlReader typeclass:

bar :: LT.Text
bar = (runUrlReader (renderTextT foo)) "example.com"

To change the mode of rendering, simple change the coerced type of foo.

Constructors

RelativeUrl 

Fields

runRelativeUrl :: Text -> a