[Git][ghc/ghc][wip/T25888] Test the Interaction of -XExtendedDefaultRules and -XNamedDefaults

Patrick pushed to branch wip/T25888 at Glasgow Haskell Compiler / GHC Commits: b24033cc by Patrick at 2025-04-18T14:47:51+08:00 Test the Interaction of -XExtendedDefaultRules and -XNamedDefaults Add Testcases T25888v1-2 Fix #25888 - - - - - 5 changed files: - + testsuite/tests/default/T25888v1.hs - + testsuite/tests/default/T25888v1.stdout - + testsuite/tests/default/T25888v2.hs - + testsuite/tests/default/T25888v2.stdout - testsuite/tests/default/all.T Changes: ===================================== testsuite/tests/default/T25888v1.hs ===================================== @@ -0,0 +1,52 @@ +{-# LANGUAGE ExtendedDefaultRules #-} +{-# LANGUAGE NamedDefaults #-} +{-# LANGUAGE RequiredTypeArguments #-} + +module Main where +import Data.Foldable (Foldable(..)) +import Data.Functor.Identity (Identity(..)) + +default Foldable (Maybe) +default Num (Double) +default Show () +-- This is ensured we cleanup defaults for Show, +-- we do not want Show to effect the defaulting of `Num, Foldable`. +-- since we are using Show to print out the result. + +class (Foldable t) => Build t where + polyFold :: forall a -> t a + +instance Build Maybe where + polyFold x = Nothing + +instance Build [] where + polyFold x = [] + + +-- This test demonstrates the functionality of ExtendedDefaultRules and NamedDefaults. +-- +-- By default, ExtendedDefaultRules implicitly provides: +-- default Foldable ([]) +-- default Num (Integer, Double) +-- +-- However, we override these with our explicit declarations: +-- default Foldable (Maybe) +-- default Num (Double) +-- +-- This test verifies that our overrides work correctly: +-- 1. For an unresolved type variable 't' with a 'Foldable t' constraint, +-- 't' defaults to 'Maybe' (not '[]') +-- 2. For an unresolved type variable 'a' with a 'Num a' constraint, +-- 'a' defaults to 'Double' (not 'Integer') +-- +-- Expected outcomes: +-- * 'polyFold Int' evaluates to 'Nothing' (not '[]') +-- * '1' is a 'Double' (1.0) (not an 'Integer') +-- +-- See also T25888v2.hs for a companion test without overriding the defaults + +main :: IO () +main = do + print $ polyFold Int + print $ 1 + ===================================== testsuite/tests/default/T25888v1.stdout ===================================== @@ -0,0 +1,2 @@ +Nothing +1.0 ===================================== testsuite/tests/default/T25888v2.hs ===================================== @@ -0,0 +1,40 @@ +{-# LANGUAGE ExtendedDefaultRules #-} +{-# LANGUAGE NamedDefaults #-} +{-# LANGUAGE RequiredTypeArguments #-} + +module Main where +import Data.Foldable (Foldable(..)) +import Data.Functor.Identity (Identity(..)) + +default Show () +-- This is ensured we cleanup defaults for Show, +-- we do not want Show to effect the defaulting of `Num, Foldable`. +-- since we are using Show to print out the result. + +class (Foldable t) => Build t where + polyFold :: forall a -> t a + +instance Build Maybe where + polyFold x = Nothing + +instance Build [] where + polyFold x = [] + +-- With ExtendedDefaultRules enabled, we implicitly have the following defaults: +-- default Foldable ([]), Num (Integer, Double) +-- These defaults are not overridden in this module. + +-- According to the defaulting rules: +-- 1. For an unresolved type variable 't' with constraint 'Foldable t', 't' defaults to [] +-- 2. For an unresolved type variable 'a' with constraint 'Num a', 'a' defaults to Integer + +-- Therefore: +-- * polyFold Int should evaluate to [] (empty list) +-- * The literal 1 should be of type Integer + +-- See also T25888v1.hs for the same test with overridden defaults +main :: IO () +main = do + print $ polyFold Int + print $ 1 + ===================================== testsuite/tests/default/T25888v2.stdout ===================================== @@ -0,0 +1,2 @@ +[] +1 ===================================== testsuite/tests/default/all.T ===================================== @@ -42,3 +42,5 @@ test('T25882', normal, compile, ['']) test('T25912', [extra_files(['T25912_helper.hs'])], multimod_compile_and_run, ['T25912', '']) test('T25914', normal, compile, ['']) test('T25934', normal, compile, ['']) +test('T25888v1', normal, compile_and_run, ['']) +test('T25888v2', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b24033cc8613f98c153e7928db43870b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b24033cc8613f98c153e7928db43870b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Patrick (@soulomoon)