uri-bytestring-0.1.5: Haskell URI parsing as ByteStrings

Copyright(c) Soostone Inc., 2014-2015 Michael Xavier, 2014-2015
LicenseBSD3
Maintainermichael.xavier@soostone.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

URI.ByteString

Contents

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

URI-related types

newtype Scheme Source

Required first component to referring to a specification for the remainder of the URI's components, e.g. "http" or "https"

Constructors

Scheme 

Fields

schemeBS :: ByteString
 

newtype Host Source

Constructors

Host 

Fields

hostBS :: ByteString
 

Instances

newtype Port Source

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

portNumber :: Int
 

Instances

newtype Query Source

Constructors

Query 

data URI Source

Constructors

URI 

Fields

uriScheme :: Scheme
 
uriAuthority :: Maybe Authority
 
uriPath :: ByteString
 
uriQuery :: Query
 
uriFragment :: Maybe ByteString

URI fragment. Does not include the #

Instances

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

data URIParserOptions Source

Options for the parser. You will probably want to use either "strictURIParserOptions" or "laxURIParserOptions"

Constructors

URIParserOptions 

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})

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

portNumberL :: Functor f => (Int -> f Int) -> Port -> f Port Source

portNumberL :: Lens' Port Int

Lenses over Authority

authorityUserInfoL :: Functor f => (Maybe UserInfo -> f (Maybe UserInfo)) -> Authority -> f Authority Source

authorityUserInfoL :: Lens' Authority (Maybe UserInfo)

authorityHostL :: Functor f => (Host -> f Host) -> Authority -> f Authority Source

authorityHostL :: Lens' Authority Host

authorityPortL :: Functor f => (Maybe Port -> f (Maybe Port)) -> Authority -> f Authority Source

authorityPortL :: Lens' Authority (Maybe Port)

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

uriSchemeL :: Functor f => (Scheme -> f Scheme) -> URI -> f URI Source

uriSchemeL :: Lens' URI Scheme

uriAuthorityL :: Functor f => (Maybe Authority -> f (Maybe Authority)) -> URI -> f URI Source

uriAuthorityL :: Lens' URI (Maybe Authority)

uriPathL :: Functor f => (ByteString -> f ByteString) -> URI -> f URI Source

uriPathL :: Lens' URI ByteString

uriQueryL :: Functor f => (Query -> f Query) -> URI -> f URI Source

uriQueryL :: Lens' URI Query

uriFragmentL :: Functor f => (Maybe ByteString -> f (Maybe ByteString)) -> URI -> f URI Source

uriFragmentL :: Lens' URI (Maybe ByteString)

Lenses over RelativeRef

rrQueryL :: Functor f => (Query -> f Query) -> RelativeRef -> f RelativeRef Source

rrQueryL :: Lens' RelativeRef Query

Lenses over URIParserOptions

upoValidQueryCharL :: Functor f => ((Word8 -> Bool) -> f (Word8 -> Bool)) -> URIParserOptions -> f URIParserOptions Source

upoValidQueryCharL :: Lens' URIParserOptions (Word8 -> Bool)