module UrlPath
( UrlReader (..)
, Url (..)
, module UrlPath.Types ) where
import UrlPath.Types
import Data.String
import Data.Monoid
import Control.Applicative
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Reader.Class
class ( IsString string, Monoid string, MonadReader string m ) =>
Url string (m :: * -> *) where
url :: UrlString string
-> m string
stringUrl :: string
-> m string
class Url string m => UrlReader string m where
runUrlReader :: Url string m =>
m string
-> string
-> string
instance ( Monoid a
, IsString a ) => Url a (RelativeUrl a) where
url = RelativeUrl . const . expandRelative
stringUrl x = RelativeUrl $ const $ expandRelative $ UrlString x []
instance ( Monoid a
, IsString a ) => UrlReader a (RelativeUrl a) where
runUrlReader = runRelativeUrl
instance ( Monoid a
, IsString a ) => Url a (GroundedUrl a) where
url = GroundedUrl . const . expandGrounded
stringUrl x = GroundedUrl $ const $ expandGrounded $ UrlString x []
instance ( Monoid a
, IsString a ) => UrlReader a (GroundedUrl a) where
runUrlReader = runGroundedUrl
instance ( Monoid a
, IsString a ) => Url a (AbsoluteUrl a) where
url = expandAbsolute
stringUrl x = expandAbsolute $ UrlString x []
instance ( Monoid a
, IsString a ) => UrlReader a (AbsoluteUrl a) where
runUrlReader = runAbsoluteUrl
instance ( Monad m
, Monoid a
, IsString a ) => Url a (RelativeUrlT a m) where
url = RelativeUrlT . const . return . expandRelative
stringUrl x = RelativeUrlT $ const $ return $ expandRelative $ UrlString x []
instance ( Monad m
, Monoid a
, IsString a ) => Url a (GroundedUrlT a m) where
url = GroundedUrlT . const . return . expandGrounded
stringUrl x = GroundedUrlT $ const $ return $ expandGrounded $ UrlString x []
instance ( Monad m
, Monoid a
, IsString a ) => Url a (AbsoluteUrlT a m) where
url = expandAbsolute
stringUrl x = expandAbsolute $ UrlString x []