servant/servant/src/Servant/API/Alternative.hs

33 lines
961 B
Haskell
Raw Normal View History

2015-04-20 19:52:29 +02:00
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeOperators #-}
2015-05-02 03:21:03 +02:00
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Alternative ((:<|>)(..)) where
2015-04-20 19:52:29 +02:00
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid (..))
2015-04-20 19:52:29 +02:00
#endif
import Data.Typeable (Typeable)
-- | Union of two APIs, first takes precedence in case of overlap.
2014-11-22 15:08:25 +01:00
--
-- Example:
--
-- >>> :{
--type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
-- :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] () -- POST /books
-- :}
data a :<|> b = a :<|> b
deriving (Typeable, Eq, Show)
infixr 8 :<|>
instance (Monoid a, Monoid b) => Monoid (a :<|> b) where
mempty = mempty :<|> mempty
(a :<|> b) `mappend` (a' :<|> b') = (a `mappend` a') :<|> (b `mappend` b')
-- $setup
-- >>> import Servant.API
-- >>> import Data.Aeson
-- >>> import Data.Text
-- >>> data Book
-- >>> instance ToJSON Book where { toJSON = undefined }