-
Notifications
You must be signed in to change notification settings - Fork 25
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
1 parent
a661389
commit 1c0134c
Showing
11 changed files
with
1,143 additions
and
1,087 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,2 +1,3 @@ | ||
import Distribution.Simple | ||
|
||
main = defaultMain |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,84 +1,94 @@ | ||
{-# LANGUAGE FlexibleInstances #-} | ||
{-# LANGUAGE GADTs #-} | ||
{-# LANGUAGE GADTs #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# OPTIONS_GHC -fno-warn-orphans #-} | ||
|
||
module Main (main) where | ||
|
||
------------------------------------------------------------------------------- | ||
import Blaze.ByteString.Builder | ||
import Control.DeepSeq | ||
import Criterion.Main | ||
import Data.String | ||
import qualified Network.URI as NU | ||
import Blaze.ByteString.Builder | ||
import Control.DeepSeq | ||
import Criterion.Main | ||
import Data.String | ||
import qualified Network.URI as NU | ||
------------------------------------------------------------------------------- | ||
import URI.ByteString | ||
import URI.ByteString | ||
|
||
------------------------------------------------------------------------------- | ||
|
||
------------------------------------------------------------------------------- | ||
instance NFData Authority | ||
|
||
instance NFData Host | ||
|
||
instance NFData UserInfo | ||
|
||
instance NFData SchemaError | ||
|
||
instance NFData URIParseError | ||
|
||
instance NFData Scheme | ||
|
||
instance NFData Port | ||
|
||
instance NFData Query | ||
|
||
instance NFData (URIRef a) where | ||
rnf (URI a b c d e) = rnf a `seq` rnf b `seq` rnf c `seq` rnf d `seq` rnf e | ||
rnf (RelativeRef b c d e) = rnf b `seq` rnf c `seq` rnf d `seq` rnf e | ||
|
||
|
||
------------------------------------------------------------------------------- | ||
main :: IO () | ||
main = defaultMain | ||
[ | ||
bgroup "parsing" | ||
[ | ||
bench "Network.URI.parseURI" $ nf NU.parseURI exampleURIS | ||
, bench "URI.ByteString.parseURI strict" $ nf (parseURI strictURIParserOptions) exampleURIS | ||
, bench "URI.ByteString.parseURI lax" $ nf (parseURI laxURIParserOptions) exampleURIS | ||
, bench "URI.ByteString.parseRelativeRef strict" $ nf (parseRelativeRef strictURIParserOptions) exampleRelativeRefS | ||
, bench "URI.ByteString.parseRelativeRef lax" $ nf (parseRelativeRef laxURIParserOptions) exampleRelativeRefS | ||
] | ||
, bgroup "serializing" | ||
[ | ||
bench "URI.ByteString.serializeURIRef on URI" $ nf (toLazyByteString . serializeURIRef) exampleURI | ||
, bench "URI.ByteString.serializeURIRef on relative ref" $ nf (toLazyByteString . serializeURIRef) exampleRelativeRef | ||
main = | ||
defaultMain | ||
[ bgroup | ||
"parsing" | ||
[ bench "Network.URI.parseURI" $ nf NU.parseURI exampleURIS, | ||
bench "URI.ByteString.parseURI strict" $ nf (parseURI strictURIParserOptions) exampleURIS, | ||
bench "URI.ByteString.parseURI lax" $ nf (parseURI laxURIParserOptions) exampleURIS, | ||
bench "URI.ByteString.parseRelativeRef strict" $ nf (parseRelativeRef strictURIParserOptions) exampleRelativeRefS, | ||
bench "URI.ByteString.parseRelativeRef lax" $ nf (parseRelativeRef laxURIParserOptions) exampleRelativeRefS | ||
], | ||
bgroup | ||
"serializing" | ||
[ bench "URI.ByteString.serializeURIRef on URI" $ nf (toLazyByteString . serializeURIRef) exampleURI, | ||
bench "URI.ByteString.serializeURIRef on relative ref" $ nf (toLazyByteString . serializeURIRef) exampleRelativeRef | ||
] | ||
] | ||
] | ||
|
||
|
||
exampleURIS :: IsString s => s | ||
exampleURIS = "http://google.com/example?params=youbetcha" | ||
|
||
|
||
exampleRelativeRefS :: IsString s => s | ||
exampleRelativeRefS = "/example?params=youbetcha#17u" | ||
|
||
|
||
exampleURI :: URI | ||
exampleURI = URI { | ||
uriScheme = Scheme "http" | ||
, uriAuthority = Just Authority { | ||
authorityUserInfo = Nothing | ||
, authorityHost = Host "google.com" | ||
, authorityPort = Nothing | ||
} | ||
, uriPath = "/example" | ||
, uriQuery = Query [("params", "youbetcha")] | ||
, uriFragment = Nothing | ||
exampleURI = | ||
URI | ||
{ uriScheme = Scheme "http", | ||
uriAuthority = | ||
Just | ||
Authority | ||
{ authorityUserInfo = Nothing, | ||
authorityHost = Host "google.com", | ||
authorityPort = Nothing | ||
}, | ||
uriPath = "/example", | ||
uriQuery = Query [("params", "youbetcha")], | ||
uriFragment = Nothing | ||
} | ||
|
||
|
||
exampleRelativeRef :: RelativeRef | ||
exampleRelativeRef = RelativeRef { | ||
rrAuthority = Just Authority { | ||
authorityUserInfo = Nothing | ||
, authorityHost = Host "google.com" | ||
, authorityPort = Nothing | ||
} | ||
, rrPath = "/example" | ||
, rrQuery = Query [("params", "youbetcha")] | ||
, rrFragment = Nothing | ||
exampleRelativeRef = | ||
RelativeRef | ||
{ rrAuthority = | ||
Just | ||
Authority | ||
{ authorityUserInfo = Nothing, | ||
authorityHost = Host "google.com", | ||
authorityPort = Nothing | ||
}, | ||
rrPath = "/example", | ||
rrQuery = Query [("params", "youbetcha")], | ||
rrFragment = Nothing | ||
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,120 +1,135 @@ | ||
{-| | ||
Module : URI.ByteString | ||
Description : ByteString URI Parser and Serializer | ||
Copyright : (c) Soostone Inc., 2014-2015 | ||
Michael Xavier, 2014-2015 | ||
License : BSD3 | ||
Maintainer : [email protected] | ||
Stability : experimental | ||
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. | ||
-} | ||
-- | | ||
-- | ||
-- Module : URI.ByteString | ||
-- Description : ByteString URI Parser and Serializer | ||
-- Copyright : (c) Soostone Inc., 2014-2015 | ||
-- Michael Xavier, 2014-2015 | ||
-- License : BSD3 | ||
-- Maintainer : [email protected] | ||
-- Stability : experimental | ||
-- | ||
-- 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. | ||
module URI.ByteString | ||
(-- * URI-related types | ||
Scheme(..) | ||
, Host(..) | ||
, Port(..) | ||
, Authority(..) | ||
, UserInfo(..) | ||
, Query(..) | ||
, URIRef(..) | ||
, Absolute | ||
, Relative | ||
, SchemaError(..) | ||
, URIParseError(..) | ||
, URIParserOptions(..) | ||
, strictURIParserOptions | ||
, laxURIParserOptions | ||
, URINormalizationOptions(..) | ||
, noNormalization | ||
, rfc3986Normalization | ||
, httpNormalization | ||
, aggressiveNormalization | ||
, httpDefaultPorts | ||
( -- * URI-related types | ||
Scheme (..), | ||
Host (..), | ||
Port (..), | ||
Authority (..), | ||
UserInfo (..), | ||
Query (..), | ||
URIRef (..), | ||
Absolute, | ||
Relative, | ||
SchemaError (..), | ||
URIParseError (..), | ||
URIParserOptions (..), | ||
strictURIParserOptions, | ||
laxURIParserOptions, | ||
URINormalizationOptions (..), | ||
noNormalization, | ||
rfc3986Normalization, | ||
httpNormalization, | ||
aggressiveNormalization, | ||
httpDefaultPorts, | ||
|
||
-- * Operations | ||
, toAbsolute | ||
toAbsolute, | ||
|
||
-- * Parsing | ||
, parseURI | ||
, parseRelativeRef | ||
, uriParser | ||
, relativeRefParser | ||
parseURI, | ||
parseRelativeRef, | ||
uriParser, | ||
relativeRefParser, | ||
|
||
-- * Serializing | ||
, serializeURIRef | ||
, serializeURIRef' | ||
, serializeQuery | ||
, serializeQuery' | ||
, serializeFragment | ||
, serializeFragment' | ||
, serializeAuthority | ||
, serializeAuthority' | ||
, serializeUserInfo | ||
, serializeUserInfo' | ||
serializeURIRef, | ||
serializeURIRef', | ||
serializeQuery, | ||
serializeQuery', | ||
serializeFragment, | ||
serializeFragment', | ||
serializeAuthority, | ||
serializeAuthority', | ||
serializeUserInfo, | ||
serializeUserInfo', | ||
|
||
-- ** Normalized Serialization | ||
, normalizeURIRef | ||
, normalizeURIRef' | ||
normalizeURIRef, | ||
normalizeURIRef', | ||
|
||
-- * Low level utility functions | ||
, urlDecode | ||
, urlDecodeQuery | ||
, urlEncodeQuery | ||
, urlEncodePath | ||
, urlEncode | ||
urlDecode, | ||
urlDecodeQuery, | ||
urlEncodeQuery, | ||
urlEncodePath, | ||
urlEncode, | ||
|
||
-- * Lenses | ||
|
||
-- ** Lenses over 'Scheme' | ||
, schemeBSL | ||
schemeBSL, | ||
|
||
-- ** Lenses over 'Host' | ||
, hostBSL | ||
hostBSL, | ||
|
||
-- ** Lenses over 'Port' | ||
, portNumberL | ||
portNumberL, | ||
|
||
-- ** Lenses over 'Authority' | ||
, authorityUserInfoL | ||
, authorityHostL | ||
, authorityPortL | ||
authorityUserInfoL, | ||
authorityHostL, | ||
authorityPortL, | ||
|
||
-- ** Lenses over 'UserInfo' | ||
, uiUsernameL | ||
, uiPasswordL | ||
uiUsernameL, | ||
uiPasswordL, | ||
|
||
-- ** Lenses over 'Query' | ||
, queryPairsL | ||
queryPairsL, | ||
|
||
-- ** Lenses over 'URIRef' | ||
, uriSchemeL | ||
, authorityL | ||
, pathL | ||
, queryL | ||
, fragmentL | ||
uriSchemeL, | ||
authorityL, | ||
pathL, | ||
queryL, | ||
fragmentL, | ||
|
||
-- ** Lenses over 'URIParserOptions' | ||
, upoValidQueryCharL | ||
upoValidQueryCharL, | ||
|
||
-- ** Deprecated | ||
, URI | ||
, RelativeRef | ||
, serializeURI | ||
, serializeURI' | ||
, serializeRelativeRef | ||
, serializeRelativeRef' | ||
, uriAuthorityL | ||
, uriPathL | ||
, uriQueryL | ||
, uriFragmentL | ||
, rrAuthorityL | ||
, rrPathL | ||
, rrQueryL | ||
, rrFragmentL | ||
) where | ||
URI, | ||
RelativeRef, | ||
serializeURI, | ||
serializeURI', | ||
serializeRelativeRef, | ||
serializeRelativeRef', | ||
uriAuthorityL, | ||
uriPathL, | ||
uriQueryL, | ||
uriFragmentL, | ||
rrAuthorityL, | ||
rrPathL, | ||
rrQueryL, | ||
rrFragmentL, | ||
) | ||
where | ||
|
||
------------------------------------------------------------------------------- | ||
import URI.ByteString.Internal | ||
import URI.ByteString.Lens | ||
import URI.ByteString.Types | ||
import URI.ByteString.Internal | ||
import URI.ByteString.Lens | ||
import URI.ByteString.Types | ||
|
||
------------------------------------------------------------------------------- |
Oops, something went wrong.