2014-10-28 13:22:11 +01:00
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE FunctionalDependencies #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2014-10-28 15:22:28 +01:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2014-11-12 11:34:33 +01:00
|
|
|
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
2014-11-07 09:55:17 +01:00
|
|
|
module Servant.Utils.ApiQuasiQuoting where
|
2014-10-28 13:22:11 +01:00
|
|
|
|
2014-11-12 11:34:33 +01:00
|
|
|
import Control.Monad (void)
|
|
|
|
import Control.Applicative hiding (many, (<|>), optional)
|
2014-10-28 15:22:28 +01:00
|
|
|
import Language.Haskell.TH.Quote
|
2014-10-28 13:22:11 +01:00
|
|
|
import Language.Haskell.TH
|
2014-11-12 11:34:33 +01:00
|
|
|
import Text.ParserCombinators.Parsec
|
2014-10-28 13:22:11 +01:00
|
|
|
|
|
|
|
import Servant.API.Capture
|
|
|
|
import Servant.API.Get
|
|
|
|
import Servant.API.Post
|
|
|
|
import Servant.API.Put
|
|
|
|
import Servant.API.Delete
|
2014-10-29 13:10:04 +01:00
|
|
|
import Servant.API.QueryParam
|
|
|
|
import Servant.API.ReqBody
|
2014-10-28 13:22:11 +01:00
|
|
|
import Servant.API.Sub
|
2014-10-30 11:37:58 +01:00
|
|
|
import Servant.API.Alternative
|
2014-10-28 13:22:11 +01:00
|
|
|
|
|
|
|
class ExpSYM repr' repr | repr -> repr', repr' -> repr where
|
2014-10-28 15:22:28 +01:00
|
|
|
lit :: String -> repr' -> repr
|
|
|
|
capture :: String -> String -> repr -> repr
|
2014-10-29 13:10:04 +01:00
|
|
|
reqBody :: String -> repr -> repr
|
|
|
|
queryParam :: String -> String -> repr -> repr
|
2014-10-28 15:22:28 +01:00
|
|
|
conj :: repr' -> repr -> repr
|
|
|
|
get :: String -> repr
|
|
|
|
post :: String -> repr
|
|
|
|
put :: String -> repr
|
|
|
|
delete :: String -> repr
|
|
|
|
|
2014-11-12 11:34:33 +01:00
|
|
|
|
2014-10-28 15:22:28 +01:00
|
|
|
infixr 6 >:
|
|
|
|
|
|
|
|
(>:) :: Type -> Type -> Type
|
|
|
|
(>:) = conj
|
2014-10-28 13:22:11 +01:00
|
|
|
|
2014-10-28 17:32:22 +01:00
|
|
|
|
2014-10-28 13:22:11 +01:00
|
|
|
instance ExpSYM Type Type where
|
2014-10-29 14:54:13 +01:00
|
|
|
lit name r = LitT (StrTyLit name) >: r
|
|
|
|
capture name typ r = AppT (AppT (ConT ''Capture) (LitT (StrTyLit name)))
|
|
|
|
(ConT $ mkName typ) >: r
|
|
|
|
reqBody typ r = AppT (ConT ''ReqBody) (ConT $ mkName typ) >: r
|
|
|
|
queryParam name typ r = AppT (AppT (ConT ''QueryParam) (LitT (StrTyLit name)))
|
|
|
|
(ConT $ mkName typ) >: r
|
|
|
|
conj x = AppT (AppT (ConT ''(:>)) x)
|
2014-10-29 13:10:04 +01:00
|
|
|
get typ = AppT (ConT ''Get) (ConT $ mkName typ)
|
|
|
|
post typ = AppT (ConT ''Post) (ConT $ mkName typ)
|
|
|
|
put typ = AppT (ConT ''Put) (ConT $ mkName typ)
|
|
|
|
delete "()" = ConT ''Delete
|
|
|
|
delete _ = error "Delete does not return a request body"
|
2014-10-28 15:22:28 +01:00
|
|
|
|
2014-11-12 11:34:33 +01:00
|
|
|
parseMethod :: ExpSYM repr' repr => Parser (String -> repr)
|
|
|
|
parseMethod = try (string "GET" >> return get)
|
|
|
|
<|> try (string "POST" >> return post)
|
|
|
|
<|> try (string "PUT" >> return put)
|
|
|
|
<|> try (string "DELETE" >> return delete)
|
|
|
|
|
|
|
|
parseUrlSegment :: ExpSYM repr repr => Parser (repr -> repr)
|
|
|
|
parseUrlSegment = try parseCapture
|
|
|
|
<|> try parseQueryParam
|
|
|
|
<|> try parseLit
|
|
|
|
where
|
|
|
|
parseCapture = do
|
|
|
|
cname <- many (noneOf " ?/:")
|
|
|
|
char ':'
|
|
|
|
ctyp <- many (noneOf " ?/:")
|
|
|
|
return $ capture cname ctyp
|
|
|
|
parseQueryParam = do
|
|
|
|
char '?'
|
|
|
|
cname <- many (noneOf " ?/:")
|
|
|
|
char ':'
|
|
|
|
ctyp <- many (noneOf " ?/:")
|
|
|
|
return $ queryParam cname ctyp
|
|
|
|
parseLit = lit <$> many (noneOf " ?/:")
|
|
|
|
|
|
|
|
parseUrl :: ExpSYM repr repr => Parser (repr -> repr)
|
|
|
|
parseUrl = do
|
|
|
|
optional $ char '/'
|
|
|
|
url <- parseUrlSegment `sepBy1` char '/'
|
|
|
|
return $ foldr1 (.) url
|
|
|
|
|
|
|
|
data Typ = Val String
|
|
|
|
| ReqArgVal String String
|
|
|
|
|
|
|
|
parseTyp :: Parser Typ
|
|
|
|
parseTyp = do
|
2014-11-13 18:22:26 +01:00
|
|
|
f <- many (noneOf "-{\n\r")
|
2014-11-12 11:34:33 +01:00
|
|
|
spaces
|
2014-11-13 18:22:26 +01:00
|
|
|
s <- optionMaybe (try parseRet)
|
|
|
|
try $ optional inlineComment
|
|
|
|
try $ optional blockComment
|
2014-11-12 11:34:33 +01:00
|
|
|
case s of
|
|
|
|
Nothing -> return $ Val (stripTr f)
|
|
|
|
Just s' -> return $ ReqArgVal (stripTr f) (stripTr s')
|
|
|
|
where
|
|
|
|
parseRet :: Parser String
|
|
|
|
parseRet = do
|
|
|
|
string "->"
|
|
|
|
spaces
|
2014-11-13 18:22:26 +01:00
|
|
|
many (noneOf "-{\n\r")
|
2014-11-12 11:34:33 +01:00
|
|
|
stripTr = reverse . dropWhile (== ' ') . reverse
|
|
|
|
|
|
|
|
|
|
|
|
parseEntry :: ExpSYM repr repr => Parser repr
|
|
|
|
parseEntry = do
|
|
|
|
met <- parseMethod
|
|
|
|
spaces
|
|
|
|
url <- parseUrl
|
|
|
|
spaces
|
|
|
|
typ <- parseTyp
|
|
|
|
case typ of
|
|
|
|
Val s -> return $ url (met s)
|
|
|
|
ReqArgVal i o -> return $ url $ reqBody i (met o)
|
|
|
|
|
2014-11-13 18:22:26 +01:00
|
|
|
blockComment :: Parser ()
|
|
|
|
blockComment = do
|
|
|
|
string "{-"
|
|
|
|
manyTill anyChar (try $ string "-}")
|
|
|
|
return ()
|
|
|
|
|
|
|
|
inlineComment :: Parser ()
|
|
|
|
inlineComment = do
|
|
|
|
string "--"
|
|
|
|
manyTill anyChar (try $ lookAhead eol)
|
|
|
|
return ()
|
|
|
|
|
2014-11-12 11:34:33 +01:00
|
|
|
eol :: Parser String
|
|
|
|
eol = try (string "\n\r")
|
|
|
|
<|> try (string "\r\n")
|
|
|
|
<|> string "\n"
|
|
|
|
<|> string "\r"
|
|
|
|
<?> "end of line"
|
|
|
|
|
|
|
|
eols :: Parser ()
|
2014-11-13 18:22:26 +01:00
|
|
|
eols = skipMany $ void eol <|> blockComment <|> inlineComment
|
2014-11-12 11:34:33 +01:00
|
|
|
|
|
|
|
parseAll :: Parser Type
|
|
|
|
parseAll = do
|
|
|
|
eols
|
|
|
|
entries <- parseEntry `endBy` eols
|
|
|
|
return $ foldr1 union entries
|
|
|
|
where union :: Type -> Type -> Type
|
|
|
|
union a = AppT (AppT (ConT ''(:<|>)) a)
|
2014-10-28 15:22:28 +01:00
|
|
|
|
|
|
|
sitemap :: QuasiQuoter
|
|
|
|
sitemap = QuasiQuoter { quoteExp = undefined
|
|
|
|
, quotePat = undefined
|
2014-11-12 11:34:33 +01:00
|
|
|
, quoteType = \x -> case parse parseAll "" x of
|
|
|
|
Left err -> error $ show err
|
|
|
|
Right st -> return st
|
2014-10-28 15:22:28 +01:00
|
|
|
, quoteDec = undefined
|
|
|
|
}
|
2014-10-28 13:22:11 +01:00
|
|
|
|