{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Servant.Seo.Combinators where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as BSL
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import GHC.TypeLits (KnownSymbol, Nat, Symbol)
import qualified Network.HTTP.Media as M
import Servant
data XML deriving Typeable
instance Accept XML where
contentType _ = "text" M.// "xml"
instance MimeRender XML Text where
mimeRender _ = BSL.fromStrict . Text.encodeUtf8
instance MimeRender XML ByteString where
mimeRender _ = BSL.fromStrict
instance MimeRender XML BSL.ByteString where
mimeRender _ = id
data Disallow (sym :: Symbol)
instance (KnownSymbol sym, HasServer api context) => HasServer (Disallow sym :> api) context where
type ServerT (Disallow sym :> api) m = ServerT (sym :> api) m
route (Proxy :: Proxy (Disallow sym :> api)) context server =
route (Proxy @(sym :> api)) context server
hoistServerWithContext _ pc nt api =
hoistServerWithContext (Proxy @(sym :> api)) pc nt api
data Frequency (period :: Period)
instance (HasPeriod period, HasServer api context) =>
HasServer (Frequency period :> api) context where
type ServerT (Frequency period :> api) m = ServerT api m
route (Proxy :: Proxy (Frequency period :> api)) context server =
route (Proxy @api) context server
hoistServerWithContext _ pc nt api =
hoistServerWithContext (Proxy @api) pc nt api
data Period = Never
| Yearly
| Monthly
| Weekly
| Daily
| Hourly
| Always
deriving (Show, Eq, Ord, Enum, Generic)
class HasPeriod a where
getPeriod :: Proxy a -> Period
instance HasPeriod 'Never where getPeriod _ = Never
instance HasPeriod 'Yearly where getPeriod _ = Yearly
instance HasPeriod 'Monthly where getPeriod _ = Monthly
instance HasPeriod 'Weekly where getPeriod _ = Weekly
instance HasPeriod 'Daily where getPeriod _ = Daily
instance HasPeriod 'Hourly where getPeriod _ = Hourly
instance HasPeriod 'Always where getPeriod _ = Always
data Priority (priority :: (Nat, Nat))
instance (HasServer api context) =>
HasServer (Priority priority :> api) context where
type ServerT (Priority priority :> api) m = ServerT api m
route (Proxy :: Proxy (Priority priority :> api)) context server =
route (Proxy @api) context server
hoistServerWithContext _ pc nt api =
hoistServerWithContext (Proxy @api) pc nt api