Skip to content

Commit

Permalink
Annotation on Method
Browse files Browse the repository at this point in the history
  • Loading branch information
Hyojun Kang committed Aug 10, 2016
1 parent 7255996 commit 1f1f169
Show file tree
Hide file tree
Showing 7 changed files with 58 additions and 22 deletions.
13 changes: 10 additions & 3 deletions src/Nirum/Constructs/Service.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Nirum.Constructs.Service ( Method ( Method
, methodAnnotations
, methodDocs
, methodName
, parameters
Expand All @@ -12,6 +13,7 @@ module Nirum.Constructs.Service ( Method ( Method
import qualified Data.Text as T

import Nirum.Constructs (Construct(toCode))
import Nirum.Constructs.Annotation (AnnotationSet)
import Nirum.Constructs.Declaration ( Declaration(name, docs)
, Docs
, toCodeWithPrefix
Expand Down Expand Up @@ -40,13 +42,18 @@ instance Declaration Parameter where
-- | 'Service' method.
data Method = Method { methodName :: Name
, parameters :: DeclarationSet Parameter
, returnType :: TypeExpression
, returnType :: TypeExpression
, methodDocs :: Maybe Docs
, methodAnnotations :: AnnotationSet
} deriving (Eq, Ord, Show)

instance Construct Method where
toCode method@Method { parameters = params, methodDocs = docs' } =
T.concat $ [ toCode $ returnType method
toCode method@Method { parameters = params
, methodDocs = docs'
, methodAnnotations = annotationSet'
} =
T.concat $ [ toCode annotationSet'
, toCode $ returnType method
, " "
, toCode $ methodName method
, " ("
Expand Down
3 changes: 2 additions & 1 deletion src/Nirum/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -438,6 +438,7 @@ parameterSet = option empty $ try $ do

method :: Parser Method
method = do
annotationSet' <- annotationSet <?> "service method annotation"
returnType <- typeExpression <?> "method return type"
spaces1
methodName <- name <?> "method name"
Expand All @@ -451,7 +452,7 @@ method = do
params <- parameterSet
spaces
char ')'
return $ Method methodName params returnType docs'
return $ Method methodName params returnType docs' annotationSet'

methods :: Parser [Method]
methods = method `sepEndBy` try (spaces >> char ',' >> spaces)
Expand Down
4 changes: 2 additions & 2 deletions src/Nirum/Targets/Python.hs
Original file line number Diff line number Diff line change
Expand Up @@ -515,7 +515,7 @@ class $className(service_type):
commaNl :: [T.Text] -> T.Text
commaNl = T.intercalate ",\n"
compileMethod :: Method -> CodeGen Code
compileMethod (Method mName params rtype _) = do
compileMethod (Method mName params rtype _ _) = do
let mName' = toAttributeName' mName
params' <- mapM compileParameter $ toList params
rtypeExpr <- compileTypeExpression src rtype
Expand All @@ -528,7 +528,7 @@ class $className(service_type):
pTypeExpr <- compileTypeExpression src pType
return [qq|{toAttributeName' pName}: $pTypeExpr|]
compileMethodMetadata :: Method -> CodeGen Code
compileMethodMetadata (Method mName params rtype _) = do
compileMethodMetadata (Method mName params rtype _ _) = do
let params' = toList params :: [Parameter]
rtypeExpr <- compileTypeExpression src rtype
paramMetadata <- mapM compileParameterMetadata params'
Expand Down
33 changes: 23 additions & 10 deletions test/Nirum/Constructs/ServiceSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,44 +3,53 @@ module Nirum.Constructs.ServiceSpec where

import Test.Hspec.Meta

import Nirum.Constructs.Annotation (Annotation (Annotation), empty, fromList)
import Nirum.Constructs.Declaration (toCode)
import Nirum.Constructs.Service (Method(Method), Parameter(Parameter))
import Nirum.Constructs.TypeExpression ( TypeExpression ( ListModifier
, OptionModifier
)
)


spec :: Spec
spec = do
let Right methodAnno = fromList [Annotation "http-get" "/ping/"]
describe "Parameter" $
specify "toCode" $ do
toCode (Parameter "dob" "date" Nothing) `shouldBe` "date dob,"
toCode (Parameter "dob" "date" $ Just "docs...") `shouldBe`
"date dob,\n# docs..."
describe "Method" $
specify "toCode" $ do
toCode (Method "ping" [] "bool" Nothing) `shouldBe`
toCode (Method "ping" [] "bool" Nothing empty) `shouldBe`
"bool ping (),"
toCode (Method "ping" [] "bool" $ Just "docs...") `shouldBe`
toCode (Method "ping" [] "bool" Nothing methodAnno) `shouldBe`
"[http-get: \"/ping/\"]\nbool ping (),"
toCode (Method "ping" [] "bool" (Just "docs...") empty) `shouldBe`
"bool ping (\n # docs...\n),"
toCode (Method "get-user"
[Parameter "user-id" "uuid" Nothing]
(OptionModifier "user")
Nothing) `shouldBe` "user? get-user (uuid user-id),"
Nothing
empty) `shouldBe` "user? get-user (uuid user-id),"
toCode (Method "get-user"
[Parameter "user-id" "uuid" Nothing]
(OptionModifier "user")
$ Just "docs...") `shouldBe`
(Just "docs...")
empty) `shouldBe`
"user? get-user (\n # docs...\n uuid user-id,\n),"
toCode (Method "get-user"
[Parameter "user-id" "uuid" $ Just "param docs..."]
(OptionModifier "user")
Nothing) `shouldBe`
Nothing
empty) `shouldBe`
"user? get-user (\n uuid user-id,\n # param docs...\n),"
toCode (Method "get-user"
[Parameter "user-id" "uuid" $ Just "param docs..."]
(OptionModifier "user")
$ Just "docs...") `shouldBe`
(Just "docs...")
empty) `shouldBe`
"user? get-user (\n\
\ # docs...\n\
\ uuid user-id,\n\
Expand All @@ -51,14 +60,16 @@ spec = do
, Parameter "keyword" "text" Nothing
]
(ListModifier "post")
Nothing) `shouldBe`
Nothing
empty) `shouldBe`
"[post] search-posts (\n uuid blog-id,\n text keyword,\n),"
toCode (Method "search-posts"
[ Parameter "blog-id" "uuid" Nothing
, Parameter "keyword" "text" Nothing
]
(ListModifier "post")
$ Just "docs...") `shouldBe`
(Just "docs...")
empty) `shouldBe`
"[post] search-posts (\n\
\ # docs...\n\
\ uuid blog-id,\n\
Expand All @@ -69,7 +80,8 @@ spec = do
, Parameter "keyword" "text" $ Just "keyword..."
]
(ListModifier "post")
Nothing) `shouldBe`
Nothing
empty) `shouldBe`
"[post] search-posts (\n\
\ uuid blog-id,\n\
\ # blog id...\n\
Expand All @@ -81,7 +93,8 @@ spec = do
, Parameter "keyword" "text" $ Just "keyword..."
]
(ListModifier "post")
$ Just "docs...") `shouldBe`
(Just "docs...")
empty) `shouldBe`
"[post] search-posts (\n\
\ # docs...\n\
\ uuid blog-id,\n\
Expand Down
2 changes: 1 addition & 1 deletion test/Nirum/Constructs/TypeDeclarationSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,7 @@ spec = do
ServiceDeclaration "null-service" nullService
(Just "Null service declaration.")
empty
pingService = Service [ Method "ping" [] "bool" Nothing ]
pingService = Service [ Method "ping" [] "bool" Nothing empty ]
pingDecl = ServiceDeclaration "ping-service" pingService Nothing
empty
pingDecl' =
Expand Down
22 changes: 18 additions & 4 deletions test/Nirum/ParserSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -569,23 +569,31 @@ spec = do

describe "method" $ do
let (parse', expectError) = helperFuncs P.method
httpGetAnnotation =
head $ rights [fromList [Annotation "http-get" "/get-name/"]]
it "emits Method if succeeded to parse" $ do
parse' "text get-name()" `shouldBeRight`
Method "get-name" [] "text" Nothing
Method "get-name" [] "text" Nothing empty
parse' "text get-name (person user)" `shouldBeRight`
Method "get-name" [Parameter "user" "person" Nothing]
"text" Nothing
"text" Nothing empty
parse' "text get-name ( person user,text default )" `shouldBeRight`
Method "get-name"
[ Parameter "user" "person" Nothing
, Parameter "default" "text" Nothing
]
"text" Nothing
"text" Nothing empty
parse' "[http-get: \"/get-name/\"] text get-name ( person user,text default )" `shouldBeRight`
Method "get-name"
[ Parameter "user" "person" Nothing
, Parameter "default" "text" Nothing
]
"text" Nothing httpGetAnnotation
it "can have docs" $ do
parse' "text get-name (\n\
\ # Gets the name.\n\
\)" `shouldBeRight`
Method "get-name" [] "text" (Just "Gets the name.")
Method "get-name" [] "text" (Just "Gets the name.") empty
parse' "text get-name (\n\
\ # Gets the name of the user.\n\
\ person user,\n\
Expand All @@ -594,6 +602,7 @@ spec = do
[Parameter "user" "person" Nothing]
"text"
(Just "Gets the name of the user.")
empty
parse' "text get-name (\n\
\ # Gets the name of the user.\n\
\ person user,\n\
Expand All @@ -610,6 +619,7 @@ spec = do
]
"text"
(Just "Gets the name of the user.")
empty
it "fails to parse if there are parameters of the same facial name" $ do
expectError "bool pred(text a, text a/b)" 1 11
expectError "bool pred(text a/b, text a)" 1 11
Expand Down Expand Up @@ -640,6 +650,7 @@ spec = do
[Parameter "user-id" "uuid" Nothing]
"user"
Nothing
empty
])
Nothing
empty
Expand All @@ -656,6 +667,7 @@ spec = do
[Parameter "user-id" "uuid" Nothing]
"user"
(Just "Gets an user by its id.")
empty
])
(Just "Service having only one method.")
empty
Expand All @@ -676,10 +688,12 @@ spec = do
[Parameter "user" "user" Nothing]
"user"
(Just "Creates a new user")
empty
, Method "get-user"
[Parameter "user-id" "uuid" Nothing]
"user"
(Just "Gets an user by its id.")
empty
])
(Just "Service having multiple methods.")
empty
Expand Down
3 changes: 2 additions & 1 deletion test/Nirum/Targets/PythonSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -760,7 +760,8 @@ spec = parallel $ do
pingService = Service [Method "ping"
[Parameter "nonce" "text" Nothing]
"bool"
Nothing]
Nothing
empty]
ping' = ServiceDeclaration "ping-service" pingService
Nothing empty
tT null' "issubclass(NullService, __import__('nirum').rpc.Service)"
Expand Down

0 comments on commit 1f1f169

Please sign in to comment.