yam-0.6.1: A wrapper of servant

Copyright(c) 2019 Daniel YU
LicenseBSD3
Maintainerleptonyu@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Yam

Contents

Description

A out-of-the-box wrapper of servant, providing configuration loader salak and flexible extension with AppMiddleware.

Synopsis

How to use this library

import           Salak.Yaml
import           Servant
import           Yam
import           Data.Version

type API = "hello" :> Get '[PlainText] Text

service :: ServerT API AppSimple
service = return "world"

main = start "app" YAML (makeVersion []) (return emptyAM) (Proxy @API) (return service)

Yam Server

start Source #

Arguments

:: (HasLoad file, HasLogger cxt, HasServer api cxt, HasSwagger api) 
=> String

File config name

-> file

Config file format

-> Version

Version

-> RunSalak (AppMiddleware Simple cxt)

Application Middleware

-> Proxy api

Application API Proxy

-> RunSalak (ServerT api (AppV cxt IO))

Application API Server

-> IO () 

Standard Starter of Yam.

start' :: forall api cxt. (HasLogger cxt, HasServer api cxt, HasSwagger api) => LoadSalakT IO () -> Version -> RunSalak (AppMiddleware Simple cxt) -> Proxy api -> RunSalak (ServerT api (AppV cxt IO)) -> IO () Source #

Standard Starter of Yam.

serveWarp :: AppConfig -> Application -> IO () Source #

default http server by warp.

Application Configuration

data AppConfig Source #

Application Configuration.

Constructors

AppConfig 

Fields

Instances
Eq AppConfig Source # 
Instance details

Defined in Yam.Config

Show AppConfig Source # 
Instance details

Defined in Yam.Config

Default AppConfig Source # 
Instance details

Defined in Yam.Config

Methods

def :: AppConfig #

FromProp AppConfig Source # 
Instance details

Defined in Yam.Config

Application Context

data AppT cxt m a Source #

Application Context Monad.

Instances
MonadTrans (AppT cxt) Source # 
Instance details

Defined in Yam.App

Methods

lift :: Monad m => m a -> AppT cxt m a #

Monad m => MonadReader (Context cxt) (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

ask :: AppT cxt m (Context cxt) #

local :: (Context cxt -> Context cxt) -> AppT cxt m a -> AppT cxt m a #

reader :: (Context cxt -> a) -> AppT cxt m a #

Monad m => Monad (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

(>>=) :: AppT cxt m a -> (a -> AppT cxt m b) -> AppT cxt m b #

(>>) :: AppT cxt m a -> AppT cxt m b -> AppT cxt m b #

return :: a -> AppT cxt m a #

fail :: String -> AppT cxt m a #

Functor m => Functor (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

fmap :: (a -> b) -> AppT cxt m a -> AppT cxt m b #

(<$) :: a -> AppT cxt m b -> AppT cxt m a #

Applicative m => Applicative (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

pure :: a -> AppT cxt m a #

(<*>) :: AppT cxt m (a -> b) -> AppT cxt m a -> AppT cxt m b #

liftA2 :: (a -> b -> c) -> AppT cxt m a -> AppT cxt m b -> AppT cxt m c #

(*>) :: AppT cxt m a -> AppT cxt m b -> AppT cxt m b #

(<*) :: AppT cxt m a -> AppT cxt m b -> AppT cxt m a #

MonadIO m => MonadIO (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

liftIO :: IO a -> AppT cxt m a #

MonadUnliftIO m => MonadUnliftIO (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

askUnliftIO :: AppT cxt m (UnliftIO (AppT cxt m)) #

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

(HasLogger cxt, MonadIO m) => HasValid (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

invalid :: HasI18n a => a -> AppT cxt m b #

mark :: String -> AppT cxt m a -> AppT cxt m a #

(HasLogger cxt, MonadIO m) => MonadLogger (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> AppT cxt m () #

(HasLogger cxt, MonadIO m) => MonadLoggerIO (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

askLoggerIO :: AppT cxt m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

(HasContextEntry cxt SourcePack, Monad m) => HasSourcePack (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

askSourcePack :: AppT cxt m SourcePack #

logSP :: Text -> AppT cxt m () #

readLogs :: AppT cxt m [Text] #

type AppV cxt = AppT (VaultHolder ': cxt) Source #

Application with Vault

type AppIO cxt = AppT cxt IO Source #

Application on IO.

type AppSimple = AppV Simple IO Source #

Simple Application with logger context.

type Simple = '[LogFuncHolder] Source #

Simple Application context

runAppT :: Context cxt -> AppT cxt m a -> m a Source #

Run Application with context.

runVault :: MonadIO m => Context cxt -> Vault -> AppV cxt IO a -> m a Source #

Run Application with Vault.

throwS Source #

Arguments

:: (HasCallStack, MonadIO m, MonadLogger m) 
=> ServerError

Server error

-> Text

message

-> m a 

throw ServerError with message

Application Middleware

newtype AppMiddleware a b Source #

Application Middleware.

Constructors

AppMiddleware 
Instances
Category AppMiddleware Source # 
Instance details

Defined in Yam.Middleware

Methods

id :: AppMiddleware a a #

(.) :: AppMiddleware b c -> AppMiddleware a b -> AppMiddleware a c #

emptyAM :: AppMiddleware cxt cxt Source #

Empty Application Middleware.

simpleContext :: a -> AppMiddleware cxt (a ': cxt) Source #

Simple Application Middleware, just provide a config to context.

simpleConfig :: (HasSalak cxt, FromProp a) => Text -> AppMiddleware cxt (a ': cxt) Source #

Simple Application Middleware, just provide a config to context.

simpleConfig' :: (HasSalak cxt, FromProp a) => Text -> (a -> AppT cxt (LoggingT IO) b) -> AppMiddleware cxt (b ': cxt) Source #

Simple Application Middleware, just provide a config to context.

simpleMiddleware :: Middleware -> AppMiddleware cxt cxt Source #

Simple Application Middleware, promote a Middleware to AppMiddleware

Health

data HealthStatus Source #

Constructors

UP 
DOWN 
Instances
Eq HealthStatus Source # 
Instance details

Defined in Yam.Server.Health

Show HealthStatus Source # 
Instance details

Defined in Yam.Server.Health

Generic HealthStatus Source # 
Instance details

Defined in Yam.Server.Health

Associated Types

type Rep HealthStatus :: Type -> Type #

ToJSON HealthStatus Source # 
Instance details

Defined in Yam.Server.Health

ToSchema HealthStatus Source # 
Instance details

Defined in Yam.Server.Health

type Rep HealthStatus Source # 
Instance details

Defined in Yam.Server.Health

type Rep HealthStatus = D1 (MetaData "HealthStatus" "Yam.Server.Health" "yam-0.6.1-JEH5qTiZhtn1fXFavk36JU" False) (C1 (MetaCons "UP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DOWN" PrefixI False) (U1 :: Type -> Type))

data HealthResult Source #

Instances
Eq HealthResult Source # 
Instance details

Defined in Yam.Server.Health

Show HealthResult Source # 
Instance details

Defined in Yam.Server.Health

Generic HealthResult Source # 
Instance details

Defined in Yam.Server.Health

Associated Types

type Rep HealthResult :: Type -> Type #

ToJSON HealthResult Source # 
Instance details

Defined in Yam.Server.Health

ToSchema HealthResult Source # 
Instance details

Defined in Yam.Server.Health

type Rep HealthResult Source # 
Instance details

Defined in Yam.Server.Health

Modules

Logger

data LogConfig Source #

Logger config

Constructors

LogConfig 

Fields

Instances
Eq LogConfig Source # 
Instance details

Defined in Yam.Logger

Show LogConfig Source # 
Instance details

Defined in Yam.Logger

Default LogConfig Source # 
Instance details

Defined in Yam.Logger

Methods

def :: LogConfig #

FromProp LogConfig Source # 
Instance details

Defined in Yam.Logger

type HasLogger cxt = (HasContextEntry cxt LogFuncHolder, TryContextEntry cxt VaultHolder) Source #

Context with logger.

data LogFuncHolder Source #

Holder for LogFunc

data VaultHolder Source #

Holder for Vault

Context

data Context (contextTypes :: [Type]) where #

Contexts are used to pass values to combinators. (They are not meant to be used to pass parameters to your handlers, i.e. they should not replace any custom ReaderT-monad-stack that you're using with hoistServer.) If you don't use combinators that require any context entries, you can just use serve as always.

If you are using combinators that require a non-empty Context you have to use serveWithContext and pass it a Context that contains all the values your combinators need. A Context is essentially a heterogenous list and accessing the elements is being done by type (see getContextEntry). The parameter of the type Context is a type-level list reflecting the types of the contained context entries. To create a Context with entries, use the operator (:.):

>>> :type True :. () :. EmptyContext
True :. () :. EmptyContext :: Context '[Bool, ()]

Constructors

EmptyContext :: forall (contextTypes :: [Type]). Context ([] :: [Type]) 
(:.) :: forall (contextTypes :: [Type]) x (xs :: [Type]). x -> Context xs -> Context (x ': xs) infixr 5 
Instances
(Eq a, Eq (Context as)) => Eq (Context (a ': as)) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

(==) :: Context (a ': as) -> Context (a ': as) -> Bool #

(/=) :: Context (a ': as) -> Context (a ': as) -> Bool #

Eq (Context ([] :: [Type])) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

(==) :: Context [] -> Context [] -> Bool #

(/=) :: Context [] -> Context [] -> Bool #

(Show a, Show (Context as)) => Show (Context (a ': as)) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

showsPrec :: Int -> Context (a ': as) -> ShowS #

show :: Context (a ': as) -> String #

showList :: [Context (a ': as)] -> ShowS #

Show (Context ([] :: [Type])) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

showsPrec :: Int -> Context [] -> ShowS #

show :: Context [] -> String #

showList :: [Context []] -> ShowS #

Monad m => MonadReader (Context cxt) (AppT cxt m) Source # 
Instance details

Defined in Yam.App

Methods

ask :: AppT cxt m (Context cxt) #

local :: (Context cxt -> Context cxt) -> AppT cxt m a -> AppT cxt m a #

reader :: (Context cxt -> a) -> AppT cxt m a #

class HasContextEntry (context :: [Type]) val where #

This class is used to access context entries in Contexts. getContextEntry returns the first value where the type matches:

>>> getContextEntry (True :. False :. EmptyContext) :: Bool
True

If the Context does not contain an entry of the requested type, you'll get an error:

>>> getContextEntry (True :. False :. EmptyContext) :: String
...
...No instance for (HasContextEntry '[] [Char])
...

Methods

getContextEntry :: Context context -> val #

Instances
HasContextEntry xs val => HasContextEntry (notIt ': xs) val 
Instance details

Defined in Servant.Server.Internal.Context

Methods

getContextEntry :: Context (notIt ': xs) -> val #

HasContextEntry (val ': xs) val 
Instance details

Defined in Servant.Server.Internal.Context

Methods

getContextEntry :: Context (val ': xs) -> val #

class TryContextEntry (cxt :: [*]) (entry :: *) where Source #

This class provide a optional supports for get entry from Context.

Methods

tryContextEntry :: Context cxt -> Maybe entry Source #

Instances
TryContextEntry a entry Source # 
Instance details

Defined in Yam.Prelude

Methods

tryContextEntry :: Context a -> Maybe entry Source #

TryContextEntry (entry ': as) entry Source # 
Instance details

Defined in Yam.Prelude

Methods

tryContextEntry :: Context (entry ': as) -> Maybe entry Source #

TryContextEntry as entry => TryContextEntry (a ': as) entry Source # 
Instance details

Defined in Yam.Prelude

Methods

tryContextEntry :: Context (a ': as) -> Maybe entry Source #

getEntry :: (HasContextEntry cxt entry, Monad m) => AppT cxt m entry Source #

Get entry from AppT

tryEntry :: (TryContextEntry cxt entry, Monad m) => AppT cxt m (Maybe entry) Source #

Try get entry from AppT

Swagger

data SwaggerConfig Source #

Swagger Configuration

Constructors

SwaggerConfig 

Fields

Instances
Eq SwaggerConfig Source # 
Instance details

Defined in Yam.Swagger

Show SwaggerConfig Source # 
Instance details

Defined in Yam.Swagger

FromProp SwaggerConfig Source # 
Instance details

Defined in Yam.Swagger

serveWithContextAndSwagger Source #

Arguments

:: (HasSwagger api, HasServer api context) 
=> SwaggerConfig

Swagger configuration.

-> (Swagger -> Swagger)

Swagger modification.

-> Proxy api

Application API Proxy.

-> Context context

Application context.

-> ServerT api Handler

Application API Server

-> Application 

Serve with swagger.

baseInfo Source #

Arguments

:: String

Hostname

-> Text

Server Name

-> Version

Server version

-> Int

Port

-> Swagger

Old swagger

-> Swagger 

Swagger modification

data SwaggerTag (name :: Symbol) (desp :: Symbol) Source #

Instances
HasClient m api => HasClient m (SwaggerTag name desp :> api) Source # 
Instance details

Defined in Yam.Swagger

Associated Types

type Client m (SwaggerTag name desp :> api) :: Type #

Methods

clientWithRoute :: Proxy m -> Proxy (SwaggerTag name desp :> api) -> Request -> Client m (SwaggerTag name desp :> api) #

hoistClientMonad :: Proxy m -> Proxy (SwaggerTag name desp :> api) -> (forall x. mon x -> mon' x) -> Client mon (SwaggerTag name desp :> api) -> Client mon' (SwaggerTag name desp :> api) #

(HasSwagger api, KnownSymbol name, KnownSymbol desp) => HasSwagger (SwaggerTag name desp :> api :: Type) Source # 
Instance details

Defined in Yam.Swagger

Methods

toSwagger :: Proxy (SwaggerTag name desp :> api) -> Swagger #

HasServer api ctx => HasServer (SwaggerTag name desp :> api :: Type) ctx Source # 
Instance details

Defined in Yam.Swagger

Associated Types

type ServerT (SwaggerTag name desp :> api) m :: Type #

Methods

route :: Proxy (SwaggerTag name desp :> api) -> Context ctx -> Delayed env (Server (SwaggerTag name desp :> api)) -> Router env #

hoistServerWithContext :: Proxy (SwaggerTag name desp :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (SwaggerTag name desp :> api) m -> ServerT (SwaggerTag name desp :> api) n #

type Client m (SwaggerTag name desp :> api) Source # 
Instance details

Defined in Yam.Swagger

type Client m (SwaggerTag name desp :> api) = Client m api
type ServerT (SwaggerTag name desp :> api :: Type) m Source # 
Instance details

Defined in Yam.Swagger

type ServerT (SwaggerTag name desp :> api :: Type) m = ServerT api m

Reexport

spanNoNotifier :: Span -> AppV cxt IO () Source #

Empty span notifier.

data Span Source #

Instances
Eq Span Source # 
Instance details

Defined in Data.Opentracing.Types

Methods

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

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

Show Span Source # 
Instance details

Defined in Data.Opentracing.Types

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

data SpanTag Source #

Instances
Eq SpanTag Source # 
Instance details

Defined in Data.Opentracing.Types

Methods

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

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

Show SpanTag Source # 
Instance details

Defined in Data.Opentracing.Types

data SpanReference Source #

Constructors

SpanReference 

Fields

showText :: Show a => a -> Text Source #

Show text.

decodeUtf8 :: ByteString -> Text #

Decode a ByteString containing UTF-8 encoded text that is known to be valid.

If the input contains any invalid UTF-8 data, an exception will be thrown that cannot be caught in pure code. For more control over the handling of invalid data, use decodeUtf8' or decodeUtf8With.

encodeUtf8 :: Text -> ByteString #

Encode text using UTF-8 encoding.

pack :: String -> Text #

O(n) Convert a String into a Text. Subject to fusion. Performs replacement on invalid scalar values.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

fromMaybe :: a -> Maybe a -> a #

The fromMaybe function takes a default value and and Maybe value. If the Maybe is Nothing, it returns the default values; otherwise, it returns the value contained in the Maybe.

Examples

Expand

Basic usage:

>>> fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>> fromMaybe "" Nothing
""

Read an integer from a string using readMaybe. If we fail to parse an integer, we want to return 0 by default:

>>> import Text.Read ( readMaybe )
>>> fromMaybe 0 (readMaybe "5")
5
>>> fromMaybe 0 (readMaybe "")
0

throw :: Exception e => e -> a #

Throw an exception. Exceptions may be thrown from purely functional code, but may only be caught within the IO monad.

logInfo :: (HasCallStack, MonadLogger m) => Text -> m () #

See logDebug

Since: monad-logger-0.3.19

logError :: (HasCallStack, MonadLogger m) => Text -> m () #

See logDebug

Since: monad-logger-0.3.19

logWarn :: (HasCallStack, MonadLogger m) => Text -> m () #

See logDebug

Since: monad-logger-0.3.19

logDebug :: (HasCallStack, MonadLogger m) => Text -> m () #

Logs a message with the location provided by an implicit CallStack.

Since: monad-logger-0.3.19

newtype RunSalak a Source #

Constructors

RunSalak 

Fields

Instances
Monad RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

(>>=) :: RunSalak a -> (a -> RunSalak b) -> RunSalak b #

(>>) :: RunSalak a -> RunSalak b -> RunSalak b #

return :: a -> RunSalak a #

fail :: String -> RunSalak a #

Functor RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

fmap :: (a -> b) -> RunSalak a -> RunSalak b #

(<$) :: a -> RunSalak b -> RunSalak a #

Applicative RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

pure :: a -> RunSalak a #

(<*>) :: RunSalak (a -> b) -> RunSalak a -> RunSalak b #

liftA2 :: (a -> b -> c) -> RunSalak a -> RunSalak b -> RunSalak c #

(*>) :: RunSalak a -> RunSalak b -> RunSalak b #

(<*) :: RunSalak a -> RunSalak b -> RunSalak a #

MonadIO RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

liftIO :: IO a -> RunSalak a #

MonadUnliftIO RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

askUnliftIO :: RunSalak (UnliftIO RunSalak) #

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

MonadLogger RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> RunSalak () #

MonadLoggerIO RunSalak Source # 
Instance details

Defined in Yam.Prelude

Methods

askLoggerIO :: RunSalak (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

HasSourcePack RunSalak Source # 
Instance details

Defined in Yam.Prelude