Copyright | (c) Soostone Inc., 2014-2015 Michael Xavier, 2014-2015 |
---|---|
License | BSD3 |
Maintainer | michael.xavier@soostone.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
URI.ByteString aims to be an RFC3986 compliant URI parser that uses efficient ByteStrings for parsing and representing the data. This module provides a URI datatype as well as a parser and serializer.
Note that this library is an early release and may have issues. It is currently being used in production and no issues have been encountered, however. Please report any issues encountered to the issue tracker.
This module also provides analogs to Lens over the various types in this library. These are written in a generic way to avoid a dependency on any particular lens library. You should be able to use these with a number of packages including lens and lens-family-core.
- newtype Scheme = Scheme {}
- newtype Host = Host {
- hostBS :: ByteString
- newtype Port = Port {
- portNumber :: Int
- data Authority = Authority {}
- data UserInfo = UserInfo {}
- newtype Query = Query {
- queryPairs :: [(ByteString, ByteString)]
- data URI = URI {}
- data RelativeRef = RelativeRef {}
- data SchemaError
- data URIParseError
- data URIParserOptions = URIParserOptions {
- upoValidQueryChar :: Word8 -> Bool
- strictURIParserOptions :: URIParserOptions
- laxURIParserOptions :: URIParserOptions
- parseURI :: URIParserOptions -> ByteString -> Either URIParseError URI
- parseRelativeRef :: URIParserOptions -> ByteString -> Either URIParseError RelativeRef
- serializeURI :: URI -> Builder
- serializeRelativeRef :: RelativeRef -> Builder
- schemeBSL :: Functor f => (ByteString -> f ByteString) -> Scheme -> f Scheme
- hostBSL :: Functor f => (ByteString -> f ByteString) -> Host -> f Host
- portNumberL :: Functor f => (Int -> f Int) -> Port -> f Port
- authorityUserInfoL :: Functor f => (Maybe UserInfo -> f (Maybe UserInfo)) -> Authority -> f Authority
- authorityHostL :: Functor f => (Host -> f Host) -> Authority -> f Authority
- authorityPortL :: Functor f => (Maybe Port -> f (Maybe Port)) -> Authority -> f Authority
- uiUsernameL :: Functor f => (ByteString -> f ByteString) -> UserInfo -> f UserInfo
- uiPasswordL :: Functor f => (ByteString -> f ByteString) -> UserInfo -> f UserInfo
- queryPairsL :: Functor f => ([(ByteString, ByteString)] -> f [(ByteString, ByteString)]) -> Query -> f Query
- uriSchemeL :: Functor f => (Scheme -> f Scheme) -> URI -> f URI
- uriAuthorityL :: Functor f => (Maybe Authority -> f (Maybe Authority)) -> URI -> f URI
- uriPathL :: Functor f => (ByteString -> f ByteString) -> URI -> f URI
- uriQueryL :: Functor f => (Query -> f Query) -> URI -> f URI
- uriFragmentL :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> URI -> f URI
- rrAuthorityL :: Functor f => (Maybe Authority -> f (Maybe Authority)) -> RelativeRef -> f RelativeRef
- rrPathL :: Functor f => (ByteString -> f ByteString) -> RelativeRef -> f RelativeRef
- rrQueryL :: Functor f => (Query -> f Query) -> RelativeRef -> f RelativeRef
- rrFragmentL :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> RelativeRef -> f RelativeRef
- upoValidQueryCharL :: Functor f => ((Word8 -> Bool) -> f (Word8 -> Bool)) -> URIParserOptions -> f URIParserOptions
URI-related types
Required first component to referring to a specification for the remainder of the URI's components, e.g. "http" or "https"
Host | |
|
While some libraries have chosen to limit this to a Word16, the spec only specifies that the string be comprised of digits.
Port | |
|
Query | |
|
URI | |
|
data RelativeRef Source
RelativeRef | |
|
data SchemaError Source
URI Parser Types
NonAlphaLeading | Scheme must start with an alphabet character |
InvalidChars | Subsequent characters in the schema were invalid |
MissingColon | Schemas must be followed by a colon |
data URIParseError Source
MalformedScheme SchemaError | |
MalformedUserInfo | |
MalformedQuery | |
MalformedFragment | |
MalformedHost | |
MalformedPort | |
MalformedPath | |
OtherError String | Catchall for unpredictable errors |
data URIParserOptions Source
Options for the parser. You will probably want to use either "strictURIParserOptions" or "laxURIParserOptions"
strictURIParserOptions :: URIParserOptions Source
Strict URI Parser config. Follows RFC3986 as-specified. Use this if you can be certain that your URIs are properly encoded or if you want parsing to fail if they deviate from the spec at all.
laxURIParserOptions :: URIParserOptions Source
Lax URI Parser config. Use this if you you want to handle common deviations from the spec gracefully.
- Allows non-encoded [ and ] in query string
Parsing
parseURI :: URIParserOptions -> ByteString -> Either URIParseError URI Source
Parse a strict ByteString into a URI or an error.
Example:
>>>
parseURI strictURIParserOptions "http://www.example.org/foo?bar=baz#quux"
Right (URI {uriScheme = Scheme {schemeBS = "http"}, uriAuthority = Just (Authority {authorityUserInfo = Nothing, authorityHost = Host {hostBS = "www.example.org"}, authorityPort = Nothing}), uriPath = "/foo", uriQuery = Query {queryPairs = [("bar","baz")]}, uriFragment = Just "quux"})
>>>
parseURI strictURIParserOptions "$$$$://badurl.example.org"
Left (MalformedScheme NonAlphaLeading)
There are some urls that you'll encounter which defy the spec, such as those with square brackets in the query string. If you must be able to parse those, you can use "laxURIParserOptions" or specify your own
>>>
parseURI strictURIParserOptions "http://www.example.org/foo?bar[]=baz"
Left MalformedQuery
>>>
parseURI laxURIParserOptions "http://www.example.org/foo?bar[]=baz"
Right (URI {uriScheme = Scheme {schemeBS = "http"}, uriAuthority = Just (Authority {authorityUserInfo = Nothing, authorityHost = Host {hostBS = "www.example.org"}, authorityPort = Nothing}), uriPath = "/foo", uriQuery = Query {queryPairs = [("bar[]","baz")]}, uriFragment = Nothing})
>>>
let myLaxOptions = URIParserOptions { upoValidQueryChar = liftA2 (||) (upoValidQueryChar strictURIParserOptions) (inClass "[]")}
>>>
parseURI myLaxOptions "http://www.example.org/foo?bar[]=baz"
Right (URI {uriScheme = Scheme {schemeBS = "http"}, uriAuthority = Just (Authority {authorityUserInfo = Nothing, authorityHost = Host {hostBS = "www.example.org"}, authorityPort = Nothing}), uriPath = "/foo", uriQuery = Query {queryPairs = [("bar[]","baz")]}, uriFragment = Nothing})
parseRelativeRef :: URIParserOptions -> ByteString -> Either URIParseError RelativeRef Source
Like parseURI
, but do not parse scheme.
Serializing
serializeURI :: URI -> Builder Source
URI Serializer
Serialize a URI into a strict ByteString Example:
>>>
BB.toLazyByteString $ serializeURI $ URI {uriScheme = Scheme {schemeBS = "http"}, uriAuthority = Just (Authority {authorityUserInfo = Nothing, authorityHost = Host {hostBS = "www.example.org"}, authorityPort = Nothing}), uriPath = "/foo", uriQuery = Query {queryPairs = [("bar","baz")]}, uriFragment = Just "quux"}
"http://www.example.org/foo?bar=baz#quux"
serializeRelativeRef :: RelativeRef -> Builder Source
Like serializeURI
, but do not render scheme.
Lenses
Lenses over Scheme
schemeBSL :: Functor f => (ByteString -> f ByteString) -> Scheme -> f Scheme Source
schemeBSL :: Lens'Scheme
ByteString
Lenses over Host
hostBSL :: Functor f => (ByteString -> f ByteString) -> Host -> f Host Source
hostBSL :: Lens'Host
ByteString
Lenses over Port
Lenses over Authority
authorityUserInfoL :: Functor f => (Maybe UserInfo -> f (Maybe UserInfo)) -> Authority -> f Authority Source
Lenses over UserInfo
uiUsernameL :: Functor f => (ByteString -> f ByteString) -> UserInfo -> f UserInfo Source
uiUsernameL :: Lens'UserInfo
ByteString
uiPasswordL :: Functor f => (ByteString -> f ByteString) -> UserInfo -> f UserInfo Source
uiPasswordL :: Lens'UserInfo
ByteString
Lenses over Query
queryPairsL :: Functor f => ([(ByteString, ByteString)] -> f [(ByteString, ByteString)]) -> Query -> f Query Source
queryPairsL :: Lens'Query
[(ByteString
,ByteString
)]
Lenses over URI
uriPathL :: Functor f => (ByteString -> f ByteString) -> URI -> f URI Source
uriPathL :: Lens'URI
ByteString
uriFragmentL :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> URI -> f URI Source
uriFragmentL :: Lens'URI
(Maybe
ByteString
)
Lenses over RelativeRef
rrAuthorityL :: Functor f => (Maybe Authority -> f (Maybe Authority)) -> RelativeRef -> f RelativeRef Source
rrAuthorityL :: Lens'RelativeRef
(Maybe
Authority
)
rrPathL :: Functor f => (ByteString -> f ByteString) -> RelativeRef -> f RelativeRef Source
rrPathL :: Lens'RelativeRef
ByteString
rrQueryL :: Functor f => (Query -> f Query) -> RelativeRef -> f RelativeRef Source
rrQueryL :: Lens'RelativeRef
Query
rrFragmentL :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> RelativeRef -> f RelativeRef Source
rrFragmentL :: Lens'RelativeRef
(Maybe
ByteString
)
Lenses over URIParserOptions
upoValidQueryCharL :: Functor f => ((Word8 -> Bool) -> f (Word8 -> Bool)) -> URIParserOptions -> f URIParserOptions Source
upoValidQueryCharL :: Lens' URIParserOptions (Word8 -> Bool)