{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module Lib.Applicative.Test where

import Test.Tasty

import Data.Proxy (Proxy(..))
import Prelude hiding ((&&), not, (||))

import Language.Symantic.Lib
import Compiling.Test
import Lib.Bool.Test ()

type SS =
 [ Proxy (->)
 , Proxy Integer
 , Proxy Bool
 , Proxy Maybe
 , Proxy Functor
 , Proxy Applicative
 ]
(==>) = test_readTerm @() @SS

tests :: TestTree
tests = testGroup "Applicative"
 [ "Just (xor True) <*> Just True"    ==> Right (tyMaybe tyBool, Just False, "Just (\\x0 -> True `xor` x0) <*> Just True")
 , "Just (xor True) <*> Nothing"      ==> Right (tyMaybe tyBool, Nothing   , "Just (\\x0 -> True `xor` x0) <*> Nothing")
 , "xor <$> Just True <*> Just False" ==> Right (tyMaybe tyBool, Just True , "(\\x0 -> (\\x1 -> x0 `xor` x1)) <$> Just True <*> Just False")
 , "Just False <* Just True"          ==> Right (tyMaybe tyBool, Just False, "Just False <* Just True")
 , "Just False *> Just True"          ==> Right (tyMaybe tyBool, Just True , "Just False *> Just True")
 ]