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

import Test.Tasty

import qualified Data.MonoTraversable as MT
import Data.Proxy (Proxy(..))
import Prelude hiding (zipWith)

import Language.Symantic.Typing
import Compiling.Term.Test

type Ifaces =
 [ Proxy (->)
 , Proxy []
 , Proxy Integer
 , Proxy Bool
 , Proxy Char
 , Proxy MT.MonoFunctor
 , Proxy Maybe
 ]
(==>) = test_compile @Ifaces

tests :: TestTree
tests = testGroup "MonoFunctor"
 [ "omap not (Just True)" ==> Right
	 ( ty @Maybe :$ ty @Bool
	 , Just False
	 , "omap (\\x0 -> not x0) (Just True)" )
 , "omap Char.toUpper ['a', 'b', 'c']" ==> Right
	 ( ty @[] :$ ty @Char
	 , "ABC"
	 , "omap (\\x0 -> Char.toUpper x0) ('a' : 'b' : 'c' : [])" )
 ]