{-# LANGUAGE OverloadedRecordDot #-} {-# OPTIONS_GHC -fprint-potential-instances -fprint-typechecker-elaboration #-} module Spec.HTree.Labeled (spec) where import Data.HTree.Labeled (Proxy (Proxy), SearchStrategy (BFS, DFS), getElem) import Spec.HTree.Fixtures (exBfsDfs, exL, unI) import Test.Hspec (Spec, describe, it) spec :: Spec spec = describe "elements in the example get returned as expected" do it "has top node 5" do (5 :: Int) == unI exL.top it "has a node 42" do (42 :: Int) == unI exL.a it "has bla node 9" do (9 :: Int) == unI exL.bla it "has d node False" do not $ unI exL.d it "has e node \"test\"" do ("test" :: String) == unI exL.e it "finds int via BFS" do unI (getElem @BFS @"foo" @Int Proxy exBfsDfs) == 67 it "finds int via DFS" do unI (getElem @DFS @"foo" @Int Proxy exBfsDfs) == 69