servant/servant-server/test/Servant/ServerSpec.hs

562 lines
21 KiB
Haskell
Raw Normal View History

2015-10-12 19:23:13 +02:00
{-# LANGUAGE CPP #-}
2015-10-12 19:14:42 +02:00
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleInstances #-}
2015-10-12 19:14:42 +02:00
{-# LANGUAGE OverloadedStrings #-}
2016-01-08 17:43:10 +01:00
{-# LANGUAGE PolyKinds #-}
2015-10-12 19:14:42 +02:00
{-# LANGUAGE ScopedTypeVariables #-}
2016-01-08 17:43:10 +01:00
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
2015-10-12 19:14:42 +02:00
{-# LANGUAGE TypeSynonymInstances #-}
2014-12-10 16:10:57 +01:00
module Servant.ServerSpec where
2015-10-12 19:23:13 +02:00
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
2016-01-08 17:43:10 +01:00
import Control.Monad (forM_, when, unless)
2015-09-12 14:11:24 +02:00
import Control.Monad.Trans.Except (ExceptT, throwE)
import Data.Aeson (FromJSON, ToJSON, decode', encode)
import Data.ByteString.Conversion ()
import Data.Char (toUpper)
import Data.Proxy (Proxy (Proxy))
import Data.String (fromString)
import Data.String.Conversions (cs)
import qualified Data.Text as T
import GHC.Generics (Generic)
2016-01-08 17:43:10 +01:00
import Network.HTTP.Types (Status (..), hAccept, hContentType,
methodDelete, methodGet,
methodHead, methodPatch,
methodPost, methodPut, ok200,
parseQuery)
import Network.Wai (Application, Request, pathInfo,
queryString, rawQueryString,
2016-01-08 17:43:10 +01:00
responseBuilder, responseLBS)
import Network.Wai.Internal (Response (ResponseBuilder))
import Network.Wai.Test (defaultRequest, request,
2016-01-08 17:43:10 +01:00
runSession, simpleBody,
simpleHeaders, simpleStatus)
import Servant.API ((:<|>) (..), (:>), Capture, Delete,
2016-01-08 17:43:10 +01:00
Get, Header (..),
Headers, HttpVersion,
IsSecure (..), JSON,
NoContent (..), Patch, PlainText,
Post, Put,
QueryFlag, QueryParam, QueryParams,
2016-01-08 17:43:10 +01:00
Raw, RemoteHost, ReqBody,
StdMethod (..), Verb, addHeader)
import Servant.API.Internal.Test.ComprehensiveAPI
2016-01-08 17:43:10 +01:00
import Servant.Server (ServantErr (..), Server, err404,
2016-02-28 23:23:32 +01:00
serve, serveWithContext, Context(EmptyContext))
2016-01-08 17:43:10 +01:00
import Test.Hspec (Spec, context, describe, it,
shouldBe, shouldContain)
import Test.Hspec.Wai (get, liftIO, matchHeaders,
2016-01-08 17:43:10 +01:00
matchStatus, request,
shouldRespondWith, with, (<:>))
2016-01-08 17:43:10 +01:00
import Servant.Server.Internal.RoutingApplication
(toApplication, RouteResult(..))
2015-10-12 19:23:13 +02:00
import Servant.Server.Internal.Router
(tweakResponse, runRouter,
Router, Router'(LeafRouter))
2016-02-28 23:23:32 +01:00
import Servant.Server.Internal.Context
(Context(..), NamedContext(..))
2014-12-10 16:10:57 +01:00
-- * comprehensive api test
-- This declaration simply checks that all instances are in place.
2016-02-28 23:23:32 +01:00
_ = serveWithContext comprehensiveAPI comprehensiveApiContext
2016-02-28 23:23:32 +01:00
comprehensiveApiContext :: Context '[NamedContext "foo" '[]]
comprehensiveApiContext = NamedContext EmptyContext :. EmptyContext
2014-12-10 16:10:57 +01:00
2016-01-08 17:43:10 +01:00
-- * Specs
2014-12-10 16:10:57 +01:00
spec :: Spec
spec = do
2016-01-08 17:43:10 +01:00
verbSpec
2014-12-10 16:10:57 +01:00
captureSpec
queryParamSpec
2016-01-08 17:43:10 +01:00
reqBodySpec
2015-02-24 14:48:17 +01:00
headerSpec
2014-12-10 16:10:57 +01:00
rawSpec
2016-01-08 17:43:10 +01:00
alternativeSpec
responseHeadersSpec
2016-01-08 17:43:10 +01:00
routerSpec
miscCombinatorSpec
------------------------------------------------------------------------------
-- * verbSpec {{{
------------------------------------------------------------------------------
type VerbApi method status
= Verb method status '[JSON] Person
:<|> "noContent" :> Verb method status '[JSON] NoContent
:<|> "header" :> Verb method status '[JSON] (Headers '[Header "H" Int] Person)
:<|> "headerNC" :> Verb method status '[JSON] (Headers '[Header "H" Int] NoContent)
verbSpec :: Spec
verbSpec = describe "Servant.API.Verb" $ do
let server :: Server (VerbApi method status)
server = return alice
:<|> return NoContent
:<|> return (addHeader 5 alice)
:<|> return (addHeader 10 NoContent)
get200 = Proxy :: Proxy (VerbApi 'GET 200)
post210 = Proxy :: Proxy (VerbApi 'POST 210)
put203 = Proxy :: Proxy (VerbApi 'PUT 203)
delete280 = Proxy :: Proxy (VerbApi 'DELETE 280)
patch214 = Proxy :: Proxy (VerbApi 'PATCH 214)
wrongMethod m = if m == methodPatch then methodPost else methodPatch
test desc api method (status :: Int) = context desc $
with (return $ serve api server) $ do
2016-01-08 17:43:10 +01:00
-- HEAD and 214/215 need not return bodies
unless (status `elem` [214, 215] || method == methodHead) $
it "returns the person" $ do
response <- Test.Hspec.Wai.request method "/" [] ""
liftIO $ statusCode (simpleStatus response) `shouldBe` status
liftIO $ decode' (simpleBody response) `shouldBe` Just alice
it "returns no content on NoContent" $ do
response <- Test.Hspec.Wai.request method "/noContent" [] ""
liftIO $ statusCode (simpleStatus response) `shouldBe` status
liftIO $ simpleBody response `shouldBe` ""
-- HEAD should not return body
when (method == methodHead) $
it "HEAD returns no content body" $ do
response <- Test.Hspec.Wai.request method "/" [] ""
liftIO $ simpleBody response `shouldBe` ""
it "throws 405 on wrong method " $ do
Test.Hspec.Wai.request (wrongMethod method) "/" [] ""
`shouldRespondWith` 405
it "returns headers" $ do
response1 <- Test.Hspec.Wai.request method "/header" [] ""
liftIO $ statusCode (simpleStatus response1) `shouldBe` status
liftIO $ simpleHeaders response1 `shouldContain` [("H", "5")]
response2 <- Test.Hspec.Wai.request method "/header" [] ""
liftIO $ statusCode (simpleStatus response2) `shouldBe` status
liftIO $ simpleHeaders response2 `shouldContain` [("H", "5")]
it "handles trailing '/' gracefully" $ do
response <- Test.Hspec.Wai.request method "/headerNC/" [] ""
liftIO $ statusCode (simpleStatus response) `shouldBe` status
it "returns 406 if the Accept header is not supported" $ do
Test.Hspec.Wai.request method "" [(hAccept, "crazy/mime")] ""
`shouldRespondWith` 406
it "responds if the Accept header is supported" $ do
response <- Test.Hspec.Wai.request method ""
[(hAccept, "application/json")] ""
liftIO $ statusCode (simpleStatus response) `shouldBe` status
it "sets the Content-Type header" $ do
response <- Test.Hspec.Wai.request method "" [] ""
liftIO $ simpleHeaders response `shouldContain`
[("Content-Type", "application/json")]
test "GET 200" get200 methodGet 200
test "POST 210" post210 methodPost 210
test "PUT 203" put203 methodPut 203
test "DELETE 280" delete280 methodDelete 280
test "PATCH 214" patch214 methodPatch 214
test "GET 200 with HEAD" get200 methodHead 200
-- }}}
------------------------------------------------------------------------------
-- * captureSpec {{{
------------------------------------------------------------------------------
2014-12-10 16:10:57 +01:00
2015-01-12 15:08:41 +01:00
type CaptureApi = Capture "legs" Integer :> Get '[JSON] Animal
2014-12-10 16:10:57 +01:00
captureApi :: Proxy CaptureApi
captureApi = Proxy
2015-09-12 14:11:24 +02:00
captureServer :: Integer -> ExceptT ServantErr IO Animal
2014-12-10 16:10:57 +01:00
captureServer legs = case legs of
4 -> return jerry
2 -> return tweety
2015-09-12 14:11:24 +02:00
_ -> throwE err404
2014-12-10 16:10:57 +01:00
captureSpec :: Spec
captureSpec = do
describe "Servant.API.Capture" $ do
with (return (serve captureApi captureServer)) $ do
2015-04-06 16:43:36 +02:00
2014-12-10 16:10:57 +01:00
it "can capture parts of the 'pathInfo'" $ do
response <- get "/2"
2015-04-06 16:43:36 +02:00
liftIO $ decode' (simpleBody response) `shouldBe` Just tweety
it "returns 404 if the decoding fails" $ do
get "/notAnInt" `shouldRespondWith` 404
2014-12-10 16:10:57 +01:00
with (return (serve
(Proxy :: Proxy (Capture "captured" String :> Raw))
2015-01-06 17:26:37 +01:00
(\ "captured" request_ respond ->
respond $ responseLBS ok200 [] (cs $ show $ pathInfo request_)))) $ do
2014-12-10 16:10:57 +01:00
it "strips the captured path snippet from pathInfo" $ do
get "/captured/foo" `shouldRespondWith` (fromString (show ["foo" :: String]))
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * queryParamSpec {{{
------------------------------------------------------------------------------
2014-12-10 16:10:57 +01:00
2015-01-12 15:08:41 +01:00
type QueryParamApi = QueryParam "name" String :> Get '[JSON] Person
:<|> "a" :> QueryParams "names" String :> Get '[JSON] Person
:<|> "b" :> QueryFlag "capitalize" :> Get '[JSON] Person
2014-12-10 16:10:57 +01:00
queryParamApi :: Proxy QueryParamApi
queryParamApi = Proxy
qpServer :: Server QueryParamApi
qpServer = queryParamServer :<|> qpNames :<|> qpCapitalize
where qpNames (_:name2:_) = return alice { name = name2 }
qpNames _ = return alice
qpCapitalize False = return alice
qpCapitalize True = return alice { name = map toUpper (name alice) }
2015-01-06 17:26:37 +01:00
queryParamServer (Just name_) = return alice{name = name_}
2014-12-10 16:10:57 +01:00
queryParamServer Nothing = return alice
queryParamSpec :: Spec
queryParamSpec = do
describe "Servant.API.QueryParam" $ do
2016-01-14 23:43:48 +01:00
it "allows retrieving simple GET parameters" $
(flip runSession) (serve queryParamApi qpServer) $ do
2014-12-10 16:10:57 +01:00
let params1 = "?name=bob"
response1 <- Network.Wai.Test.request defaultRequest{
rawQueryString = params1,
queryString = parseQuery params1
}
liftIO $ do
decode' (simpleBody response1) `shouldBe` Just alice{
name = "bob"
}
2016-01-14 23:43:48 +01:00
it "allows retrieving lists in GET parameters" $
(flip runSession) (serve queryParamApi qpServer) $ do
2014-12-10 16:10:57 +01:00
let params2 = "?names[]=bob&names[]=john"
response2 <- Network.Wai.Test.request defaultRequest{
rawQueryString = params2,
queryString = parseQuery params2,
pathInfo = ["a"]
}
liftIO $
decode' (simpleBody response2) `shouldBe` Just alice{
name = "john"
}
2015-01-13 20:40:41 +01:00
2016-01-14 23:43:48 +01:00
it "allows retrieving value-less GET parameters" $
(flip runSession) (serve queryParamApi qpServer) $ do
2014-12-10 16:10:57 +01:00
let params3 = "?capitalize"
response3 <- Network.Wai.Test.request defaultRequest{
rawQueryString = params3,
queryString = parseQuery params3,
pathInfo = ["b"]
}
liftIO $
decode' (simpleBody response3) `shouldBe` Just alice{
name = "ALICE"
}
let params3' = "?capitalize="
response3' <- Network.Wai.Test.request defaultRequest{
rawQueryString = params3',
queryString = parseQuery params3',
pathInfo = ["b"]
}
liftIO $
decode' (simpleBody response3') `shouldBe` Just alice{
name = "ALICE"
}
2014-12-28 23:07:14 +01:00
let params3'' = "?unknown="
response3'' <- Network.Wai.Test.request defaultRequest{
2014-12-28 23:07:14 +01:00
rawQueryString = params3'',
queryString = parseQuery params3'',
pathInfo = ["b"]
}
liftIO $
decode' (simpleBody response3'') `shouldBe` Just alice{
2014-12-28 23:07:14 +01:00
name = "Alice"
}
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * reqBodySpec {{{
------------------------------------------------------------------------------
type ReqBodyApi = ReqBody '[JSON] Person :> Post '[JSON] Person
:<|> "blah" :> ReqBody '[JSON] Person :> Put '[JSON] Integer
2016-01-08 17:43:10 +01:00
reqBodyApi :: Proxy ReqBodyApi
reqBodyApi = Proxy
2016-01-08 17:43:10 +01:00
reqBodySpec :: Spec
reqBodySpec = describe "Servant.API.ReqBody" $ do
2016-01-08 17:43:10 +01:00
let server :: Server ReqBodyApi
server = return :<|> return . age
mkReq method x = Test.Hspec.Wai.request method x
[(hContentType, "application/json;charset=utf-8")]
with (return $ serve reqBodyApi server) $ do
2016-01-08 17:43:10 +01:00
it "passes the argument to the handler" $ do
response <- mkReq methodPost "" (encode alice)
liftIO $ decode' (simpleBody response) `shouldBe` Just alice
2016-01-08 17:43:10 +01:00
it "rejects invalid request bodies with status 400" $ do
mkReq methodPut "/blah" "some invalid body" `shouldRespondWith` 400
2016-01-08 17:43:10 +01:00
it "responds with 415 if the request body media type is unsupported" $ do
Test.Hspec.Wai.request methodPost "/"
[(hContentType, "application/nonsense")] "" `shouldRespondWith` 415
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * headerSpec {{{
------------------------------------------------------------------------------
type HeaderApi a = Header "MyHeader" a :> Delete '[JSON] ()
2015-02-24 14:48:17 +01:00
headerApi :: Proxy (HeaderApi a)
headerApi = Proxy
headerSpec :: Spec
headerSpec = describe "Servant.API.Header" $ do
2015-09-12 14:11:24 +02:00
let expectsInt :: Maybe Int -> ExceptT ServantErr IO ()
2015-02-24 14:48:17 +01:00
expectsInt (Just x) = when (x /= 5) $ error "Expected 5"
expectsInt Nothing = error "Expected an int"
2015-09-12 14:11:24 +02:00
let expectsString :: Maybe String -> ExceptT ServantErr IO ()
2015-02-24 14:48:17 +01:00
expectsString (Just x) = when (x /= "more from you") $ error "Expected more from you"
expectsString Nothing = error "Expected a string"
with (return (serve headerApi expectsInt)) $ do
let delete' x = Test.Hspec.Wai.request methodDelete x [("MyHeader", "5")]
2015-02-24 14:48:17 +01:00
it "passes the header to the handler (Int)" $
delete' "/" "" `shouldRespondWith` 200
2015-02-24 14:48:17 +01:00
with (return (serve headerApi expectsString)) $ do
let delete' x = Test.Hspec.Wai.request methodDelete x [("MyHeader", "more from you")]
2015-02-24 14:48:17 +01:00
it "passes the header to the handler (String)" $
delete' "/" "" `shouldRespondWith` 200
2015-02-24 14:48:17 +01:00
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * rawSpec {{{
------------------------------------------------------------------------------
2014-12-10 16:10:57 +01:00
type RawApi = "foo" :> Raw
2016-01-08 17:43:10 +01:00
2014-12-10 16:10:57 +01:00
rawApi :: Proxy RawApi
rawApi = Proxy
2016-01-08 17:43:10 +01:00
2014-12-10 16:10:57 +01:00
rawApplication :: Show a => (Request -> a) -> Application
2016-01-08 17:43:10 +01:00
rawApplication f request_ respond = respond $ responseLBS ok200 []
(cs $ show $ f request_)
2014-12-10 16:10:57 +01:00
rawSpec :: Spec
rawSpec = do
describe "Servant.API.Raw" $ do
it "runs applications" $ do
(flip runSession) (serve rawApi (rawApplication (const (42 :: Integer)))) $ do
2014-12-10 16:10:57 +01:00
response <- Network.Wai.Test.request defaultRequest{
pathInfo = ["foo"]
}
liftIO $ do
simpleBody response `shouldBe` "42"
it "gets the pathInfo modified" $ do
(flip runSession) (serve rawApi (rawApplication pathInfo)) $ do
2014-12-10 16:10:57 +01:00
response <- Network.Wai.Test.request defaultRequest{
pathInfo = ["foo", "bar"]
}
liftIO $ do
simpleBody response `shouldBe` cs (show ["bar" :: String])
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * alternativeSpec {{{
------------------------------------------------------------------------------
2014-12-10 16:10:57 +01:00
type AlternativeApi =
2015-01-12 15:08:41 +01:00
"foo" :> Get '[JSON] Person
:<|> "bar" :> Get '[JSON] Animal
:<|> "foo" :> Get '[PlainText] T.Text
2015-04-06 16:43:36 +02:00
:<|> "bar" :> Post '[JSON] Animal
:<|> "bar" :> Put '[JSON] Animal
:<|> "bar" :> Delete '[JSON] ()
2014-12-10 16:10:57 +01:00
2016-01-08 17:43:10 +01:00
alternativeApi :: Proxy AlternativeApi
alternativeApi = Proxy
alternativeServer :: Server AlternativeApi
alternativeServer =
2014-12-10 16:10:57 +01:00
return alice
:<|> return jerry
:<|> return "a string"
2015-04-06 16:43:36 +02:00
:<|> return jerry
:<|> return jerry
:<|> return ()
2014-12-10 16:10:57 +01:00
2016-01-08 17:43:10 +01:00
alternativeSpec :: Spec
alternativeSpec = do
2014-12-10 16:10:57 +01:00
describe "Servant.API.Alternative" $ do
with (return $ serve alternativeApi alternativeServer) $ do
2015-04-06 16:43:36 +02:00
2014-12-10 16:10:57 +01:00
it "unions endpoints" $ do
response <- get "/foo"
liftIO $ do
decode' (simpleBody response) `shouldBe`
Just alice
2015-01-06 17:26:37 +01:00
response_ <- get "/bar"
2014-12-10 16:10:57 +01:00
liftIO $ do
2015-01-06 17:26:37 +01:00
decode' (simpleBody response_) `shouldBe`
2014-12-10 16:10:57 +01:00
Just jerry
2015-04-06 16:43:36 +02:00
it "checks all endpoints before returning 415" $ do
get "/foo" `shouldRespondWith` 200
2015-04-06 16:43:36 +02:00
it "returns 404 if the path does not exist" $ do
get "/nonexistent" `shouldRespondWith` 404
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * responseHeaderSpec {{{
------------------------------------------------------------------------------
type ResponseHeadersApi =
Get '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
:<|> Post '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
:<|> Put '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
:<|> Patch '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
responseHeadersServer :: Server ResponseHeadersApi
responseHeadersServer = let h = return $ addHeader 5 $ addHeader "kilroy" "hi"
in h :<|> h :<|> h :<|> h
responseHeadersSpec :: Spec
responseHeadersSpec = describe "ResponseHeaders" $ do
with (return $ serve (Proxy :: Proxy ResponseHeadersApi) responseHeadersServer) $ do
2016-01-08 17:43:10 +01:00
let methods = [methodGet, methodPost, methodPut, methodPatch]
it "includes the headers in the response" $
2016-01-08 17:43:10 +01:00
forM_ methods $ \method ->
Test.Hspec.Wai.request method "/" [] ""
`shouldRespondWith` "\"hi\""{ matchHeaders = ["H1" <:> "5", "H2" <:> "kilroy"]
2016-01-08 17:43:10 +01:00
, matchStatus = 200
}
it "responds with not found for non-existent endpoints" $
2016-01-08 17:43:10 +01:00
forM_ methods $ \method ->
Test.Hspec.Wai.request method "blahblah" [] ""
`shouldRespondWith` 404
it "returns 406 if the Accept header is not supported" $
2016-01-08 17:43:10 +01:00
forM_ methods $ \method ->
Test.Hspec.Wai.request method "" [(hAccept, "crazy/mime")] ""
`shouldRespondWith` 406
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * routerSpec {{{
------------------------------------------------------------------------------
2015-10-12 19:23:13 +02:00
routerSpec :: Spec
routerSpec = do
describe "Servant.Server.Internal.Router" $ do
let app' :: Application
app' = toApplication $ runRouter router'
router', router :: Router
router' = tweakResponse (twk <$>) router
router = LeafRouter $ \_ cont -> cont (Route $ responseBuilder (Status 201 "") [] "")
2015-10-12 19:23:13 +02:00
twk :: Response -> Response
twk (ResponseBuilder (Status i s) hs b) = ResponseBuilder (Status (i + 1) s) hs b
twk b = b
describe "tweakResponse" . with (return app') $ do
it "calls f on route result" $ do
get "" `shouldRespondWith` 202
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * miscCombinatorSpec {{{
------------------------------------------------------------------------------
type MiscCombinatorsAPI
= "version" :> HttpVersion :> Get '[JSON] String
:<|> "secure" :> IsSecure :> Get '[JSON] String
:<|> "host" :> RemoteHost :> Get '[JSON] String
miscApi :: Proxy MiscCombinatorsAPI
miscApi = Proxy
miscServ :: Server MiscCombinatorsAPI
miscServ = versionHandler
:<|> secureHandler
:<|> hostHandler
where versionHandler = return . show
secureHandler Secure = return "secure"
secureHandler NotSecure = return "not secure"
hostHandler = return . show
2016-01-08 17:43:10 +01:00
miscCombinatorSpec :: Spec
miscCombinatorSpec = with (return $ serve miscApi miscServ) $
describe "Misc. combinators for request inspection" $ do
it "Successfully gets the HTTP version specified in the request" $
go "/version" "\"HTTP/1.0\""
it "Checks that hspec-wai uses HTTP, not HTTPS" $
go "/secure" "\"not secure\""
it "Checks that hspec-wai issues request from 0.0.0.0" $
go "/host" "\"0.0.0.0:0\""
where go path res = Test.Hspec.Wai.get path `shouldRespondWith` res
2016-01-08 17:43:10 +01:00
-- }}}
------------------------------------------------------------------------------
-- * Test data types {{{
------------------------------------------------------------------------------
data Person = Person {
name :: String,
age :: Integer
}
deriving (Eq, Show, Generic)
instance ToJSON Person
instance FromJSON Person
alice :: Person
alice = Person "Alice" 42
data Animal = Animal {
species :: String,
numberOfLegs :: Integer
}
deriving (Eq, Show, Generic)
instance ToJSON Animal
instance FromJSON Animal
jerry :: Animal
jerry = Animal "Mouse" 4
tweety :: Animal
tweety = Animal "Bird" 2
-- }}}