More instances for Alternative

This commit is contained in:
Julian K. Arni 2015-09-28 18:06:49 +02:00
parent de447dfe22
commit f14d227b11

View file

@ -1,5 +1,7 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Alternative ((:<|>)(..)) where module Servant.API.Alternative ((:<|>)(..)) where
@ -17,7 +19,7 @@ import Data.Typeable (Typeable)
-- :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] () -- POST /books -- :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] () -- POST /books
-- :} -- :}
data a :<|> b = a :<|> b data a :<|> b = a :<|> b
deriving (Typeable, Eq, Show) deriving (Typeable, Eq, Show, Functor, Traversable, Foldable, Bounded)
infixr 8 :<|> infixr 8 :<|>
instance (Monoid a, Monoid b) => Monoid (a :<|> b) where instance (Monoid a, Monoid b) => Monoid (a :<|> b) where