| Copyright | (c) Soostone Inc. 2014-2015 Michael Xavier 2014-2015 | 
|---|---|
| License | BSD3 | 
| Maintainer | michael.xavier@soostone.com | 
| Stability | experimental | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
URI.ByteString
Description
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.
Synopsis
- 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 URIRef a where
- data Absolute
- data Relative
- data SchemaError
- data URIParseError
- data URIParserOptions = URIParserOptions {}
- strictURIParserOptions :: URIParserOptions
- laxURIParserOptions :: URIParserOptions
- data URINormalizationOptions = URINormalizationOptions {}
- noNormalization :: URINormalizationOptions
- rfc3986Normalization :: URINormalizationOptions
- httpNormalization :: URINormalizationOptions
- aggressiveNormalization :: URINormalizationOptions
- httpDefaultPorts :: Map Scheme Port
- toAbsolute :: Scheme -> URIRef a -> URIRef Absolute
- parseURI :: URIParserOptions -> ByteString -> Either URIParseError (URIRef Absolute)
- parseRelativeRef :: URIParserOptions -> ByteString -> Either URIParseError (URIRef Relative)
- uriParser :: URIParserOptions -> Parser (URIRef Absolute)
- relativeRefParser :: URIParserOptions -> Parser (URIRef Relative)
- serializeURIRef :: URIRef a -> Builder
- serializeURIRef' :: URIRef a -> ByteString
- serializeQuery :: URINormalizationOptions -> Query -> Builder
- serializeQuery' :: URINormalizationOptions -> Query -> ByteString
- serializeFragment :: Maybe ByteString -> Builder
- serializeFragment' :: Maybe ByteString -> ByteString
- serializeAuthority :: URINormalizationOptions -> Maybe Scheme -> Authority -> Builder
- serializeAuthority' :: URINormalizationOptions -> Maybe Scheme -> Authority -> ByteString
- serializeUserInfo :: UserInfo -> Builder
- serializeUserInfo' :: UserInfo -> ByteString
- normalizeURIRef :: URINormalizationOptions -> URIRef a -> Builder
- normalizeURIRef' :: URINormalizationOptions -> URIRef a -> ByteString
- urlEncodeQuery :: ByteString -> Builder
- urlEncodePath :: ByteString -> Builder
- urlEncode :: [Word8] -> ByteString -> Builder
- schemeBSL :: Lens' Scheme ByteString
- hostBSL :: Lens' Host ByteString
- portNumberL :: Lens' Port Int
- authorityUserInfoL :: Lens' Authority (Maybe UserInfo)
- authorityHostL :: Lens' Authority Host
- authorityPortL :: Lens' Authority (Maybe Port)
- uiUsernameL :: Lens' UserInfo ByteString
- uiPasswordL :: Lens' UserInfo ByteString
- queryPairsL :: Lens' Query [(ByteString, ByteString)]
- uriSchemeL :: Lens' (URIRef Absolute) Scheme
- authorityL :: Lens' (URIRef a) (Maybe Authority)
- pathL :: Lens' (URIRef a) ByteString
- queryL :: Lens' (URIRef a) Query
- fragmentL :: Lens' (URIRef a) (Maybe ByteString)
- upoValidQueryCharL :: Lens' URIParserOptions Bool
- type URI = URIRef Absolute
- type RelativeRef = URIRef Relative
- serializeURI :: URIRef Absolute -> Builder
- serializeURI' :: URIRef Absolute -> ByteString
- serializeRelativeRef :: URIRef Relative -> Builder
- serializeRelativeRef' :: URIRef Relative -> ByteString
- uriAuthorityL :: Lens' URI (Maybe Authority)
- uriPathL :: Lens' URI ByteString
- uriQueryL :: Lens' URI Query
- uriFragmentL :: Lens' URI (Maybe ByteString)
- rrAuthorityL :: Lens' RelativeRef (Maybe Authority)
- rrPathL :: Lens' RelativeRef ByteString
- rrQueryL :: Lens' RelativeRef Query
- rrFragmentL :: Lens' RelativeRef (Maybe ByteString)
URI-related types
Required first component to referring to a specification for the remainder of the URI's components, e.g. "http" or "https"
Constructors
| Scheme | |
| Fields | |
Instances
| Generic Scheme Source # | |
| Show Scheme Source # | |
| Eq Scheme Source # | |
| Ord Scheme Source # | |
| Lift Scheme Source # | |
| type Rep Scheme Source # | |
| Defined in URI.ByteString.Types type Rep Scheme = D1 ('MetaData "Scheme" "URI.ByteString.Types" "uri-bytestring-0.4.0.1-KWHje5pJZAgHzQBKGUpT1s" 'True) (C1 ('MetaCons "Scheme" 'PrefixI 'True) (S1 ('MetaSel ('Just "schemeBS") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
Constructors
| Host | |
| Fields 
 | |
Instances
| Generic Host Source # | |
| Show Host Source # | |
| Eq Host Source # | |
| Ord Host Source # | |
| Lift Host Source # | |
| type Rep Host Source # | |
| Defined in URI.ByteString.Types type Rep Host = D1 ('MetaData "Host" "URI.ByteString.Types" "uri-bytestring-0.4.0.1-KWHje5pJZAgHzQBKGUpT1s" 'True) (C1 ('MetaCons "Host" 'PrefixI 'True) (S1 ('MetaSel ('Just "hostBS") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
While some libraries have chosen to limit this to a Word16, the spec only specifies that the string be comprised of digits.
Constructors
| Port | |
| Fields 
 | |
Constructors
| Authority | |
| Fields | |
Instances
| Generic Authority Source # | |
| Show Authority Source # | |
| Eq Authority Source # | |
| Ord Authority Source # | |
| Lift Authority Source # | |
| type Rep Authority Source # | |
| Defined in URI.ByteString.Types type Rep Authority = D1 ('MetaData "Authority" "URI.ByteString.Types" "uri-bytestring-0.4.0.1-KWHje5pJZAgHzQBKGUpT1s" 'False) (C1 ('MetaCons "Authority" 'PrefixI 'True) (S1 ('MetaSel ('Just "authorityUserInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UserInfo)) :*: (S1 ('MetaSel ('Just "authorityHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Host) :*: S1 ('MetaSel ('Just "authorityPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Port))))) | |
Constructors
| UserInfo | |
| Fields | |
Instances
| Generic UserInfo Source # | |
| Show UserInfo Source # | |
| Eq UserInfo Source # | |
| Ord UserInfo Source # | |
| Defined in URI.ByteString.Types | |
| Lift UserInfo Source # | |
| type Rep UserInfo Source # | |
| Defined in URI.ByteString.Types type Rep UserInfo = D1 ('MetaData "UserInfo" "URI.ByteString.Types" "uri-bytestring-0.4.0.1-KWHje5pJZAgHzQBKGUpT1s" 'False) (C1 ('MetaCons "UserInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "uiUsername") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "uiPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
Constructors
| Query | |
| Fields 
 | |
Instances
| Monoid Query Source # | |
| Semigroup Query Source # | |
| Generic Query Source # | |
| Show Query Source # | |
| Eq Query Source # | |
| Ord Query Source # | |
| Lift Query Source # | |
| type Rep Query Source # | |
| Defined in URI.ByteString.Types type Rep Query = D1 ('MetaData "Query" "URI.ByteString.Types" "uri-bytestring-0.4.0.1-KWHje5pJZAgHzQBKGUpT1s" 'True) (C1 ('MetaCons "Query" 'PrefixI 'True) (S1 ('MetaSel ('Just "queryPairs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, ByteString)]))) | |
Note: URI fragment does not include the #
Constructors
| URI | |
| Fields 
 | |
| RelativeRef | |
| Fields 
 | |
data SchemaError Source #
URI Parser Types
Constructors
| NonAlphaLeading | Scheme must start with an alphabet character | 
| InvalidChars | Subsequent characters in the schema were invalid | 
| MissingColon | Schemas must be followed by a colon | 
Instances
data URIParseError Source #
Constructors
| MalformedScheme SchemaError | |
| MalformedUserInfo | |
| MalformedQuery | |
| MalformedFragment | |
| MalformedHost | |
| MalformedPort | |
| MalformedPath | |
| OtherError String | Catchall for unpredictable errors | 
Instances
data URIParserOptions Source #
Options for the parser. You will probably want to use either "strictURIParserOptions" or "laxURIParserOptions"
Constructors
| URIParserOptions | |
| Fields | |
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
data URINormalizationOptions Source #
Constructors
| URINormalizationOptions | |
| Fields 
 | |
Instances
| Show URINormalizationOptions Source # | |
| Defined in URI.ByteString.Types Methods showsPrec :: Int -> URINormalizationOptions -> ShowS # show :: URINormalizationOptions -> String # showList :: [URINormalizationOptions] -> ShowS # | |
| Eq URINormalizationOptions Source # | |
| Defined in URI.ByteString.Types Methods (==) :: URINormalizationOptions -> URINormalizationOptions -> Bool # (/=) :: URINormalizationOptions -> URINormalizationOptions -> Bool # | |
noNormalization :: URINormalizationOptions Source #
All normalization options disabled
rfc3986Normalization :: URINormalizationOptions Source #
Only normalizations deemed appropriate for all protocols by RFC3986 enabled, namely:
- Downcase Scheme
- Downcase Host
- Remove Dot Segments
httpNormalization :: URINormalizationOptions Source #
The same as rfc3986Normalization but with additional enabled
 features if you're working with HTTP URIs:
- Drop Default Port (with httpDefaultPorts)
- Drop Extra Slashes
aggressiveNormalization :: URINormalizationOptions Source #
All options enabled
httpDefaultPorts :: Map Scheme Port Source #
The set of known default ports to schemes. Currently only
 contains http/80 and https/443. Feel free to extend it if needed
 with unoDefaultPorts.
Operations
toAbsolute :: Scheme -> URIRef a -> URIRef Absolute Source #
toAbsolute scheme ref converts ref to an absolute URI.
 If ref is already absolute, then it is unchanged.
Parsing
parseURI :: URIParserOptions -> ByteString -> Either URIParseError (URIRef Absolute) 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 (URIRef Relative) Source #
Like parseURI, but do not parse scheme.
uriParser :: URIParserOptions -> Parser (URIRef Absolute) Source #
Underlying attoparsec parser. Useful for composing with your own parsers.
relativeRefParser :: URIParserOptions -> Parser (URIRef Relative) Source #
Underlying attoparsec parser. Useful for composing with your own parsers.
Serializing
serializeURIRef :: URIRef a -> Builder Source #
URI Serializer
Serialize a URI reference into a Builder.
Example of serializing + converting to a lazy Data.ByteString.Lazy.ByteString:
>>>BB.toLazyByteString $ serializeURIRef $ 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"
serializeURIRef' :: URIRef a -> ByteString Source #
Like serializeURIRef, with conversion into a strict ByteString.
serializeQuery :: URINormalizationOptions -> Query -> Builder Source #
Serialize the query part of a url
 serializeQuery opts mempty = ""
 serializeQuery opts (Query [("a","b"),("c","d")]) = "?a=b&c=d"
serializeAuthority :: URINormalizationOptions -> Maybe Scheme -> Authority -> Builder Source #
serializeUserInfo :: UserInfo -> Builder Source #
Normalized Serialization
normalizeURIRef :: URINormalizationOptions -> URIRef a -> Builder Source #
Similar to serializeURIRef but performs configurable degrees of
 URI normalization. If your goal is the fastest serialization speed
 possible, serializeURIRef will be fine. If you intend on
 comparing URIs (say for caching purposes), you'll want to use this.
normalizeURIRef' :: URINormalizationOptions -> URIRef a -> ByteString Source #
Low level utility functions
urlEncodeQuery :: ByteString -> Builder Source #
Encode a ByteString for use in the query section of a URL
urlEncodePath :: ByteString -> Builder Source #
Encode a ByteString for use in the path section of a URL
urlEncode :: [Word8] -> ByteString -> Builder Source #
Percent-encoding for URLs. Specify a list of additional unreserved characters to permit.
Lenses
Lenses over Scheme
schemeBSL :: Lens' Scheme ByteString Source #
Lenses over Host
hostBSL :: Lens' Host ByteString Source #
Lenses over Port
portNumberL :: Lens' Port Int Source #
Lenses over Authority
authorityHostL :: Lens' Authority Host Source #
Lenses over UserInfo
uiUsernameL :: Lens' UserInfo ByteString Source #
uiPasswordL :: Lens' UserInfo ByteString Source #
Lenses over Query
queryPairsL :: Lens' Query [(ByteString, ByteString)] Source #
Lenses over URIRef
pathL :: Lens' (URIRef a) ByteString Source #
Lenses over URIParserOptions
upoValidQueryCharL :: Lens' URIParserOptions Bool Source #
Deprecated
type RelativeRef = URIRef Relative Source #
serializeURI :: URIRef Absolute -> Builder Source #
Deprecated: Use serializeURIRef instead
Serialize a URI into a Builder.
serializeURI' :: URIRef Absolute -> ByteString Source #
Deprecated: Use serializeURIRef' instead
Like serializeURI, with conversion into a strict ByteString.
serializeRelativeRef :: URIRef Relative -> Builder Source #
Deprecated: Use serializeURIRef instead
Like serializeURI, but do not render scheme.
serializeRelativeRef' :: URIRef Relative -> ByteString Source #
Deprecated: Use serializeURIRef' instead
Like serializeRelativeRef, with conversion into a strict ByteString.
uriAuthorityL :: Lens' URI (Maybe Authority) Source #
Deprecated: Use authorityL instead
uriFragmentL :: Lens' URI (Maybe ByteString) Source #
Deprecated: Use fragmentL instead
rrAuthorityL :: Lens' RelativeRef (Maybe Authority) Source #
Deprecated: Use authorityL instead
rrPathL :: Lens' RelativeRef ByteString Source #
Deprecated: Use pathL instead
rrFragmentL :: Lens' RelativeRef (Maybe ByteString) Source #
Deprecated: Use fragmentL instead