heddit-0.2: Reddit API bindings
Copyright(c) 2021 Rory Tyler Hayford
LicenseBSD-3-Clause
Maintainerrory.hayford@protonmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Network.Reddit.Types

Description

 
Synopsis

Reddit

data RedditT m a Source #

The monad tranformer in which Reddit API transactions can be executed

Instances

Instances details
Monad m => MonadReader Client (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

ask :: RedditT m Client #

local :: (Client -> Client) -> RedditT m a -> RedditT m a #

reader :: (Client -> a) -> RedditT m a #

Monad m => Monad (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(>>=) :: RedditT m a -> (a -> RedditT m b) -> RedditT m b #

(>>) :: RedditT m a -> RedditT m b -> RedditT m b #

return :: a -> RedditT m a #

Functor m => Functor (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

fmap :: (a -> b) -> RedditT m a -> RedditT m b #

(<$) :: a -> RedditT m b -> RedditT m a #

Applicative m => Applicative (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

pure :: a -> RedditT m a #

(<*>) :: RedditT m (a -> b) -> RedditT m a -> RedditT m b #

liftA2 :: (a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c #

(*>) :: RedditT m a -> RedditT m b -> RedditT m b #

(<*) :: RedditT m a -> RedditT m b -> RedditT m a #

MonadIO m => MonadIO (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

liftIO :: IO a -> RedditT m a #

MonadUnliftIO m => MonadUnliftIO (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

withRunInIO :: ((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b #

MonadThrow m => MonadThrow (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

throwM :: Exception e => e -> RedditT m a #

MonadCatch m => MonadCatch (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

catch :: Exception e => RedditT m a -> (e -> RedditT m a) -> RedditT m a #

runRedditT :: Client -> RedditT m a -> m a Source #

Run a RedditT action

type MonadReddit m = (MonadUnliftIO m, MonadThrow m, MonadCatch m, MonadReader Client m) Source #

Synonym for constraints that RedditT actions must satisfy

data UserAgent Source #

A unique user agent to identify your application; Reddit applies rate-limiting to common agents, and actively bans misleading ones

Constructors

UserAgent 

Fields

Instances

Instances details
Eq UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

Show UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

Generic UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep UserAgent :: Type -> Type #

type Rep UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

type Rep UserAgent = D1 ('MetaData "UserAgent" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "UserAgent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "platform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "appID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

type ClientSite = Text Source #

A client site corresponds to a field in your auth configuration ini file. For instance, the ClientSite "mybot" should map to section such as:

[MYBOT]
id = <clientID>
...

in your auth.ini file.

Note: The ClientSite and the corresponding ini section are case insensitive!

data Client Source #

A client facilitating access to Reddit's API

Instances

Instances details
Generic Client Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep Client :: Type -> Type #

Methods

from :: Client -> Rep Client x #

to :: Rep Client x -> Client #

HasHttpManager Client Source # 
Instance details

Defined in Network.Reddit.Types

Monad m => MonadReader Client (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

ask :: RedditT m Client #

local :: (Client -> Client) -> RedditT m a -> RedditT m a #

reader :: (Client -> a) -> RedditT m a #

type Rep Client Source # 
Instance details

Defined in Network.Reddit.Types

data ClientState Source #

Stateful data that may be updated over the course of a Client lifetime

Constructors

ClientState 

Fields

Instances

Instances details
Eq ClientState Source # 
Instance details

Defined in Network.Reddit.Types

Show ClientState Source # 
Instance details

Defined in Network.Reddit.Types

Generic ClientState Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep ClientState :: Type -> Type #

type Rep ClientState Source # 
Instance details

Defined in Network.Reddit.Types

type Rep ClientState = D1 ('MetaData "ClientState" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "ClientState" 'PrefixI 'True) (S1 ('MetaSel ('Just "accessToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessToken) :*: (S1 ('MetaSel ('Just "tokenObtained") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 POSIXTime) :*: S1 ('MetaSel ('Just "limits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RateLimits)))))

readClientState :: MonadReddit m => Lens' ClientState a -> m a Source #

For conveniently reading some field from the IORef ClientState inside a Client

data WithData Source #

Data, either as JSON or URL-encoded form, to be attached to requests

Instances

Instances details
Show WithData Source # 
Instance details

Defined in Network.Reddit.Types

Generic WithData Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep WithData :: Type -> Type #

Methods

from :: WithData -> Rep WithData x #

to :: Rep WithData x -> WithData #

type Rep WithData Source # 
Instance details

Defined in Network.Reddit.Types

type Rep WithData = D1 ('MetaData "WithData" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((C1 ('MetaCons "WithJSON" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)) :+: C1 ('MetaCons "WithForm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Form))) :+: (C1 ('MetaCons "WithMultipart" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Part])) :+: C1 ('MetaCons "NoData" 'PrefixI 'False) (U1 :: Type -> Type)))

data RateLimits Source #

Rate limit info

Constructors

RateLimits 

Fields

  • remaining :: Integer

    The number of requests remaining in the current rate-limiting window

  • used :: Integer
     
  • reset :: POSIXTime

    Timestamp of the upper bound on rate-limiting counter reset

  • nextRequest :: POSIXTime

    Epoch time at which the next request should be made in order to stay within the current rate limit bounds

Instances

Instances details
Eq RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

Show RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

Generic RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep RateLimits :: Type -> Type #

type Rep RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

readRateLimits :: POSIXTime -> ResponseHeaders -> Maybe RateLimits Source #

Extract rate limit info from response headers. This should only be called after making a request

Auth

data AppType Source #

The three forms of application that may use the Reddit API, each having different API access patterns

Constructors

ScriptApp ClientSecret PasswordFlow

The simplest type of application. May only be used by the developer who owns the account. This requires supplying the usernme and password associated with the account

WebApp ClientSecret CodeFlow

For applications running on a server backend

InstalledApp CodeFlow

For applications installed on devices that the developer does not own (e.g., a mobile application)

ApplicationOnly ClientSecret 

Instances

Instances details
Eq AppType Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(==) :: AppType -> AppType -> Bool #

(/=) :: AppType -> AppType -> Bool #

Show AppType Source # 
Instance details

Defined in Network.Reddit.Types

Generic AppType Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep AppType :: Type -> Type #

Methods

from :: AppType -> Rep AppType x #

to :: Rep AppType x -> AppType #

ToForm AppType Source # 
Instance details

Defined in Network.Reddit.Types

Methods

toForm :: AppType -> Form #

type Rep AppType Source # 
Instance details

Defined in Network.Reddit.Types

data AuthConfig Source #

A configuration

Constructors

AuthConfig 

Fields

  • clientID :: ClientID

    Your application's client ID

  • appType :: AppType

    The type of your application. This will determine how OAuth credentials are obtained

  • userAgent :: UserAgent

    Your unique user agent; will be used in the client that is obtained after authenticating

Instances

Instances details
Eq AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

Show AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

Generic AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep AuthConfig :: Type -> Type #

type Rep AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

type Rep AuthConfig = D1 ('MetaData "AuthConfig" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "AuthConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClientID) :*: (S1 ('MetaSel ('Just "appType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AppType) :*: S1 ('MetaSel ('Just "userAgent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UserAgent))))

data AccessToken Source #

Token received after authentication

Instances

Instances details
Eq AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

Show AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

Generic AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep AccessToken :: Type -> Type #

FromJSON AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

type Rep AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

type Rep AccessToken = D1 ('MetaData "AccessToken" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "AccessToken" 'PrefixI 'True) ((S1 ('MetaSel ('Just "token") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Token) :*: S1 ('MetaSel ('Just "expiresIn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NominalDiffTime)) :*: (S1 ('MetaSel ('Just "scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Scope]) :*: S1 ('MetaSel ('Just "refreshToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Token)))))

type Token = Text Source #

Type synonym for the text of a token

type Code = Text Source #

Type synonym for the text of codes returned from auth URLs, for WebApps and InstalledApps

data Scope Source #

Represents a specific Reddit functionality that must be explicitly requested

Instances

Instances details
Enum Scope Source # 
Instance details

Defined in Network.Reddit.Types

Eq Scope Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(==) :: Scope -> Scope -> Bool #

(/=) :: Scope -> Scope -> Bool #

Ord Scope Source # 
Instance details

Defined in Network.Reddit.Types

Methods

compare :: Scope -> Scope -> Ordering #

(<) :: Scope -> Scope -> Bool #

(<=) :: Scope -> Scope -> Bool #

(>) :: Scope -> Scope -> Bool #

(>=) :: Scope -> Scope -> Bool #

max :: Scope -> Scope -> Scope #

min :: Scope -> Scope -> Scope #

Show Scope Source # 
Instance details

Defined in Network.Reddit.Types

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Generic Scope Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep Scope :: Type -> Type #

Methods

from :: Scope -> Rep Scope x #

to :: Rep Scope x -> Scope #

FromJSON Scope Source # 
Instance details

Defined in Network.Reddit.Types

ToHttpApiData Scope Source # 
Instance details

Defined in Network.Reddit.Types

type Rep Scope Source # 
Instance details

Defined in Network.Reddit.Types

type Rep Scope = D1 ('MetaData "Scope" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((((C1 ('MetaCons "Accounts" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Creddits" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Edit" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Flair" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "History" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Identity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiveManage" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ModConfig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModContributors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModFlair" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ModLog" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModMail" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModOthers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModPosts" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ModSelf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModTraffic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModWiki" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MySubreddits" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrivateMessages" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Read" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Report" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Save" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StructuredStyles" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Submit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Subscribe" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Vote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WikiEdit" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WikiRead" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unlimited" 'PrefixI 'False) (U1 :: Type -> Type))))))

data PasswordFlow Source #

Simple user credentials for authenticating via ScriptApps

Note: These credentials will be kept in memory!

Constructors

PasswordFlow 

Fields

  • username :: Text

    The name of the user you are authenticating as

  • password :: Text

    The password of the user you are authenticating as

Instances

Instances details
Eq PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Show PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Generic PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep PasswordFlow :: Type -> Type #

ToForm PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Methods

toForm :: PasswordFlow -> Form #

type Rep PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

type Rep PasswordFlow = D1 ('MetaData "PasswordFlow" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "PasswordFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "password") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

data CodeFlow Source #

Details for OAuth "code flow", for WebApps and InstalledApps

Constructors

CodeFlow 

Fields

  • redirectURI :: URL

    This must exactly match the redirect URL you entered when making your application on Reddit

  • code :: Code

    This is the code that is obtained after a user grants permissions by visiting the URL generated by getAuthURL. If you are using a TokenManager with newClientWithManager, you can leave this field as empty text, since it won't be used to get the initial refresh token

Instances

Instances details
Eq CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Show CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Generic CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep CodeFlow :: Type -> Type #

Methods

from :: CodeFlow -> Rep CodeFlow x #

to :: Rep CodeFlow x -> CodeFlow #

ToForm CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Methods

toForm :: CodeFlow -> Form #

type Rep CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

type Rep CodeFlow = D1 ('MetaData "CodeFlow" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "CodeFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "redirectURI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Code)))

type ClientID = Text Source #

Type synonym for client IDs

type ClientSecret = Text Source #

Type synonym for client secrets

data TokenDuration Source #

The duration of the access token for WebApps and InstalledApps

Constructors

Temporary

Generates one-hour access tokens without a refresh token

Permanent

Generates a one-hour access tokens with a refresh token that can be used to indefinitely obtain new access tokens

Instances

Instances details
Eq TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

Show TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

Generic TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep TokenDuration :: Type -> Type #

ToHttpApiData TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

type Rep TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

type Rep TokenDuration = D1 ('MetaData "TokenDuration" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Temporary" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Permanent" 'PrefixI 'False) (U1 :: Type -> Type))

data TokenManager Source #

Monadic actions to load and save Tokens, specifically refresh tokens, when creating new Clients for WebApps and InstalledApps

Constructors

TokenManager 

Fields

  • loadToken :: forall m. (MonadIO m, MonadThrow m) => m Token

    Load an existing refresh token, for instance from a file or database

  • putToken :: forall m. (MonadIO m, MonadThrow m) => Maybe Token -> m ()

    Store the new refresh token that is received when exchanging the existing one for a new AccessToken.

    This action must take a Maybe Token as its argument, as it is possible (albeit perhaps unlikely) that Reddit does not return a new token when exchanging the existing refresh token for a new access token

Requests

data APIAction a Source #

An API request parameterized by the type it evaluates to when executed

Instances

Instances details
Generic (APIAction a) Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep (APIAction a) :: Type -> Type #

Methods

from :: APIAction a -> Rep (APIAction a) x #

to :: Rep (APIAction a) x -> APIAction a #

type Rep (APIAction a) Source # 
Instance details

Defined in Network.Reddit.Types

data Method Source #

HTTP method, excluding those not used in the Reddit API

Constructors

GET 
POST 
DELETE 
PUT 
PATCH 

Instances

Instances details
Eq Method Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(==) :: Method -> Method -> Bool #

(/=) :: Method -> Method -> Bool #

Show Method Source # 
Instance details

Defined in Network.Reddit.Types

Generic Method Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep Method :: Type -> Type #

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

type Rep Method Source # 
Instance details

Defined in Network.Reddit.Types

type Rep Method = D1 ('MetaData "Method" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((C1 ('MetaCons "GET" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "POST" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DELETE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PUT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PATCH" 'PrefixI 'False) (U1 :: Type -> Type))))

type PathSegment = Text Source #

Type synonym for a segment of a URL path

Re-exports