{-# LANGUAGE OverloadedStrings #-} module GraknSpec ( spec ) where import Data.Function ((&)) import qualified Example import Grakn import Test.Hspec spec :: Spec spec = do it "a simple query string representation" $ match [x `isa` person] & get [] ~= "match $x isa person; get;" it "a relation query string representation" $ match [rel [x, y]] & get [] ~= "match ($x, $y); get;" it "a relation query string representation with types" $ match [rel [husband .: x, wife .: y] -: marriage] & get [] ~= "match (husband: $x, wife: $y) isa marriage; get;" it "a resource query string representation" $ match [x `hasText` firstName $ "Bob"] & get [] ~= "match $x has first-name \"Bob\"; get;" it "multiple patterns" $ match [x -: person, y -: firstName] & get [] ~= "match $x isa person; $y isa first-name; get;" it "get query with type" $ match [x -: y] & get [x, y] ~= "match $x isa $y; get $x, $y;" it "mix role types" $ match [rel [husband .: x, rp y]] & get [] ~= "match (husband: $x, $y); get;" it "limit" $ match [x -: person] & limit 10 & get [] ~= "match $x isa person; limit 10; get;" it "type of type" $ match [person -: x] & get [] ~= "match person isa $x; get;" it "reify a relation" $ match [x <: [y, z]] & get [] ~= "match $x ($y, $z); get;" it "match just a variable" $ match [x] & get [] ~= "match $x; get;" it "example query output" $ Example.query ~= "match $x isa person; (husband: $x, wife: $y) isa marriage; get $y;" x :: Var x = var "x" y :: Var y = var "y" z :: Var z = var "z" person :: Label person = label "person" firstName :: Label firstName = label "first-name" marriage :: Label marriage = label "marriage" husband :: Label husband = label "husband" wife :: Label wife = label "wife" infixr 0 ~= (~=) :: GetQuery -> String -> Expectation (~=) = shouldBe . show