Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Core API description
Synopsis
- data Api a
- newtype Path = Path {}
- newtype ApiNormal a = ApiNormal (MethodMap (OutputMediaMap (InputMediaMap a)))
- toNormalApi :: forall m. Api (Route m) -> ApiNormal (Api (Route m))
- fromNormalApi :: Method -> ByteString -> ByteString -> ApiNormal a -> Maybe a
- data PathItem
- getPath :: [Text] -> Api a -> Maybe (a, CaptureMap)
- type CaptureMap = Map Text Text
- flatApi :: Api a -> [(Path, a)]
- fromFlatApi :: [(Path, a)] -> Api a
- type MethodMap a = Map Method a
- newtype OutputMediaMap a = OutputMediaMap (MediaMap a)
- newtype InputMediaMap a = InputMediaMap (MediaMap a)
- data MediaMap a = MediaMap {}
Documentation
HTTP API container
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
Foldable Api Source # | |
Defined in Mig.Core.Api 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 # elem :: Eq a => a -> Api a -> Bool # maximum :: Ord a => Api a -> a # | |
Traversable Api Source # | |
Functor Api Source # | |
Monoid (Api a) Source # | |
Semigroup (Api a) Source # | |
Show a => Show (Api a) Source # | |
Eq a => Eq (Api a) 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 "*"]
Instances
IsString Path Source # | |
Defined in Mig.Core.Api fromString :: String -> Path # | |
Monoid Path Source # | |
Semigroup Path Source # | |
Show Path Source # | |
Eq Path Source # | |
Ord Path Source # | |
ToHttpApiData Path Source # | |
Defined in Mig.Core.Api toUrlPiece :: Path -> Text # toEncodedUrlPiece :: Path -> Builder # toHeader :: Path -> ByteString # toQueryParam :: Path -> Text # toEncodedQueryParam :: Path -> Builder # |
Efficient representation of API to fetch routes
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
Path can be a static item or capture with a name
Instances
Show PathItem Source # | |
Eq PathItem Source # | |
Ord PathItem Source # | |
Defined in Mig.Core.Api | |
ToHttpApiData PathItem Source # | |
Defined in Mig.Core.Api toUrlPiece :: PathItem -> Text # toEncodedUrlPiece :: PathItem -> Builder # toHeader :: PathItem -> ByteString # toQueryParam :: PathItem -> Text # toEncodedQueryParam :: PathItem -> Builder # |
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.
newtype OutputMediaMap a Source #
filter by Accept header
Instances
Functor OutputMediaMap Source # | |
Defined in Mig.Core.Api fmap :: (a -> b) -> OutputMediaMap a -> OutputMediaMap b # (<$) :: a -> OutputMediaMap b -> OutputMediaMap a # | |
Show a => Show (OutputMediaMap a) Source # | |
Defined in Mig.Core.Api showsPrec :: Int -> OutputMediaMap a -> ShowS # show :: OutputMediaMap a -> String # showList :: [OutputMediaMap a] -> ShowS # | |
Eq a => Eq (OutputMediaMap a) Source # | |
Defined in Mig.Core.Api (==) :: OutputMediaMap a -> OutputMediaMap a -> Bool # (/=) :: OutputMediaMap a -> OutputMediaMap a -> Bool # |
newtype InputMediaMap a Source #
filter by Content-Type header
Instances
Functor InputMediaMap Source # | |
Defined in Mig.Core.Api fmap :: (a -> b) -> InputMediaMap a -> InputMediaMap b # (<$) :: a -> InputMediaMap b -> InputMediaMap a # | |
Show a => Show (InputMediaMap a) Source # | |
Defined in Mig.Core.Api showsPrec :: Int -> InputMediaMap a -> ShowS # show :: InputMediaMap a -> String # showList :: [InputMediaMap a] -> ShowS # | |
Eq a => Eq (InputMediaMap a) Source # | |
Defined in Mig.Core.Api (==) :: InputMediaMap a -> InputMediaMap a -> Bool # (/=) :: InputMediaMap a -> InputMediaMap a -> Bool # |