urlpath-0.1: Painfully simple URL writing combinators

Safe HaskellSafe-Inferred
LanguageHaskell2010

UrlPath.Types

Synopsis

Documentation

data UrlString a where Source

A Url string - a target page and GET parameters. We only require a constraint of IsString so that construction can be convenient, but rendering will require a monomorphic type.

Constructors

UrlString :: (IsString a, Monoid a) => a -> [(a, a)] -> UrlString a 

showUrlString :: UrlString a -> a Source

We choose to not provide a Show instance for UrlString to evade the String demand.

(<?>) infixl 9 Source

Arguments

:: (IsString a, Monoid a) 
=> a

Target string

-> (a, a)

GET Parameter

-> UrlString a 

Lifts a raw target path and a GET parameter pair into a UrlString.

(<&>) infixl 8 Source

Arguments

:: (IsString a, Monoid a) 
=> UrlString a

Old Url

-> (a, a)

Additional GET Parameter

-> UrlString a 

Adds another GET parameter pair to a UrlString.

expandRelative :: (IsString a, Monoid a) => UrlString a -> a Source

Render the Url String as relative

expandGrounded :: (IsString a, Monoid a) => UrlString a -> a Source

Render the Url String as grounded

expandAbsolute :: (MonadReader a m, IsString a, Monoid a) => UrlString a -> m a Source

Render the Url String as absolute - getting the root from a MonadReader context. The Monoid instance will be decided monomorphically, therefore a type signature will be needed when ran.

expandAbsoluteWith :: (MonadReader a m, IsString a, Monoid a) => UrlString a -> (a -> a) -> m a 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 h 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
  path <- lift $ url $ "foo.php" <?> ("bar","baz")
  script_ [src_ path] ""

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

bar :: ( Monad m, IsString a, Monoid a ) => m a
bar = (runRelativeUrlT (renderTextT foo)) "example.com"

Constructors

RelativeUrlT 

Fields

runRelativeUrlT :: h -> m a
 

newtype RelativeUrl h 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
  path <- lift $ url $ "foo.php" <?> ("bar","baz")
  script_ [src_ path] ""

when running the monad reader, use the runUrlReader member function of the UrlReader typeclass:

bar :: ( IsString a, Monoid a ) => a
bar = (runUrlReader (renderTextT foo)) "example.com"

To change the deployment sheme, simply coerce the environment monad in foo.

Constructors

RelativeUrl 

Fields

runRelativeUrl :: h -> a
 

newtype GroundedUrlT h m a Source

Constructors

GroundedUrlT 

Fields

runGroundedUrlT :: h -> m a
 

newtype GroundedUrl h a Source

Constructors

GroundedUrl 

Fields

runGroundedUrl :: h -> a
 

newtype AbsoluteUrlT h m a Source

Constructors

AbsoluteUrlT 

Fields

runAbsoluteUrlT :: h -> m a
 

newtype AbsoluteUrl h a Source

Constructors

AbsoluteUrl 

Fields

runAbsoluteUrl :: h -> a
 

Instances

IsString a => MonadReader a (AbsoluteUrl a) 
(Monoid a, IsString a) => UrlReader a (AbsoluteUrl a)

Hand-off host prepending to the MonadReader instance

(Monoid a, IsString a) => Url a (AbsoluteUrl a) 
Monad (AbsoluteUrl h) 
Functor (AbsoluteUrl h) 
Applicative (AbsoluteUrl h)