yam-0.6.0: 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
import           Salak.Yaml
import           Servant
import           Yam
import qualified Control.Category    as C
import           Data.Version

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

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

main = runSalakWith "app" YAML $ do
  al <- require  "yam.application"
  sw <- require  "yam.swagger"
  lc <- requireD "yam.logging"
  start al sw (makeVersion []) lc spanNoNotifier emptyAM serveWarp (Proxy @API) service

Yam Server

start Source #

Arguments

:: (HasServer api cxt, HasSwagger api) 
=> AppConfig

Application Config

-> SwaggerConfig

SwaggerConfig

-> Version

Application Version

-> IO LogConfig

Logger Config

-> (Span -> AppV cxt IO ())

Opentracing notifier

-> AppMiddleware Simple cxt

Application Middleware

-> (AppConfig -> Application -> IO ())

Run Application

-> Proxy api

Application API Proxy

-> ServerT api (AppV cxt IO)

Application API Server

-> IO () 

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 #

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 

Fields

Instances
Category AppMiddleware Source # 
Instance details

Defined in Yam

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

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

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.