{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Description (
Description,
Summary,
FoldDescription,
FoldDescription',
reflectDescription,
) where
import Data.Kind
(Type)
import Data.Proxy
(Proxy (..))
import Data.Typeable
(Typeable)
import GHC.TypeLits
(KnownSymbol, Symbol, symbolVal)
data Summary (sym :: Symbol)
deriving (Typeable)
data Description (sym :: Symbol)
deriving (Typeable)
type FoldDescription mods = FoldDescription' "" mods
type family FoldDescription' (acc :: Symbol) (mods :: [Type]) :: Symbol where
FoldDescription' acc '[] = acc
FoldDescription' acc (Description desc ': mods) = FoldDescription' desc mods
FoldDescription' acc (mod ': mods) = FoldDescription' acc mods
reflectDescription :: forall mods. KnownSymbol (FoldDescription mods) => Proxy mods -> String
reflectDescription :: forall (mods :: [Type]).
KnownSymbol (FoldDescription mods) =>
Proxy mods -> String
reflectDescription Proxy mods
_ = Proxy (FoldDescription mods) -> String
forall (n :: Symbol) (proxy :: Symbol -> Type).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy (FoldDescription mods)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (FoldDescription mods))