| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Servant.Client.Core.BaseUrl
Synopsis
- data BaseUrl = BaseUrl {}
- data Scheme
- showBaseUrl :: BaseUrl -> String
- parseBaseUrl :: MonadThrow m => String -> m BaseUrl
- newtype InvalidBaseUrlException = InvalidBaseUrlException String
Documentation
Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.
Constructors
| BaseUrl | |
| Fields 
 | |
Instances
| Eq BaseUrl Source # | |
| Data BaseUrl Source # | |
| Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaseUrl -> c BaseUrl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaseUrl # toConstr :: BaseUrl -> Constr # dataTypeOf :: BaseUrl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BaseUrl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaseUrl) # gmapT :: (forall b. Data b => b -> b) -> BaseUrl -> BaseUrl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r # gmapQ :: (forall d. Data d => d -> u) -> BaseUrl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BaseUrl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl # | |
| Ord BaseUrl Source # | |
| Defined in Servant.Client.Core.BaseUrl | |
| Show BaseUrl Source # | |
| Generic BaseUrl Source # | |
| Lift BaseUrl Source # | |
| ToJSON BaseUrl Source # | 
 | 
| Defined in Servant.Client.Core.BaseUrl | |
| ToJSONKey BaseUrl Source # | 
 | 
| Defined in Servant.Client.Core.BaseUrl | |
| FromJSON BaseUrl Source # | 
 | 
| FromJSONKey BaseUrl Source # | |
| Defined in Servant.Client.Core.BaseUrl Methods | |
| NFData BaseUrl Source # | |
| Defined in Servant.Client.Core.BaseUrl | |
| type Rep BaseUrl Source # | |
| Defined in Servant.Client.Core.BaseUrl type Rep BaseUrl = D1 (MetaData "BaseUrl" "Servant.Client.Core.BaseUrl" "servant-client-core-0.17-6TEb4JOolq16hAUWK9fzoL" False) (C1 (MetaCons "BaseUrl" PrefixI True) ((S1 (MetaSel (Just "baseUrlScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme) :*: S1 (MetaSel (Just "baseUrlHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "baseUrlPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "baseUrlPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) | |
URI scheme to use
Instances
| Eq Scheme Source # | |
| Data Scheme Source # | |
| Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme # toConstr :: Scheme -> Constr # dataTypeOf :: Scheme -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) # gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # | |
| Ord Scheme Source # | |
| Show Scheme Source # | |
| Generic Scheme Source # | |
| Lift Scheme Source # | |
| type Rep Scheme Source # | |
showBaseUrl :: BaseUrl -> String Source #
>>>showBaseUrl <$> parseBaseUrl "api.example.com""http://api.example.com"
parseBaseUrl :: MonadThrow m => String -> m BaseUrl Source #
>>>parseBaseUrl "api.example.com"BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""}
Note: trailing slash is removed
>>>parseBaseUrl "api.example.com/"BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""}
>>>parseBaseUrl "api.example.com/dir/"BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = "/dir"}
newtype InvalidBaseUrlException Source #
Constructors
| InvalidBaseUrlException String | 
Instances
| Show InvalidBaseUrlException Source # | |
| Defined in Servant.Client.Core.BaseUrl Methods showsPrec :: Int -> InvalidBaseUrlException -> ShowS # show :: InvalidBaseUrlException -> String # showList :: [InvalidBaseUrlException] -> ShowS # | |
| Exception InvalidBaseUrlException Source # | |
| Defined in Servant.Client.Core.BaseUrl | |