Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data RobotsInfo = RobotsInfo {}
- newtype DisallowedPathPiece = DisallowedPathPiece Text
- robotsSitemapPath :: Lens' RobotsInfo (Maybe ())
- robotsDisallowedPaths :: Lens' RobotsInfo [DisallowedPathPiece]
- class HasRobots a where
- toRobots :: Proxy a -> RobotsInfo
Robots.txt
RobotsInfo
data RobotsInfo Source #
Intermediate structure representing robots.txt
file.
All API parts marked as Disallow
would be aggregated into RobotsInfo
during compilation and translated to robots.txt
content.
RobotsInfo | |
|
Instances
newtype DisallowedPathPiece Source #
Part of URL that should be present in robots file.
Instances
robotsSitemapPath :: Lens' RobotsInfo (Maybe ()) Source #
robotsDisallowedPaths :: Lens' RobotsInfo [DisallowedPathPiece] Source #
HasRobots
class HasRobots a where Source #
Servant API extension.
It describes how to build RobotsInfo
from servant API.
Most of types add nothing to it.
toRobots :: Proxy a -> RobotsInfo Source #
Instances
HasRobots EmptyAPI Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy EmptyAPI -> RobotsInfo Source # | |
HasRobots Raw Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy Raw -> RobotsInfo Source # | |
(HasRobots a, HasRobots b) => HasRobots (a :<|> b :: Type) Source # | Collect different path pieces. |
Defined in Servant.Seo.Robots toRobots :: Proxy (a :<|> b) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (HttpVersion :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (HttpVersion :> sub) -> RobotsInfo Source # | |
(KnownSymbol sym, HasRobots sub) => HasRobots (Capture' mods sym a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Capture' mods sym a :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (CaptureAll sym a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (CaptureAll sym a :> sub) -> RobotsInfo Source # | |
HasRobots api => HasRobots (Description desc :> api :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Description desc :> api) -> RobotsInfo Source # | |
HasRobots api => HasRobots (Summary desc :> api :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Summary desc :> api) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (Header' mods sym a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Header' mods sym a :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (IsSecure :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (IsSecure :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (QueryFlag sym :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (QueryFlag sym :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (QueryParam' mods sym a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (QueryParam' mods sym a :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (QueryParams sym a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (QueryParams sym a :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (RemoteHost :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (RemoteHost :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (ReqBody' mods cs a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (ReqBody' mods cs a :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (StreamBody' mods fr ct a :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (StreamBody' mods fr ct a :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (Vault :> sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Vault :> sub) -> RobotsInfo Source # | |
HasRobots api => HasRobots (Priority priority :> api :: Type) Source # |
|
Defined in Servant.Seo.Robots | |
(HasPeriod period, HasRobots api) => HasRobots (Frequency period :> api :: Type) Source # |
|
Defined in Servant.Seo.Robots | |
(HasRobots sub, KnownSymbol sym) => HasRobots (Disallow sym :> sub :: Type) Source # | Generate new |
Defined in Servant.Seo.Robots | |
(HasRobots sub, KnownSymbol sym) => HasRobots (sym :> sub :: Type) Source # | Append path piece to existing |
Defined in Servant.Seo.Robots toRobots :: Proxy (sym :> sub) -> RobotsInfo Source # | |
HasRobots sub => HasRobots (WithNamedContext x c sub :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (WithNamedContext x c sub) -> RobotsInfo Source # | |
KnownNat status => HasRobots (Verb method status cs (Headers hs a) :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Verb method status cs (Headers hs a)) -> RobotsInfo Source # | |
KnownNat status => HasRobots (Verb method status cs (Headers hs NoContent) :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Verb method status cs (Headers hs NoContent)) -> RobotsInfo Source # | |
KnownNat status => HasRobots (Verb method status cs a :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Verb method status cs a) -> RobotsInfo Source # | |
KnownNat status => HasRobots (Verb method status cs NoContent :: Type) Source # | |
Defined in Servant.Seo.Robots toRobots :: Proxy (Verb method status cs NoContent) -> RobotsInfo Source # |