module Nero.Url
(
Url(..)
, Scheme(..)
, Host
, Path
, Query
, HasUrl(..)
, Location(..)
, HasHost(..)
, HasPath(..)
, HasQuery(..)
, Param(..)
, dummyUrl
) where
import Prelude hiding (null)
import Data.ByteString.Lazy (ByteString)
import Data.Text.Lazy (Text)
import Data.Text.Lazy.Lens (utf8)
import Nero.Prelude
import Nero.Param
import Nero.Binary
data Url = Url Scheme Host Path Query deriving (Show,Eq)
data Scheme = Http | Https deriving (Show,Eq)
instance Renderable Scheme where
render Http = "http"
render Https = "https"
instance Parseable Scheme where
parse "http" = Just Http
parse "https" = Just Https
parse _ = Nothing
type Host = ByteString
type Path = Text
type Query = MultiMap
class HasUrl a where
url :: Lens' a Url
class Location a where
location :: Traversal' a Url
class HasHost a where
host :: Lens' a Host
instance HasHost Url where
host f (Url s h p q) = (\h' -> Url s h' p q) <$> f h
class HasPath a where
path :: Lens' a Path
instance HasPath Url where
path f (Url s h p q) = (\p' -> Url s h p' q) <$> f p
class HasQuery a where
query :: Lens' a Query
instance HasQuery Url where
query f (Url s h p q) = Url s h p <$> f q
instance Param Url where
param k = query . param k
instance Renderable Url where
render (Url s h p q) = render s <> "://" <> h <> utf8 # p <> (
if not (null q)
then "?" <> render q
else mempty)
dummyUrl :: Url
dummyUrl = Url Http mempty mempty mempty