{- Copyright (C) 2010 Andrejs Sisojevs All rights reserved. For license and copyright information, see the file COPYRIGHT -} -------------------------------------------------------------------------- -------------------------------------------------------------------------- import Data.EmptySet import Data.NeverEmptyList import Data.Cardinality import Data.Map import Control.Monad import Control.Monad.Identity instance Eq a => Eq (Identity a) where a == b = runIdentity a == runIdentity b instance Show a => Show (Identity a) where show i_a = "Identity " ++ show (runIdentity i_a) test_set :: [(Int, Bool)] test_set = zip [1..] [ ((sContTransT []) :: Maybe (Maybe Int)) == Just Nothing , ((sContTrans ()) :: Maybe (Maybe Int)) == Just Nothing , ((sContTransT [1]) :: (Maybe (Maybe Int))) == Just (Just 1) , ((sContTransT [1, 2]) :: (Maybe (Maybe Int))) == Nothing , ((sContTransT $ Just "Hello") :: (Maybe (Identity String))) == Just (Identity "Hello") , ((sContTransT ["Hello"]) :: Maybe (Identity String)) == Just (Identity "Hello") , ((sContTransT (EmptySet :: EmptySet String)) :: (Maybe [String])) == Just [] , ((sContTransT "Hello") :: Maybe (EmptySet Char)) == Nothing , ((sContTransT ("key", "elem")) :: Maybe (Map String String)) == Just (singleton "key" "elem") , ((sContTrans [("key1", "elem1"), ("key2", "elem2")]) :: Maybe (Map String String)) == Just (fromList [("key1", "elem1"), ("key2", "elem2")]) , ((sContTrans (EmptySet :: EmptySet (String, String))) :: Maybe (Map String String)) == Just empty , ((sContTrans []) :: Maybe ()) == Just () , ((sContTrans (NEL 'H' "i!")) :: Maybe String) == Just "Hi!" -- Data.NeverEmptyList , ((sContTrans ()) :: Maybe String) == Just "" , ((sContTrans "") :: Maybe (Identity Char)) == Nothing , ((sContTrans "Hi!") :: Maybe ()) == Nothing ] main = do putStrLn ("INDEX) IS_VALID | TEST_CASE\n------------------------------") flip mapM_ test_set (\ (idx, _case) -> putStrLn (show idx ++ ") " ++ show _case))