
sheaf pushed to branch wip/outputable-natural at Glasgow Haskell Compiler / GHC Commits: b56a732d by sheaf at 2025-09-10T20:58:35+02:00 Add 'Outputable Natural' instance This commit adds an Outputable instance for the Natural natural-number type, as well as a "natural :: Natural -> SDoc" function that mirrors the existing "integer" function. - - - - - 1 changed file: - compiler/GHC/Utils/Outputable.hs Changes: ===================================== compiler/GHC/Utils/Outputable.hs ===================================== @@ -39,7 +39,7 @@ module GHC.Utils.Outputable ( spaceIfSingleQuote, isEmpty, nest, ptext, - int, intWithCommas, integer, word64, word, float, double, rational, doublePrec, + int, intWithCommas, integer, natural, word64, word, float, double, rational, doublePrec, parens, cparen, brackets, braces, quotes, quote, quoteIfPunsEnabled, doubleQuotes, angleBrackets, semi, comma, colon, dcolon, space, equals, dot, vbar, @@ -150,6 +150,7 @@ import System.IO ( Handle ) import System.FilePath import Text.Printf import Numeric (showFFloat) +import Numeric.Natural (Natural) import Data.Graph (SCC(..)) import Data.List (intersperse) import Data.List.NonEmpty (NonEmpty (..)) @@ -684,6 +685,7 @@ docToSDoc d = SDoc (\_ -> d) ptext :: PtrString -> SDoc int :: IsLine doc => Int -> doc +natural :: IsLine doc => Natural -> doc integer :: IsLine doc => Integer -> doc word :: Integer -> SDoc word64 :: IsLine doc => Word64 -> doc @@ -695,6 +697,8 @@ rational :: Rational -> SDoc ptext s = docToSDoc $ Pretty.ptext s {-# INLINE CONLIKE int #-} int n = text $ show n +{-# INLINE CONLIKE natural #-} +natural n = text $ show n {-# INLINE CONLIKE integer #-} integer n = text $ show n {-# INLINE CONLIKE float #-} @@ -947,6 +951,9 @@ instance Outputable Int64 where instance Outputable Int where ppr n = int n +instance Outputable Natural where + ppr n = natural n + instance Outputable Integer where ppr n = integer n View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b56a732d6d15e62c8572af26313e1b44... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b56a732d6d15e62c8572af26313e1b44... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
sheaf (@sheaf)