{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_GHC -O0 -fmax-simplifier-iterations=0 #-}
module Lib.Applicative.Test where

import Test.Tasty

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

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

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

tests :: TestTree
tests = testGroup "Applicative"
 [ "Just (xor True) <*> Just True" ==> Right
	 ( ty @Maybe :$ ty @Bool
	 , Just False
	 , "(\\x0 -> Just ((\\x1 -> (\\x2 -> x1 `xor` x2)) True) <*> x0) (Just True)" )
 , "Just (xor True) <*> Nothing @Bool" ==> Right
	 ( ty @Maybe :$ ty @Bool
	 , Nothing
	 , "(\\x0 -> Just ((\\x1 -> (\\x2 -> x1 `xor` x2)) True) <*> x0) Nothing" )
 , "xor <$> Just True <*> Just False" ==> Right
	 ( ty @Maybe :$ ty @Bool
	 , Just True
	 , "(\\x0 -> fmap (\\x1 -> (\\x2 -> x1 `xor` x2)) (Just True) <*> x0) (Just False)" )
 , "Just False <* Just True" ==> Right
	 ( ty @Maybe :$ ty @Bool
	 , Just False
	 , "Just False <* Just True" )
 , "Just False *> Just True" ==> Right
	 ( ty @Maybe :$ ty @Bool
	 , Just True
	 , "Just False *> Just True" )
 ]