Skip to content

Commit

Permalink
[test] add more tests
Browse files Browse the repository at this point in the history
  • Loading branch information
mauke committed Oct 23, 2024
1 parent 198392a commit a8d1898
Showing 1 changed file with 60 additions and 1 deletion.
61 changes: 60 additions & 1 deletion t/basics.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveGeneric #-}

import Data.Default
import Data.Int
Expand All @@ -11,6 +13,16 @@ import qualified Data.Set as S
import qualified Data.IntMap as IM
import qualified Data.IntSet as IS
import Data.Tree (Tree(..))
import Data.Functor.Identity
import Control.Applicative
import Data.Proxy
import Data.Tuple

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.0 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.0 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.10 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.10 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.8 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.8 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.6 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.6 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.4 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.4 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.2 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.2 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.0 on ubuntu-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.0 on windows-latest

The import of ‘Data.Tuple’ is redundant

Check warning on line 19 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 7.10 on windows-latest

The import of ‘Data.Tuple’ is redundant
import GHC.Generics
import Foreign.C.Types
import Foreign.Ptr
#if MIN_VERSION_base(4, 18, 0)
import Foreign.C.ConstPtr
#endif

import Control.Monad (when)

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.4 on ubuntu-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.4 on windows-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.2 on ubuntu-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.2 on windows-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.0 on ubuntu-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 9.0 on windows-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.10 on ubuntu-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.10 on windows-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.8 on ubuntu-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 8.8 on windows-latest

The import of ‘Control.Monad’ is redundant

Check warning on line 27 in t/basics.hs

View workflow job for this annotation

GitHub Actions / Test w/ ghc 7.10 on windows-latest

The import of ‘Control.Monad’ is redundant
import Control.Monad.Reader
Expand Down Expand Up @@ -54,9 +66,17 @@ is x y = ok (x == y) (show x ++ " == " ++ show y)
-- diag s = liftIO $ do
-- putStrLn $ "# " ++ s

data T0 a b
= C0 a a
| C1
| C2 b
deriving (Eq, Show, Generic)

instance (Default a) => Default (T0 a b)

main :: IO ()
main = runTest $ do
planTests 35
planTests 66
is def ()
is def (Nothing :: Maybe (Int, Ordering, [Float]))
is def ""
Expand All @@ -73,6 +93,13 @@ main = runTest $ do
is def (First Nothing :: First ())
is def (Sum (0 :: Integer))
is def (Product (1 :: Rational))
is def (Identity ())
is def (Const 0 :: Const Int Char)
is def (Proxy :: Proxy Char)
#if MIN_VERSION_base(4, 16, 0)
is def (pure () :: Solo ())
#endif
is def False
is def (0 :: Int)
is def (0 :: Integer)
is def (0 :: Float)
Expand All @@ -88,7 +115,39 @@ main = runTest $ do
is def (0 :: Word16)
is def (0 :: Word32)
is def (0 :: Word64)
is def (0 :: CShort)
is def (0 :: CUShort)
is def (0 :: CInt)
is def (0 :: CUInt)
is def (0 :: CLong)
is def (0 :: CULong)
is def (0 :: CLLong)
is def (0 :: CULLong)
is def (0 :: CPtrdiff)
is def (0 :: CSize)
is def (0 :: CSigAtomic)
is def (0 :: CIntPtr)
is def (0 :: CUIntPtr)
is def (0 :: CIntMax)
is def (0 :: CUIntMax)
is def (0 :: CClock)
is def (0 :: CTime)
is def (0 :: CUSeconds)
is def (0 :: CSUSeconds)
is def (0 :: CFloat)
is def (0 :: CDouble)
is def (0 :: IntPtr)
is def (0 :: WordPtr)
#if MIN_VERSION_base(4, 10, 0)
is def (0 :: CBool)
#endif
is def nullPtr
is def nullFunPtr
#if MIN_VERSION_base(4, 18, 0)
is def (ConstPtr nullPtr)
#endif
is def ((def, def) :: ((), Maybe ((), ())))
is def ((def, def, def) :: ((), Maybe ((), ()), [Ordering]))
is def ((def, def, def, def) :: ((), Maybe ((), ()), [Ordering], Float))
is def ((def, def, def, def, def, def, def) :: ((), (), (), (), (), (), ()))
is def (C0 0 0 :: T0 Int Char)

0 comments on commit a8d1898

Please sign in to comment.