Skip to content

Commit 674788d

Browse files
authored
Merge pull request #33 from garyb/re-exports
Re-export everything relevant from each module
2 parents 6bfb21c + c5d46ab commit 674788d

16 files changed

+297
-169
lines changed

src/Data/URI.purs

Lines changed: 31 additions & 133 deletions
Original file line numberDiff line numberDiff line change
@@ -1,133 +1,31 @@
1-
module Data.URI where
2-
3-
import Prelude
4-
5-
import Data.Either (Either)
6-
import Data.Generic.Rep (class Generic)
7-
import Data.Generic.Rep.Show (genericShow)
8-
import Data.List (List)
9-
import Data.Maybe (Maybe)
10-
import Data.Monoid (class Monoid)
11-
import Data.Newtype (class Newtype)
12-
import Data.Path.Pathy (Path, File, Dir, Abs, Rel, Sandboxed, Unsandboxed)
13-
import Data.Tuple (Tuple)
14-
15-
-- | A generic URI
16-
data URI = URI (Maybe Scheme) HierarchicalPart (Maybe Query) (Maybe Fragment)
17-
18-
derive instance eqURIEq URI
19-
derive instance ordURIOrd URI
20-
derive instance genericURIGeneric URI _
21-
instance showURIShow URI where show = genericShow
22-
23-
-- | An absolute URI.
24-
data AbsoluteURI = AbsoluteURI (Maybe Scheme) HierarchicalPart (Maybe Query)
25-
26-
derive instance eqAbsoluteURIEq AbsoluteURI
27-
derive instance ordAbsoluteURIOrd AbsoluteURI
28-
derive instance genericAbsoluteURIGeneric AbsoluteURI _
29-
instance showAbsoluteURIShow AbsoluteURI where show = genericShow
30-
31-
-- | A relative reference for a URI.
32-
data RelativeRef = RelativeRef RelativePart (Maybe Query) (Maybe Fragment)
33-
34-
derive instance eqRelativeRefEq RelativeRef
35-
derive instance ordRelativeRefOrd RelativeRef
36-
derive instance genericRelativeRefGeneric RelativeRef _
37-
instance showRelativeRefShow RelativeRef where show = genericShow
38-
39-
-- | A general URI path, can be used to represent relative or absolute paths
40-
-- | that are sandboxed or unsandboxed.
41-
type URIPath a s = Either (Path a Dir s) (Path a File s)
42-
43-
-- | The path part for a generic or absolute URI.
44-
type URIPathAbs = URIPath Abs Sandboxed
45-
46-
-- | The path part for a relative reference.
47-
type URIPathRel = URIPath Rel Unsandboxed
48-
49-
-- | An alias for the most common use case of resource identifiers.
50-
type URIRef = Either URI RelativeRef
51-
52-
-- | The scheme part of an absolute URI. For example: `http`, `ftp`, `git`.
53-
newtype Scheme = Scheme String
54-
55-
derive newtype instance eqSchemeEq Scheme
56-
derive newtype instance ordSchemeOrd Scheme
57-
derive instance genericSchemeGeneric Scheme _
58-
derive instance newtypeSchemeNewtype Scheme _
59-
instance showSchemeShow Scheme where show = genericShow
60-
61-
-- | The "hierarchical part" of a generic or absolute URI.
62-
data HierarchicalPart = HierarchicalPart (Maybe Authority) (Maybe URIPathAbs)
63-
64-
derive instance eqHierarchicalPartEq HierarchicalPart
65-
derive instance ordHierarchicalPartOrd HierarchicalPart
66-
derive instance genericHierarchicalPartGeneric HierarchicalPart _
67-
instance showHierarchicalPartShow HierarchicalPart where show = genericShow
68-
69-
-- | The "relative part" of a relative reference.
70-
data RelativePart = RelativePart (Maybe Authority) (Maybe URIPathRel)
71-
72-
derive instance eqRelativePartEq RelativePart
73-
derive instance ordRelativePartOrd RelativePart
74-
derive instance genericRelativePartGeneric RelativePart _
75-
instance showRelativePartShow RelativePart where show = genericShow
76-
77-
-- | The authority part of a URI. For example: `purescript.org`,
78-
-- | `localhost:3000`, `[email protected]`
79-
data Authority = Authority (Maybe UserInfo) (Array (Tuple Host (Maybe Port)))
80-
81-
derive instance eqAuthorityEq Authority
82-
derive instance ordAuthorityOrd Authority
83-
derive instance genericAuthorityGeneric Authority _
84-
instance showAuthorityShow Authority where show = genericShow
85-
86-
-- | The user info part of an `Authority`. For example: `user`, `foo:bar`.
87-
newtype UserInfo = UserInfo String
88-
89-
derive newtype instance eqUserInfoEq UserInfo
90-
derive newtype instance ordUserInfoOrd UserInfo
91-
derive instance genericUserInfoGeneric UserInfo _
92-
derive instance newtypeUserInfoNewtype UserInfo _
93-
instance showUserInfoShow UserInfo where show = genericShow
94-
95-
-- | A host address.
96-
data Host
97-
= IPv6Address String
98-
| IPv4Address String
99-
| NameAddress String
100-
101-
derive instance eqHostEq Host
102-
derive instance ordHostOrd Host
103-
derive instance genericHostGeneric Host _
104-
instance showHostShow Host where show = genericShow
105-
106-
-- | A port number.
107-
newtype Port = Port Int
108-
109-
derive newtype instance eqPortEq Port
110-
derive newtype instance ordPortOrd Port
111-
derive instance genericPortGeneric Port _
112-
derive instance newtypePortNewtype Port _
113-
instance showPortShow Port where show = genericShow
114-
115-
-- | The query component of a URI.
116-
newtype Query = Query (List (Tuple String (Maybe String)))
117-
118-
derive newtype instance eqQueryEq Query
119-
derive newtype instance ordQueryOrd Query
120-
derive instance genericQueryGeneric Query _
121-
derive instance newtypeQueryNewtype Query _
122-
instance showQueryShow Query where show = genericShow
123-
derive newtype instance semigroupQuerySemigroup Query
124-
derive newtype instance monoidQueryMonoid Query
125-
126-
-- | The hash fragment of a URI.
127-
newtype Fragment = Fragment String
128-
129-
derive newtype instance eqFragmentEq Fragment
130-
derive newtype instance ordFragmentOrd Fragment
131-
derive instance genericFragmentGeneric Fragment _
132-
derive instance newtypeFragmentNewtype Fragment _
133-
instance showFragmentShow Fragment where show = genericShow
1+
module Data.URI
2+
( module Data.URI.AbsoluteURI
3+
, module Data.URI.Authority
4+
, module Data.URI.Fragment
5+
, module Data.URI.HierarchicalPart
6+
, module Data.URI.Host
7+
, module Data.URI.Path
8+
, module Data.URI.Port
9+
, module Data.URI.Query
10+
, module Data.URI.RelativePart
11+
, module Data.URI.RelativeRef
12+
, module Data.URI.Scheme
13+
, module Data.URI.URI
14+
, module Data.URI.URIRef
15+
, module Data.URI.UserInfo
16+
) where
17+
18+
import Data.URI.AbsoluteURI (AbsoluteURI(..))
19+
import Data.URI.Authority (Authority(..))
20+
import Data.URI.Fragment (Fragment(..))
21+
import Data.URI.HierarchicalPart (HierarchicalPart(..))
22+
import Data.URI.Host (Host(..))
23+
import Data.URI.Path (URIPath, URIPathAbs, URIPathRel)
24+
import Data.URI.Port (Port(..))
25+
import Data.URI.Query (Query(..))
26+
import Data.URI.RelativePart (RelativePart(..))
27+
import Data.URI.RelativeRef (RelativeRef(..))
28+
import Data.URI.Scheme (Scheme(..))
29+
import Data.URI.URI (URI(..))
30+
import Data.URI.URIRef (URIRef)
31+
import Data.URI.UserInfo (UserInfo(..))

src/Data/URI/AbsoluteURI.purs

Lines changed: 25 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,43 @@
1-
module Data.URI.AbsoluteURI where
1+
module Data.URI.AbsoluteURI
2+
( AbsoluteURI(..)
3+
, parse
4+
, parser
5+
, print
6+
, _scheme
7+
, _hierPart
8+
, _query
9+
, module Data.URI.HierarchicalPart
10+
, module Data.URI.Query
11+
, module Data.URI.Scheme
12+
) where
213

314
import Prelude
415

516
import Data.Array (catMaybes)
617
import Data.Either (Either)
18+
import Data.Generic.Rep (class Generic)
19+
import Data.Generic.Rep.Show (genericShow)
720
import Data.Lens (Lens', lens)
821
import Data.Maybe (Maybe(..))
922
import Data.String as S
10-
import Data.URI (AbsoluteURI(..), HierarchicalPart, Query, Scheme)
1123
import Data.URI.HierarchicalPart as HPart
24+
import Data.URI.HierarchicalPart (Authority(..), HierarchicalPart(..), Host(..), Port(..), URIPath, URIPathAbs, URIPathRel, UserInfo(..), _IPv4Address, _IPv6Address, _NameAddress, _authority, _hosts, _path, _userInfo)
1225
import Data.URI.Query as Query
26+
import Data.URI.Query (Query(..))
1327
import Data.URI.Scheme as Scheme
28+
import Data.URI.Scheme (Scheme(..))
1429
import Text.Parsing.StringParser (ParseError, Parser, runParser)
1530
import Text.Parsing.StringParser.Combinators (optionMaybe)
1631
import Text.Parsing.StringParser.String (eof)
1732

33+
-- | An absolute URI.
34+
data AbsoluteURI = AbsoluteURI (Maybe Scheme) HierarchicalPart (Maybe Query)
35+
36+
derive instance eqAbsoluteURIEq AbsoluteURI
37+
derive instance ordAbsoluteURIOrd AbsoluteURI
38+
derive instance genericAbsoluteURIGeneric AbsoluteURI _
39+
instance showAbsoluteURIShow AbsoluteURI where show = genericShow
40+
1841
parse String Either ParseError AbsoluteURI
1942
parse = runParser parser
2043

src/Data/URI/Authority.purs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,42 @@
1-
module Data.URI.Authority where
1+
module Data.URI.Authority
2+
( Authority(..)
3+
, parser
4+
, print
5+
, _userInfo
6+
, _hosts
7+
, module Data.URI.Host
8+
, module Data.URI.Port
9+
, module Data.URI.UserInfo
10+
) where
211

312
import Prelude
413

514
import Data.Array (fromFoldable)
15+
import Data.Generic.Rep (class Generic)
16+
import Data.Generic.Rep.Show (genericShow)
617
import Data.Lens (Lens', lens)
718
import Data.Maybe (Maybe, maybe)
819
import Data.String as S
920
import Data.Tuple (Tuple(..))
10-
import Data.URI (Authority(..), Host, Port, UserInfo)
21+
import Data.URI.Host (Host(..), _IPv4Address, _IPv6Address, _NameAddress)
1122
import Data.URI.Host as Host
23+
import Data.URI.Port (Port(..))
1224
import Data.URI.Port as Port
25+
import Data.URI.UserInfo (UserInfo(..))
1326
import Data.URI.UserInfo as UserInfo
1427
import Text.Parsing.StringParser (Parser, try)
1528
import Text.Parsing.StringParser.Combinators (optionMaybe, sepBy)
1629
import Text.Parsing.StringParser.String (string)
1730

31+
-- | The authority part of a URI. For example: `purescript.org`,
32+
-- | `localhost:3000`, `[email protected]`
33+
data Authority = Authority (Maybe UserInfo) (Array (Tuple Host (Maybe Port)))
34+
35+
derive instance eqAuthorityEq Authority
36+
derive instance ordAuthorityOrd Authority
37+
derive instance genericAuthorityGeneric Authority _
38+
instance showAuthorityShow Authority where show = genericShow
39+
1840
parser Parser Authority
1941
parser = do
2042
_ ← string "//"

src/Data/URI/Fragment.purs

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,31 @@
1-
module Data.URI.Fragment (parser, print) where
1+
module Data.URI.Fragment where
22

33
import Prelude
44

55
import Control.Alt ((<|>))
66
import Data.Either (fromRight)
7+
import Data.Generic.Rep (class Generic)
8+
import Data.Generic.Rep.Show (genericShow)
9+
import Data.Newtype (class Newtype)
710
import Data.String as S
811
import Data.String.Regex as RX
912
import Data.String.Regex.Flags as RXF
10-
import Data.URI (Fragment(..))
1113
import Data.URI.Common (decodePCTComponent, joinWith, parsePChar)
1214
import Global (encodeURIComponent)
1315
import Partial.Unsafe (unsafePartial)
1416
import Text.Parsing.StringParser (Parser)
1517
import Text.Parsing.StringParser.Combinators (many)
1618
import Text.Parsing.StringParser.String (string)
1719

20+
-- | The hash fragment of a URI.
21+
newtype Fragment = Fragment String
22+
23+
derive newtype instance eqFragmentEq Fragment
24+
derive newtype instance ordFragmentOrd Fragment
25+
derive instance genericFragmentGeneric Fragment _
26+
derive instance newtypeFragmentNewtype Fragment _
27+
instance showFragmentShow Fragment where show = genericShow
28+
1829
parser Parser Fragment
1930
parser = string "#" *>
2031
(Fragment <<< joinWith ""

src/Data/URI/HierarchicalPart.purs

Lines changed: 26 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,35 +1,54 @@
1-
module Data.URI.HierarchicalPart where
1+
module Data.URI.HierarchicalPart
2+
( HierarchicalPart(..)
3+
, parser
4+
, print
5+
, _authority
6+
, _path
7+
, module Data.URI.Authority
8+
, module Data.URI.Path
9+
) where
210

311
import Prelude
412

513
import Control.Alt ((<|>))
614
import Data.Array (catMaybes)
15+
import Data.Generic.Rep (class Generic)
16+
import Data.Generic.Rep.Show (genericShow)
717
import Data.Lens (Lens', lens)
818
import Data.Maybe (Maybe(..))
919
import Data.String as S
10-
import Data.URI (Authority, HierarchicalPart(..), URIPathAbs)
20+
import Data.URI.Authority (Authority(..), Host(..), Port(..), UserInfo(..), _IPv4Address, _IPv6Address, _NameAddress, _hosts, _userInfo)
1121
import Data.URI.Authority as Authority
12-
import Data.URI.Path (printPath, parseURIPathAbs, parsePathRootless, parsePathAbsolute, parsePathAbEmpty)
22+
import Data.URI.Path (URIPath, URIPathAbs, URIPathRel)
23+
import Data.URI.Path as Path
1324
import Text.Parsing.StringParser (Parser)
1425

26+
-- | The "hierarchical part" of a generic or absolute URI.
27+
data HierarchicalPart = HierarchicalPart (Maybe Authority) (Maybe URIPathAbs)
28+
29+
derive instance eqHierarchicalPartEq HierarchicalPart
30+
derive instance ordHierarchicalPartOrd HierarchicalPart
31+
derive instance genericHierarchicalPartGeneric HierarchicalPart _
32+
instance showHierarchicalPartShow HierarchicalPart where show = genericShow
33+
1534
parser Parser HierarchicalPart
1635
parser = withAuth <|> withoutAuth
1736
where
1837
withAuth =
1938
HierarchicalPart <<< Just
2039
<$> Authority.parser
21-
<*> parsePathAbEmpty parseURIPathAbs
40+
<*> Path.parsePathAbEmpty Path.parseURIPathAbs
2241

2342
withoutAuth = HierarchicalPart Nothing <$> noAuthPath
2443

2544
noAuthPath
26-
= (Just <$> parsePathAbsolute parseURIPathAbs)
27-
<|> (Just <$> parsePathRootless parseURIPathAbs)
45+
= (Just <$> Path.parsePathAbsolute Path.parseURIPathAbs)
46+
<|> (Just <$> Path.parsePathRootless Path.parseURIPathAbs)
2847
<|> pure Nothing
2948

3049
print HierarchicalPart String
3150
print (HierarchicalPart a p) =
32-
S.joinWith "" (catMaybes [Authority.print <$> a, printPath <$> p])
51+
S.joinWith "" (catMaybes [Authority.print <$> a, Path.printPath <$> p])
3352

3453
_authority Lens' HierarchicalPart (Maybe Authority)
3554
_authority =

src/Data/URI/Host.purs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,40 @@
1-
module Data.URI.Host where
1+
module Data.URI.Host
2+
( Host(..)
3+
, parser
4+
, ipv6AddressParser
5+
, ipv4AddressParser
6+
, regNameParser
7+
, print
8+
, _IPv6Address
9+
, _IPv4Address
10+
, _NameAddress
11+
) where
212

313
import Prelude
414

515
import Control.Alt ((<|>))
16+
import Data.Generic.Rep (class Generic)
17+
import Data.Generic.Rep.Show (genericShow)
618
import Data.Int as Int
719
import Data.Lens (Prism', prism')
820
import Data.Maybe (Maybe(..))
9-
import Data.URI (Host(..))
1021
import Data.URI.Common (decodePCT, joinWith, parsePCTEncoded, parseSubDelims, parseUnreserved, rxPat)
1122
import Global (encodeURI)
1223
import Text.Parsing.StringParser (Parser, try, fail)
1324
import Text.Parsing.StringParser.Combinators ((<?>), many1)
1425
import Text.Parsing.StringParser.String (string, char)
1526

27+
-- | A host address.
28+
data Host
29+
= IPv6Address String
30+
| IPv4Address String
31+
| NameAddress String
32+
33+
derive instance eqHostEq Host
34+
derive instance ordHostOrd Host
35+
derive instance genericHostGeneric Host _
36+
instance showHostShow Host where show = genericShow
37+
1638
parser Parser Host
1739
parser = ipv6AddressParser <|> ipv4AddressParser <|> try regNameParser
1840

0 commit comments

Comments
 (0)