Bump versions.
[haskell/symantic.git] / symantic-lib / Language / Symantic / Lib / Num / Test.hs
index 21cfebebe483c5293c620a55bf15abd6b761a2f4..0a1d1e8828def610f7575238cd23f112226d1540 100644 (file)
@@ -1,5 +1,4 @@
 {-# LANGUAGE UndecidableInstances #-}
-{-# LANGUAGE StandaloneDeriving #-}
 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 module Lib.Num.Test where
@@ -25,7 +24,7 @@ type SS =
  , Proxy Traversable
  , Proxy []
  ]
-(==>) = test_readTerm @() @SS
+(==>) = readTe @() @SS
 
 tests :: TestTree
 tests = testGroup "Num"
@@ -36,6 +35,9 @@ tests = testGroup "Num"
  , "-1 + -2"                   ==> Right (tyInteger,  -3, "negate 1 + negate 2")
  , "-(1 + -2)"                 ==> Right (tyInteger,   1, "negate (1 + negate 2)")
  , "(+) 1 2"                   ==> Right (tyInteger,   3, "1 + 2")
+ , "1+2"                       ==> Right (tyInteger,   3, "1 + 2")
+ , "1 +2"                      ==> Right (tyInteger,   3, "1 + 2")
+ , "1+ 2"                      ==> Right (tyInteger,   3, "1 + 2")
  , "1 + 2"                     ==> Right (tyInteger,   3, "1 + 2")
  , "1 + 2 - 3"                 ==> Right (tyInteger,   0, "1 + 2 - 3")
  , "1 + 2 * 3"                 ==> Right (tyInteger,   7, "1 + 2 * 3")
@@ -59,7 +61,7 @@ tests = testGroup "Num"
  , "(+) (negate`2) 44"         ==> Right (tyInteger,  42, "negate 2 + 44")
  , "abs negate`42"             ==> Right (tyInteger,  42, "abs (negate 42)")
  , "(+) 40 2"                  ==> Right (tyInteger,  42, "40 + 2")
- , "(+) 40 -2"                 ==> Right (tyInteger,  38, "40 + negate 2")
+ , "(+) 40 $ -2"               ==> Right (tyInteger,  38, "(($) (\\x0 -> 40 + x0)) (negate 2)")
  , "negate 42 + 42`negate"     ==> Right (tyInteger, -84, "negate 42 + negate 42")
  , "(+) (negate 42) 42`negate" ==> Right (tyInteger, -84, "negate 42 + negate 42")
  , "(+) negate`42 42`negate"   ==> Right (tyInteger, -84, "negate 42 + negate 42")
@@ -67,7 +69,12 @@ tests = testGroup "Num"
  , "abs`42`negate"             ==> Right (tyInteger,  42, "abs (negate 42)")
  , "negate`42`abs"             ==> Right (tyInteger,  42, "abs (negate 42)")
  , testGroup "Error_Term"
-        [ "(+) 40 - 2" ==> Left (tyInteger,
+   [ "(+) 40 -2"  ==> Left (tyInteger,
+               Right $ Error_Term_Beta $ Error_Beta_Unify $
+               Error_Unify_Const_mismatch
+                (TypeVT $ tyFun @_ @'[])
+                (TypeVT $ tyInteger @_ @'[]))
+        , "(+) 40 - 2" ==> Left (tyInteger,
                Right $ Error_Term_Beta $ Error_Beta_Unify $
                Error_Unify_Const_mismatch
                 (TypeVT $ tyFun @_ @'[])
@@ -77,18 +84,20 @@ tests = testGroup "Num"
 
 -- | A newtype to test prefix and postfix.
 newtype Num2 a = Num2 a
-type instance Sym (Proxy Num2) = Sym_Num2
+type instance Sym Num2 = Sym_Num2
 class Sym_Num2 (term:: * -> *) where
 
 instance Sym_Num2 Eval where
 instance Sym_Num2 View where
 instance Sym_Num2 (Dup r1 r2) where
 instance Sym_Num2 term => Sym_Num2 (BetaT term) where
+instance NameTyOf Num2 where
+       nameTyOf _c = ["Num2"] `Mod` "Num2"
 instance FixityOf Num2
 instance ClassInstancesFor Num2
 instance TypeInstancesFor Num2
 instance Gram_Term_AtomsFor src ss g Num2
-instance (Source src, Inj_Sym ss Num) => ModuleFor src ss Num2 where
+instance (Source src, SymInj ss Num) => ModuleFor src ss Num2 where
        moduleFor = ["Num2"] `moduleWhere`
         [ "abs"    `withPrefix`   9 := teNum_abs
         , "negate" `withPrefix`  10 := teNum_negate