urlpath-0.2: Painfully simple URL writing combinators

Safe HaskellSafe-Inferred
LanguageHaskell2010

UrlPath.Types

Synopsis

Documentation

data UrlString a where Source

Abstract data type for a Url - a "target" and GET parameters. We require IsString and Monoid for generic construction, but rendering will require a monomorphic type.

The type constructor is parameterized over it's underlying IsString & Monoid instance.

Constructors

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

showUrlString :: UrlString a -> a Source

We can't provide a Show instance for UrlString because that would force us to use String.

(<?>) infixl 9 Source

Arguments

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

Target string

-> (a, a)

GET Parameter

-> UrlString a 

Makes a UrlString out of a raw target path and a GET parameter pair.

(<&>) 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 plain, Monoid plain) => UrlString plain -> plain Source

Render the Url String flatly - without anything prepended to the target.

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

Render the Url String as grounded - prepended with a "root" // character.

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

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

expandAbsoluteWith :: (MonadReader a m, IsString plain, Monoid plain) => UrlString plain -> (a -> plain) -> m plain 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 b Source

Constructors

RelativeUrlT 

Fields

runRelativeUrlT :: h -> m b
 

Instances

(Monad m, IsString h) => MonadReader h (RelativeUrlT h m) 
(Monad m, Monoid plain, IsString plain) => UrlReader plain (RelativeUrlT plain m) 
(Monad m, Monoid plain, IsString plain) => Url plain (RelativeUrlT plain m) 
MonadTrans (RelativeUrlT h) 
Monad m => Monad (RelativeUrlT h m) 
Functor m => Functor (RelativeUrlT h m) 
Applicative f => Applicative (RelativeUrlT h f) 
MonadIO m => MonadIO (RelativeUrlT h m) 
type Result (RelativeUrlT plain m) = m 

type RelativeUrl h b = RelativeUrlT h Identity b Source

newtype GroundedUrlT h m b Source

Constructors

GroundedUrlT 

Fields

runGroundedUrlT :: h -> m b
 

Instances

(Monad m, IsString h) => MonadReader h (GroundedUrlT h m) 
(Monad m, Monoid plain, IsString plain) => UrlReader plain (GroundedUrlT plain m) 
(Monad m, Monoid plain, IsString plain) => Url plain (GroundedUrlT plain m) 
MonadTrans (GroundedUrlT h) 
Monad m => Monad (GroundedUrlT h m) 
Functor m => Functor (GroundedUrlT h m) 
Applicative f => Applicative (GroundedUrlT h f) 
MonadIO m => MonadIO (GroundedUrlT h m) 
type Result (GroundedUrlT plain m) = m 

type GroundedUrl h b = GroundedUrlT h Identity b Source

newtype AbsoluteUrlT h m b Source

Constructors

AbsoluteUrlT 

Fields

runAbsoluteUrlT :: h -> m b
 

Instances

(Monad m, IsString h) => MonadReader h (AbsoluteUrlT h m) 
(Monad m, Monoid plain, IsString plain) => UrlReader plain (AbsoluteUrlT plain m) 
(Monad m, Monoid plain, IsString plain) => Url plain (AbsoluteUrlT plain m) 
MonadTrans (AbsoluteUrlT h) 
Monad m => Monad (AbsoluteUrlT h m) 
Functor m => Functor (AbsoluteUrlT h m) 
Applicative f => Applicative (AbsoluteUrlT h f) 
MonadIO m => MonadIO (AbsoluteUrlT h m) 
type Result (AbsoluteUrlT plain m) = m 

type AbsoluteUrl h b = AbsoluteUrlT h Identity b Source