mig-0.2.1.0: Build lightweight and composable servers
Safe HaskellSafe-Inferred
LanguageGHC2021

Mig.Core.Api

Description

Core API description

Synopsis

Documentation

data Api a Source #

HTTP API container

Constructors

Append (Api a) (Api a)

alternative between two API's

Empty

an empty API that does nothing

WithPath Path (Api a)

path prefix for an API

HandleRoute a

handle route

Instances

Instances details
Foldable Api Source # 
Instance details

Defined in Mig.Core.Api

Methods

fold :: Monoid m => Api m -> m #

foldMap :: Monoid m => (a -> m) -> Api a -> m #

foldMap' :: Monoid m => (a -> m) -> Api a -> m #

foldr :: (a -> b -> b) -> b -> Api a -> b #

foldr' :: (a -> b -> b) -> b -> Api a -> b #

foldl :: (b -> a -> b) -> b -> Api a -> b #

foldl' :: (b -> a -> b) -> b -> Api a -> b #

foldr1 :: (a -> a -> a) -> Api a -> a #

foldl1 :: (a -> a -> a) -> Api a -> a #

toList :: Api a -> [a] #

null :: Api a -> Bool #

length :: Api a -> Int #

elem :: Eq a => a -> Api a -> Bool #

maximum :: Ord a => Api a -> a #

minimum :: Ord a => Api a -> a #

sum :: Num a => Api a -> a #

product :: Num a => Api a -> a #

Traversable Api Source # 
Instance details

Defined in Mig.Core.Api

Methods

traverse :: Applicative f => (a -> f b) -> Api a -> f (Api b) #

sequenceA :: Applicative f => Api (f a) -> f (Api a) #

mapM :: Monad m => (a -> m b) -> Api a -> m (Api b) #

sequence :: Monad m => Api (m a) -> m (Api a) #

Functor Api Source # 
Instance details

Defined in Mig.Core.Api

Methods

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

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

Monoid (Api a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

mempty :: Api a #

mappend :: Api a -> Api a -> Api a #

mconcat :: [Api a] -> Api a #

Semigroup (Api a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

(<>) :: Api a -> Api a -> Api a #

sconcat :: NonEmpty (Api a) -> Api a #

stimes :: Integral b => b -> Api a -> Api a #

Show a => Show (Api a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

showsPrec :: Int -> Api a -> ShowS #

show :: Api a -> String #

showList :: [Api a] -> ShowS #

Eq a => Eq (Api a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

(==) :: Api a -> Api a -> Bool #

(/=) :: Api a -> Api a -> Bool #

newtype Path Source #

Path is a chain of elements which can be static types or capture. There is IsString instance which allows us to create paths from strings. Examples:

"api/v1/foo" ==> Path [StaticPath "api", StaticPath "v1", StaticPath "foo"]
"api/v1/*" ==> Path [StaticPath "api", StaticPath "v1", CapturePath "*"]

Constructors

Path 

Fields

Instances

Instances details
IsString Path Source # 
Instance details

Defined in Mig.Core.Api

Methods

fromString :: String -> Path #

Monoid Path Source # 
Instance details

Defined in Mig.Core.Api

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

Semigroup Path Source # 
Instance details

Defined in Mig.Core.Api

Methods

(<>) :: Path -> Path -> Path #

sconcat :: NonEmpty Path -> Path #

stimes :: Integral b => b -> Path -> Path #

Show Path Source # 
Instance details

Defined in Mig.Core.Api

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Eq Path Source # 
Instance details

Defined in Mig.Core.Api

Methods

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

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

Ord Path Source # 
Instance details

Defined in Mig.Core.Api

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

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

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

ToHttpApiData Path Source # 
Instance details

Defined in Mig.Core.Api

newtype ApiNormal a Source #

Efficient representation of API to fetch routes

Instances

Instances details
Functor ApiNormal Source # 
Instance details

Defined in Mig.Core.Api

Methods

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

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

Show a => Show (ApiNormal a) Source # 
Instance details

Defined in Mig.Core.Api

Eq a => Eq (ApiNormal a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

(==) :: ApiNormal a -> ApiNormal a -> Bool #

(/=) :: ApiNormal a -> ApiNormal a -> Bool #

toNormalApi :: forall m. Api (Route m) -> ApiNormal (Api (Route m)) Source #

converts API to efficient representation to fetch the route handlers by path

fromNormalApi :: Method -> ByteString -> ByteString -> ApiNormal a -> Maybe a Source #

Read sub-api by HTTP method, accept-type and content-type

data PathItem Source #

Path can be a static item or capture with a name

Instances

Instances details
Show PathItem Source # 
Instance details

Defined in Mig.Core.Api

Eq PathItem Source # 
Instance details

Defined in Mig.Core.Api

Ord PathItem Source # 
Instance details

Defined in Mig.Core.Api

ToHttpApiData PathItem Source # 
Instance details

Defined in Mig.Core.Api

getPath :: [Text] -> Api a -> Maybe (a, CaptureMap) Source #

Find an api item by path. Also it accumulates capture map along the way.

type CaptureMap = Map Text Text Source #

Map of capture values extracted from path. Keys are capture names.

flatApi :: Api a -> [(Path, a)] Source #

Flattens API. Creates a flat list of paths and route handlers.

fromFlatApi :: [(Path, a)] -> Api a Source #

Constructs API from flat list of pairs of paths and route handlers.

type MethodMap a = Map Method a Source #

Mthod map

newtype OutputMediaMap a Source #

filter by Accept header

Constructors

OutputMediaMap (MediaMap a) 

Instances

Instances details
Functor OutputMediaMap Source # 
Instance details

Defined in Mig.Core.Api

Methods

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

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

Show a => Show (OutputMediaMap a) Source # 
Instance details

Defined in Mig.Core.Api

Eq a => Eq (OutputMediaMap a) Source # 
Instance details

Defined in Mig.Core.Api

newtype InputMediaMap a Source #

filter by Content-Type header

Constructors

InputMediaMap (MediaMap a) 

Instances

Instances details
Functor InputMediaMap Source # 
Instance details

Defined in Mig.Core.Api

Methods

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

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

Show a => Show (InputMediaMap a) Source # 
Instance details

Defined in Mig.Core.Api

Eq a => Eq (InputMediaMap a) Source # 
Instance details

Defined in Mig.Core.Api

data MediaMap a Source #

Map by media type

Constructors

MediaMap 

Fields

Instances

Instances details
Functor MediaMap Source # 
Instance details

Defined in Mig.Core.Api

Methods

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

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

Show a => Show (MediaMap a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

showsPrec :: Int -> MediaMap a -> ShowS #

show :: MediaMap a -> String #

showList :: [MediaMap a] -> ShowS #

Eq a => Eq (MediaMap a) Source # 
Instance details

Defined in Mig.Core.Api

Methods

(==) :: MediaMap a -> MediaMap a -> Bool #

(/=) :: MediaMap a -> MediaMap a -> Bool #