{-# LANGUAGE OverloadedStrings #-} module Grakn.ClientSpec ( spec ) where import Data.Aeson (decode) import Grakn (Value (ValueNumber), label) import Grakn.Client import qualified Servant.Client as S import Test.Hspec import Test.QuickCheck (Arbitrary, arbitrary, elements, property) spec :: Spec spec = do it "The client's keyspace is set correctly" $ property $ \(BaseUrl u) k -> let client = Client {url = u, keyspace = k} in keyspace client `shouldBe` k it "The client's URI is set correctly" $ property $ \(BaseUrl u) k -> let client = Client {url = u, keyspace = k} in url client `shouldBe` u it "type can be parsed from JSON" $ do let person = Just (label "person") let json = "{\"id\": \"V123\", \"label\": \"person\"}" let concept = Concept {cid = "V123", clabel = person, ctype = Nothing, value = Nothing} decode json `shouldBe` Just concept it "instance can be parsed from JSON" $ do let number = Just (label "number") let val = Just (ValueNumber 3) let json = "{\"id\": \"V123\", \"type\": {\"label\": \"number\"}, \"value\": 3}" let concept = Concept {cid = "V123", clabel = Nothing, ctype = number, value = val} decode json `shouldBe` Just concept newtype BaseUrl = BaseUrl S.BaseUrl deriving (Show) instance Arbitrary BaseUrl where arbitrary = do let scheme = elements [S.Http, S.Https] BaseUrl <$> (S.BaseUrl <$> scheme <*> arbitrary <*> arbitrary <*> arbitrary)