Skip to content
Snippets Groups Projects
Commit fefd4e31 authored by Matthew Pickering's avatar Matthew Pickering Committed by Marge Bot
Browse files

testsuite: Remove library dependenices from T21119

These dependencies would affect the demand signature depending on
various rules and so on.

Fixes #21271
parent 99623358
No related branches found
No related tags found
No related merge requests found
......@@ -3,12 +3,31 @@
-- {-# LANGUAGE PatternSynonyms #-}
-- {-# LANGUAGE BangPatterns #-}
-- {-# LANGUAGE MagicHash, UnboxedTuples #-}
module T21119 where
{-# LANGUAGE MagicHash #-}
module T21119 ( get, getIO, indexError, throwIndexError ) where
import Control.Exception
import Control.Exception (Exception(..))
import GHC.IO hiding (throwIO)
import GHC.Exts
indexError :: Show a => (a, a) -> a -> String -> b
indexError rng i s = error (show rng ++ show i ++ show s)
throwIO :: Exception e => e -> IO a
throwIO e = IO (raiseIO# (toException e))
myconcat :: [[a]] -> [a]
myconcat = concat
{-# NOINLINE myconcat #-}
class MyShow a where
myshow :: a -> String
instance MyShow Int where
myshow !_ = "0"
instance MyShow (a, b) where
myshow !_ = "()"
indexError :: MyShow a => (a, a) -> a -> String -> b
indexError rng i s = errorWithoutStackTrace (myconcat [myshow rng, myshow i, s])
get :: (Int, Int) -> Int -> [a] -> a
get p@(l,u) i xs
......@@ -17,8 +36,8 @@ get p@(l,u) i xs
-- Now the same with precise exceptions:
throwIndexError :: Show a => (a, a) -> a -> String -> IO b
throwIndexError rng i s = throwIO (userError (show rng ++ show i ++ show s))
throwIndexError :: MyShow a => (a, a) -> a -> String -> IO b
throwIndexError rng i s = throwIO (userError (myconcat [myshow rng, myshow i, s]))
-- It's important that we don't unbox 'u' here.
-- We may or may not unbox 'p' and 'l'.
......
==================== Strictness signatures ====================
T21119.$fMyShow(,): <1!A>
T21119.$fMyShowInt: <1!A>
T21119.$tc'C:MyShow:
T21119.$tcMyShow:
T21119.$trModule:
T21119.get: <1!P(S!P(L),S!P(L))><1!P(L)><1L>
T21119.getIO: <1P(SL,L)><1L><ML><L>
T21119.indexError: <S!P(SCS(C1(L)),1C1(L),B)><1!S><S!S><1!S>b
T21119.throwIndexError: <LP(LCL(C1(L)),MCM(L),A)><ML><L><ML><L>x
T21119.get: <1!P(1!P(L),1!P(L))><1!P(L)><1L>
T21119.getIO: <1P(1L,ML)><1L><ML><L>
T21119.indexError: <1C1(L)><1!B><S!S><S!S>b
T21119.throwIndexError: <MCM(L)><MA><L><L><L>x
==================== Cpr signatures ====================
T21119.$fMyShow(,):
T21119.$fMyShowInt:
T21119.$tc'C:MyShow:
T21119.$tcMyShow:
T21119.$trModule:
T21119.get:
T21119.getIO: 1
......@@ -18,10 +26,14 @@ T21119.throwIndexError: b
==================== Strictness signatures ====================
T21119.$fMyShow(,): <1!A>
T21119.$fMyShowInt: <1!A>
T21119.$tc'C:MyShow:
T21119.$tcMyShow:
T21119.$trModule:
T21119.get: <1!P(1!P(L),1!P(L))><1!P(L)><1L>
T21119.getIO: <1P(SL,L)><1L><ML><L>
T21119.indexError: <1P(SCS(C1(L)),1C1(L),B)><1!S><S!S><1!S>b
T21119.throwIndexError: <LP(LCL(C1(L)),MCM(L),A)><ML><L><ML><L>x
T21119.getIO: <1P(1L,ML)><1L><ML><L>
T21119.indexError: <1C1(L)><1!B><S!S><S!S>b
T21119.throwIndexError: <MCM(L)><MA><L><L><L>x
......@@ -31,4 +31,5 @@ test('T18907', normal, compile, [''])
test('T13331', normal, compile, [''])
test('T20746', normal, compile, [''])
test('T20746b', normal, compile, [''])
test('T21119', normal, compile, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment