-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A family of combinators for defining webservices APIs and serving them -- @package servant @version 0.2 module Servant.Common.Text -- | For getting values from url captures and query string parameters class FromText a fromText :: FromText a => Text -> Maybe a -- | For putting values in paths and query string parameters class ToText a toText :: ToText a => a -> Text instance ToText Float instance FromText Float instance ToText Double instance FromText Double instance ToText Integer instance FromText Integer instance ToText Word64 instance FromText Word64 instance ToText Word32 instance FromText Word32 instance ToText Word16 instance FromText Word16 instance ToText Word8 instance FromText Word8 instance ToText Word instance FromText Word instance ToText Int64 instance FromText Int64 instance ToText Int32 instance FromText Int32 instance ToText Int16 instance FromText Int16 instance ToText Int8 instance FromText Int8 instance ToText Int instance FromText Int instance ToText Bool instance FromText Bool instance ToText String instance FromText String instance ToText Text instance FromText Text -- | This module lets you implement Servers for defined APIs. You'll -- most likely just need serve. module Servant.Server -- | serve allows you to implement an API and produce a wai -- Application. -- -- Example: -- --
--   type MyApi = "books" :> Get [Book] -- GET /books
--           :<|> "books" :> ReqBody Book :> Post Book -- POST /books
--   
--   server :: Server MyApi
--   server = listAllBooks :<|> postBook
--     where listAllBooks = ...
--           postBook book = ...
--   
--   app :: Application
--   app = serve myApi server
--   
--   main :: IO ()
--   main = Network.Wai.Handler.Warp.run 8080 app
--   
serve :: HasServer layout => Proxy layout -> Server layout -> Application toApplication :: RoutingApplication -> Application data RouteMismatch -- | the usual "not found" error NotFound :: RouteMismatch -- | a more informative "you just got the HTTP method wrong" error WrongMethod :: RouteMismatch -- | an even more informative "your json request body wasn't valid" error InvalidBody :: RouteMismatch -- |
--   > mempty = NotFound
--   >
--   > NotFound    mappend           x = x
--   > WrongMethod mappend InvalidBody = InvalidBody
--   > WrongMethod mappend           _ = WrongMethod
--   > InvalidBody mappend           _ = InvalidBody
--   
-- | A wrapper around Either RouteMismatch a. newtype RouteResult a RR :: Either RouteMismatch a -> RouteResult a routeResult :: RouteResult a -> Either RouteMismatch a failWith :: RouteMismatch -> RouteResult a succeedWith :: a -> RouteResult a isMismatch :: RouteResult a -> Bool -- | If we get a Right, it has precedence over everything else. -- -- This in particular means that if we could get several Rights, -- only the first we encounter would be taken into account. type RoutingApplication = Request -> (RouteResult Response -> IO ResponseReceived) -> IO ResponseReceived class HasServer layout where type family Server layout :: * route :: HasServer layout => Proxy layout -> Server layout -> RoutingApplication instance Eq RouteMismatch instance Show RouteMismatch instance Eq a => Eq (RouteResult a) instance Show a => Show (RouteResult a) instance Monoid (RouteResult a) instance Monoid RouteMismatch module Servant.API.Sub -- | The contained API (second argument) can be found under ("/" ++ -- path) (path being the first argument). -- -- Example: -- --
--   -- GET /hello/world
--   -- returning a JSON encoded World value
--   type MyApi = "hello" :> "world" :> Get World
--   
data (:>) (path :: k) a (:>) :: Proxy path -> a -> (:>) a -- | Make sure the incoming request starts with "/path", strip it -- and pass the rest of the request path to sublayout. instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) module Servant.API.Alternative -- | Union of two APIs, first takes precedence in case of overlap. -- -- Example: -- --
--   type MyApi = "books" :> Get [Book] -- GET /books
--           :<|> "books" :> ReqBody Book :> Post Book -- POST /books
--   
data (:<|>) a b (:<|>) :: a -> b -> (:<|>) a b -- | A server for a :<|> b first tries to match the -- request again the route represented by a and if it fails -- tries b. You must provide a request handler for each route. -- --
--   type MyApi = "books" :> Get [Book] -- GET /books
--           :<|> "books" :> ReqBody Book :> Post Book -- POST /books
--   
--   server :: Server MyApi
--   server = listAllBooks :<|> postBook
--     where listAllBooks = ...
--           postBook book = ...
--   
instance (HasServer a, HasServer b) => HasServer (a :<|> b) module Servant.API.Capture -- | Capture a value from the request path under a certain type a. -- -- Example: -- --
--              -- GET /books/:isbn
--   type MyApi = "books" :> Capture "isbn" Text :> Get Book
--   
data Capture sym a instance (KnownSymbol capture, FromText a, HasServer sublayout) => HasServer (Capture capture a :> sublayout) module Servant.API.Header -- | Extract the given header's value as a value of type a. -- -- Example: -- --
--   newtype Referer = Referer Text
--     deriving (Eq, Show, FromText, ToText)
--   
--              -- GET /view-my-referer
--   type MyApi = "view-my-referer" :> Header "from" Referer :> Get Referer
--   
data Header sym a -- | If you use Header in one of the endpoints for your API, this -- automatically requires your server-side handler to be a function that -- takes an argument of the type specified by Header. This lets -- servant worry about extracting it from the request and turning it into -- a value of the type you specify. -- -- All it asks is for a FromText instance. -- -- Example: -- --
--   newtype Referer = Referer Text
--     deriving (Eq, Show, FromText, ToText)
--   
--              -- GET /view-my-referer
--   type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get Referer
--   
--   server :: Server MyApi
--   server = viewReferer
--     where viewReferer :: Referer -> EitherT (Int, String) IO referer
--           viewReferer referer = return referer
--   
instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (Header sym a :> sublayout) module Servant.API.QueryParam -- | Lookup the value associated to the sym query string parameter -- and try to extract it as a value of type a. -- -- Example: -- --
--   -- /books?author=<author name>
--   type MyApi = "books" :> QueryParam "author" Text :> Get [Book]
--   
data QueryParam sym a -- | If you use QueryParam "author" Text in one of the -- endpoints for your API, this automatically requires your server-side -- handler to be a function that takes an argument of type -- Maybe Text. -- -- This lets servant worry about looking it up in the query string and -- turning it into a value of the type you specify, enclosed in -- Maybe, because it may not be there and servant would then hand -- you Nothing. -- -- You can control how it'll be converted from Text to your type -- by simply providing an instance of FromText for your type. -- -- Example: -- --
--   type MyApi = "books" :> QueryParam "author" Text :> Get [Book]
--   
--   server :: Server MyApi
--   server = getBooksBy
--     where getBooksBy :: Maybe Text -> EitherT (Int, String) IO [Book]
--           getBooksBy Nothing       = ...return all books...
--           getBooksBy (Just author) = ...return books by the given author...
--   
-- | Lookup the values associated to the sym query string -- parameter and try to extract it as a value of type [a]. This -- is typically meant to support query string parameters of the form -- param[]=val1&param[]=val2 and so on. Note that servant -- doesn't actually require the []s and will fetch the values -- just fine with param=val1&param=val2, too. -- -- Example: -- --
--   -- /books?authors[]=<author1>&authors[]=<author2>&...
--   type MyApi = "books" :> QueryParams "authors" Text :> Get [Book]
--   
data QueryParams sym a -- | If you use QueryParams "authors" Text in one of the -- endpoints for your API, this automatically requires your server-side -- handler to be a function that takes an argument of type -- [Text]. -- -- This lets servant worry about looking up 0 or more values in the query -- string associated to authors and turning each of them into a -- value of the type you specify. -- -- You can control how the individual values are converted from -- Text to your type by simply providing an instance of -- FromText for your type. -- -- Example: -- --
--   type MyApi = "books" :> QueryParams "authors" Text :> Get [Book]
--   
--   server :: Server MyApi
--   server = getBooksBy
--     where getBooksBy :: [Text] -> EitherT (Int, String) IO [Book]
--           getBooksBy authors = ...return all books by these authors...
--   
-- | Lookup a potentially value-less query string parameter with boolean -- semantics. If the param sym is there without any value, or if -- it's there with value "true" or "1", it's interpreted as True. -- Otherwise, it's interpreted as False. -- -- Example: -- --
--   -- /books?published
--   type MyApi = "books" :> QueryFlag "published" :> Get [Book]
--   
data QueryFlag sym -- | If you use QueryFlag "published" in one of the -- endpoints for your API, this automatically requires your server-side -- handler to be a function that takes an argument of type Bool. -- -- Example: -- --
--   type MyApi = "books" :> QueryFlag "published" :> Get [Book]
--   
--   server :: Server MyApi
--   server = getBooks
--     where getBooks :: Bool -> EitherT (Int, String) IO [Book]
--           getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
--   
instance (KnownSymbol sym, HasServer sublayout) => HasServer (QueryFlag sym :> sublayout) instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParams sym a :> sublayout) instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParam sym a :> sublayout) module Servant.API.ReqBody -- | Extract the request body as a value of type a. -- -- Example: -- --
--              -- POST /books
--   type MyApi = "books" :> ReqBody Book :> Post Book
--   
data ReqBody a -- | If you use ReqBody in one of the endpoints for your API, this -- automatically requires your server-side handler to be a function that -- takes an argument of the type specified by ReqBody. This lets -- servant worry about extracting it from the request and turning it into -- a value of the type you specify. -- -- All it asks is for a FromJSON instance. -- -- Example: -- --
--   type MyApi = "books" :> ReqBody Book :> Post Book
--   
--   server :: Server MyApi
--   server = postBook
--     where postBook :: Book -> EitherT (Int, String) IO Book
--           postBook book = ...insert into your db...
--   
instance (FromJSON a, HasServer sublayout) => HasServer (ReqBody a :> sublayout) module Servant.API.Get -- | Endpoint for simple GET requests. Serves the result as JSON. -- -- Example: -- --
--   type MyApi = "books" :> Get [Book]
--   
data Get a -- | When implementing the handler for a Get endpoint, just like for -- Delete, Post and Put, the handler code runs in -- the EitherT (Int, String) IO monad, where the Int -- represents the status code and the String a message, returned -- in case of failure. You can quite handily use left to quickly -- fail if some conditions are not met. -- -- If successfully returning a value, we just require that its type has a -- ToJSON instance and servant takes care of encoding it for you, -- yielding status code 200 along the way. instance Typeable Get instance ToJSON result => HasServer (Get result) module Servant.API.Post -- | Endpoint for POST requests. The type variable represents the type of -- the response body (not the request body, use RQBody for that). -- -- Example: -- --
--              -- POST /books
--              -- with a JSON encoded Book as the request body
--              -- returning the just-created Book
--   type MyApi = "books" :> ReqBody Book :> Post Book
--   
data Post a -- | When implementing the handler for a Post endpoint, just like -- for Delete, Get and Put, the handler code runs in -- the EitherT (Int, String) IO monad, where the Int -- represents the status code and the String a message, returned -- in case of failure. You can quite handily use left to quickly -- fail if some conditions are not met. -- -- If successfully returning a value, we just require that its type has a -- ToJSON instance and servant takes care of encoding it for you, -- yielding status code 201 along the way. instance Typeable Post instance ToJSON a => HasServer (Post a) module Servant.API.Delete -- | Combinator for DELETE requests. -- -- Example: -- --
--              -- DELETE /books/:isbn
--   type MyApi = "books" :> Capture "isbn" Text :> Delete
--   
data Delete -- | If you have a Delete endpoint in your API, the handler for this -- endpoint is meant to delete a resource. -- -- The code of the handler will, just like for Get, Post -- and Put, run in EitherT (Int, String) IO (). The -- Int represents the status code and the String a message -- to be returned. You can use left to painlessly error out if the -- conditions for a successful deletion are not met. instance Typeable Delete instance HasServer Delete module Servant.API.Put -- | Endpoint for PUT requests, usually used to update a ressource. The -- type a is the type of the response body that's returned. -- -- Example: -- --
--   -- PUT /books/:isbn
--   -- with a Book as request body, returning the updated Book
--   type MyApi = "books" :> Capture "isbn" Text :> ReqBody Book :> Put Book
--   
data Put a -- | When implementing the handler for a Put endpoint, just like for -- Delete, Get and Post, the handler code runs in -- the EitherT (Int, String) IO monad, where the Int -- represents the status code and the String a message, returned -- in case of failure. You can quite handily use left to quickly -- fail if some conditions are not met. -- -- If successfully returning a value, we just require that its type has a -- ToJSON instance and servant takes care of encoding it for you, -- yielding status code 200 along the way. instance Typeable Put instance ToJSON a => HasServer (Put a) -- | QuasiQuoting utilities for API types. -- -- sitemap allows you to write your type in a very natural way: -- --
--   [sitemap|
--   PUT        hello                 String -> ()
--   POST       hello/p:Int           String -> ()
--   GET        hello/?name:String    Int
--   |]
--   
-- -- Will generate: -- --
--        "hello" :> ReqBody String :> Put ()
--   :<|> "hello" :> Capture "p" Int :> ReqBody String :> Post ()
--   :<|> "hello" :> QueryParam "name" String :> Get Int
--   
-- -- Note the / before a QueryParam! module Servant.QQ -- | Finally-tagless encoding for our DSL. Keeping repr' and -- repr distinct when writing functions with an ExpSYM -- context ensures certain invariants (for instance, that there is only -- one of get, post, put, and delete in a -- value), but sometimes requires a little more work. class ExpSYM repr' repr | repr -> repr', repr' -> repr lit :: ExpSYM repr' repr => String -> repr' -> repr capture :: ExpSYM repr' repr => String -> String -> repr -> repr reqBody :: ExpSYM repr' repr => String -> repr -> repr queryParam :: ExpSYM repr' repr => String -> String -> repr -> repr conj :: ExpSYM repr' repr => repr' -> repr -> repr get :: ExpSYM repr' repr => String -> repr post :: ExpSYM repr' repr => String -> repr put :: ExpSYM repr' repr => String -> repr delete :: ExpSYM repr' repr => String -> repr (>:) :: Type -> Type -> Type parseMethod :: ExpSYM repr' repr => Parser (String -> repr) parseUrlSegment :: ExpSYM repr repr => Parser (repr -> repr) parseUrl :: ExpSYM repr repr => Parser (repr -> repr) data Typ Val :: String -> Typ ReqArgVal :: String -> String -> Typ parseTyp :: Parser Typ parseEntry :: ExpSYM repr repr => Parser repr blockComment :: Parser () inlineComment :: Parser () eol :: Parser String eols :: Parser () parseAll :: Parser Type -- | The sitemap QuasiQuoter. -- -- -- -- Comments are allowed, and have the standard Haskell format -- -- sitemap :: QuasiQuoter instance ExpSYM Type Type -- | Type safe internal links. -- -- Provides the function mkLink: -- --
--   type API = Proxy ("hello" :> Get Int
--                :| "bye" :> QueryParam "name" String :> Post Bool)
--   
--   api :: API
--   api = proxy
--   
--   link1 :: Proxy ("hello" :> Get Int)
--   link1 = proxy
--   
--   link2 :: Proxy ("hello" :> Delete)
--   link2 = proxy
--   
--   mkLink link1 API  --  typechecks, returns 'Link "/hello"'
--   
--   mkLink link2  API  -- doesn't typecheck
--   
-- -- That is, mkLink takes two arguments, a link proxy and a -- sitemap, and returns a Link, but only typechecks if the link -- proxy is a valid link, and part of the sitemap. -- -- N.B.: mkLink assumes a capture matches any string -- (without slashes). module Servant.Utils.Links -- | The 'ValidLinkIn f s' constraint holds when s is an API that -- contains f, and f is a link. class ValidLinkIn f s mkLink :: ValidLinkIn f s => f -> s -> Link data Link Link :: String -> Link class VLinkHelper f vlh :: VLinkHelper f => proxy f -> String instance Show Link instance VLinkHelper (Post x) instance VLinkHelper (Get x) instance (KnownSymbol s, VLinkHelper e) => VLinkHelper (s :> e) instance (IsElem f s ~ 'True, IsLink f ~ 'True, VLinkHelper f) => ValidLinkIn f s module Servant.API.Raw -- | Endpoint for plugging in your own Wai Applications. -- -- The given Application will get the request as received by the -- server, potentially with a modified (stripped) pathInfo if the -- Application is being routed with :>. -- -- In addition to just letting you plug in your existing WAI -- Applications, this can also be used with serveDirectory -- to serve static files stored in a particular directory on your -- filesystem, or to serve your API's documentation with -- serveDocumentation. data Raw -- | Just pass the request to the underlying application and serve its -- response. -- -- Example: -- --
--   type MyApi = "images" :> Raw
--   
--   server :: Server MyApi
--   server = serveDirectory "/var/www/images"
--   
instance HasServer Raw -- | This module defines a sever-side handler that lets you serve static -- files. -- -- module Servant.Utils.StaticFiles -- | Serve anything under the specified directory as a Raw endpoint. -- --
--   type MyApi = "static" :> Raw
--   
--   server :: Server MyApi
--   server = serveDirectory "/var/www"
--   
-- -- would capture any request to /static/<something> and -- look for <something> under /var/www. -- -- It will do its best to guess the MIME type for that file, based on the -- extension, and send an appropriate Content-Type header if -- possible. -- -- If your goal is to serve HTML, CSS and Javascript files that use the -- rest of the API as a webapp backend, you will most likely not want the -- static files to be hidden behind a /static/ prefix. In that -- case, remember to put the serveDirectory handler in the last -- position, because servant will try to match the handlers in -- order. serveDirectory :: FilePath -> Server Raw module Servant.API module Servant -- | A concrete, poly-kinded proxy type data Proxy (t :: k) :: k -> * Proxy :: Proxy