1
1
mirror of https://github.com/github/semantic.git synced 2024-12-24 23:42:31 +03:00

Clean up redundant imports and use Text, not String.

This commit is contained in:
Rob Rix 2016-06-27 13:16:56 -04:00
parent 10b5bdaab4
commit 346bec0d0b

View File

@ -1,14 +1,7 @@
{-# LANGUAGE DataKinds #-}
module TermSpec where
import Category
import Data.String
import Data.Text.Arbitrary ()
import Data.Record
import Data.Record.Arbitrary ()
import Diff
import Diff.Arbitrary
import Interpreter
import Prologue
import Term.Arbitrary
import Test.Hspec
@ -19,8 +12,8 @@ spec :: Spec
spec = parallel $ do
describe "Term" $ do
prop "equality is reflexive" $
\ a -> toTerm a == toTerm (a :: ArbitraryTerm String ())
\ a -> toTerm a == toTerm (a :: ArbitraryTerm Text ())
describe "ArbitraryTerm" $ do
prop "generates terms of a specific size" $ forAll ((arbitrary >>= \ n -> (,) n <$> termOfSize n) `suchThat` ((> 0) . fst)) $
\ (n, term) -> arbitraryTermSize (term :: ArbitraryTerm String ()) `shouldBe` n
prop "generates terms of a specific size" . forAll ((arbitrary >>= \ n -> (,) n <$> termOfSize n) `suchThat` ((> 0) . fst)) $
\ (n, term) -> arbitraryTermSize (term :: ArbitraryTerm Text ()) `shouldBe` n