Skip to content

Instantly share code, notes, and snippets.

@k-bx
Created February 15, 2015 20:14
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save k-bx/fe7027c919980eb9b7f0 to your computer and use it in GitHub Desktop.
Save k-bx/fe7027c919980eb9b7f0 to your computer and use it in GitHub Desktop.
-- | This script will replace expected stdout files of failed tests
-- with actual (new) ones. This will need some careful review (see
-- turtle_review.hs)
{-# LANGUAGE OverloadedStrings #-}
import qualified Control.Foldl as L
import Data.List ((\\))
import qualified Data.Text as T
import Data.Traversable (forM)
import qualified Filesystem.Path.CurrentOS as FP
import Prelude hiding (FilePath)
import Text.Regex.Applicative
import Turtle
main :: IO ()
main = do
void $ forM (failedTests \\ skipped) $ \testName -> do
echo ("Test name: " <> testName)
out <- readProcOutputNI "make" [(format ("TEST="%s) testName)]
let (expected, actual) = parseFileNames out
echo (format ("Expected file name: "%s) (fpToText expected))
echo (format ("Actual file name: "%s) (fpToText actual))
echo "Replacing files"
exitOnErr (proc "cp" [fpToText ("./tests/" </> actual),
fpToText ("./tests/" </> expected)] empty)
return ()
parseFileNames :: Text -> (FilePath, FilePath)
parseFileNames inp = do
let r1 = few anySym *> "Actual stderr output differs from expected:\n"
*> "--- " *> few anySym <* "\t" <* few anySym
let r2 = "+++ " *> few anySym <* "\t" <* few anySym
let r = (,) <$> r1 <*> r2
case (T.unpack inp) =~ r of
Just (f1,f2) -> (fromString f1, fromString f2)
_ -> error ("Couldn't parse input. Inp: " ++ T.unpack inp)
-- XXX: These ones need to be reviewed separately, since this script failed on them
skipped :: [Text]
skipped = ["layout006", "layout004", "layout003", "layout001", "T7276a", "T9140"]
failedTests :: [Text]
failedTests = T.splitOn " " failedTestsStr
-- utils
fpToText :: FilePath -> Text
fpToText = either id id . FP.toText
-- | NI stands for "no input"
readProcOutputNI :: Text -> [Text] -> IO Text
readProcOutputNI p args = T.unlines <$> fold (inproc p args empty) L.list
-- TODO: implement properly
exitOnErr :: IO a -> IO ()
exitOnErr = void
-- big data
-- Tests that failed after the feature-implementation
failedTestsStr :: Text
failedTestsStr = "SafeFlags07 SafeFlags04 SafeFlags03 SafeFlags18 SafeFlags19 SafeFlags09 SafeFlags08 SafeFlags29 SafeFlags28 SafeFlags17 SafeFlags23 SafeFlags22 SafeFlags25 SafeFlags26 T1372 proffail001 str001 tc056 tc175 tc116 tc078 tc115 T7220a T2494 tc167 T2497 tc182 T7562 T5481 tc126 tc125 T9834 tc243 T4912 tc161 T3696 tc141 tc168 holes3 holes2 T9939 T7903 tc211 T7050 T9497a holes FD1 FD3 FD2 tc254 T2478 HasKey mod36 mod38 mod121 mod1 mod2 mod3 mod4 mod5 mod127 mod7 mod8 mod128 T414 mod45 mod44 mod47 mod46 mod41 mod40 mod43 mod42 mod49 mod48 mod114 mod116 mod110 mod56 mod54 mod55 mod52 mod53 mod50 mod51 mod58 mod59 mod102 mod101 mod180 mod120 mod123 mod63 mod62 mod61 mod60 mod67 mod66 mod125 mod69 mod68 mod124 mod126 mod178 mod9 mod176 mod177 mod174 mod79 mod74 mod76 mod77 mod70 mod71 mod72 mod73 mod165 mod164 mod161 mod160 mod122 mod158 mod150 mod151 mod152 mod153 mod155 mod18 mod19 mod10 mod17 mod14 mod147 mod146 mod145 mod144 mod143 mod142 mod81 mod80 mod87 mod89 mod88 mod27 mod26 mod25 mod24 mod23 mod22 mod21 mod20 mod29 mod132 mod130 mod131 mod136 mod134 mod135 mod138 mod90 mod91 mod97 mod98 cabal07 T7937 T5372 T2310 rnfail052 rnfail053 rnfail050 rnfail051 rnfail056 rnfail057 rnfail054 rnfail055 T7943 T9815 T5533 T9156 T5892a T5892b T7454 T5385 T3265 T8149 T5951 rn_dup T5745 mc14 T5589 T7338a T5513 T2723 T9032 Misplaced rnfail004 rnfail007 rnfail001 rnfail003 rnfail002 rnfail009 rnfail008 T7338 T9437 T9436 T4042 T2490 rnfail016 rnfail017 rnfail015 rnfail012 rnfail013 rnfail010 rnfail011 T8448 rnfail018 rnfail019 T2993 T6060 rnfail029 rnfail028 T6148 rnfail023 rnfail022 rnfail021 T7906 rnfail027 rnfail026 rnfail025 rnfail024 T2901 T9006 T9077 T3792 rnfail039 rnfail034 rnfail035 rnfail046 rnfail030 rnfail031 rnfail032 rnfail033 T7164 T5211 RnStaticPointersFail02 RnStaticPointersFail03 RnStaticPointersFail01 mc13 T9177 rnfail049 rnfail048 T5657 rnfail041 rnfail040 rnfail043 rnfail042 rnfail045 rnfail044 rnfail047 T1595a T5281 retc001 T9230 T9178 T2526 SafeLang12 SafeLang03 SafeLang08 SafeLang16 SafeLang17 SafeLang07 SafeLang01 SafeLang10 SafeLang02 gadtSyntaxFail002 gadt-escape1 rw gadt21 gadt7 gadtSyntaxFail003 T3169 T3163 T3651 gadtSyntaxFail001 T7558 T7293 records-fail1 gadt11 gadt10 gadt13 T7294 CasePrune lazypat T5204 T3953 T3811f T3751 NondecreasingIndentationFail ParserNoBinaryLiterals1 T5425 readFail037 ParserNoLambdaCase ParserNoForallUnicode T8506 T3811e readFail003 readFail038 readFail039 ParserNoBinaryLiterals3 readFail024 readFail033 readFail030 readFail031 readFail036 readFail027 readFail034 readFail035 T3811g readFail011 readFail012 readFail013 readFail014 readFail015 readFail016 readFail017 readFail018 readFail019 T3095 readFailTraditionalRecords1 ParserNoBinaryLiterals2 T3811d ParserNoMultiWayIf readFail006 T7848 NoDoAndIfThenElse readFail023 readFail004 position001 position002 T1344a T3153 readFailTraditionalRecords2 readFailTraditionalRecords3 T3811c T3811 T1344b T1344c readFail042 T8431 readFail047 readFail046 readFail044 readFail043 readFail007 readFail041 readFail040 readFail025 readFail002 readFail001 readFail026 readFail021 readFail020 readFail005 readFail022 T3811b readFail009 readFail008 readFail029 readFail028 ExportCommaComma T984 T3103 mdofail001 mdofail002 mdofail003 mdofail005 sigof04 ds053 ds051 GadtOverlap T3263-2 ds056 T2395 T3263-1 ds022 T4488 ds020 ds058 ds041 ds043 ds002 ds003 T5455 ds019 T5117 overloadedlistsfail01 overloadedlistsfail03 overloadedlistsfail02 overloadedlistsfail05 overloadedlistsfail04 overloadedlistsfail06 haddockE004 layout006 layout004 layout003 layout001 UnsafeWarn06 UnsafeWarn07 UnsafeWarn04 UnsafeWarn05 UnsafeWarn02 UnsafeWarn03 UnsafeWarn01 TrustworthySafe03 TrustworthySafe02 UnsafeInfered08 UnsafeInfered09 UnsafeInfered02 UnsafeInfered03 UnsafeInfered01 UnsafeInfered06 UnsafeInfered05 SafeWarn01 Mixed02 Mixed03 Mixed01 UnsafeInfered19 UnsafeInfered18 UnsafeInfered15 UnsafeInfered14 UnsafeInfered17 UnsafeInfered16 UnsafeInfered11 UnsafeInfered10 UnsafeInfered13 UnsafeInfered12 T8958 Check06 Check05 Check09 Check01 Check08 simpl016 simpl020 T6082-RULE T8537 simpl017 T5359b T4398 T9872b T9872a parsing001 T5837 T9872c ccfail005 ccfail004 ccfail003 ccfail002 ccfail001 capi_value_function T3066 T7243 ccall_value T7506 T5664 ghci.prog009 hs-boot rn050 rn037 T3449 rn039 T7145b T5334 T3823 T5331 T7167 mc10 T1789 rn055 T5867 T1972 T4489 T3371 T9778 rn041 rn040 rn047 rn046 rn049 rn066 rn064 rn063 T4426 T7085 T3262 ImpSafe01 ImpSafeOnly08 ImpSafe03 ImpSafe04 ImpSafeOnly03 ImpSafeOnly07 ImpSafeOnly05 ImpSafeOnly09 T5976 T2713 TH_unresolvedInfix2 T5971 TH_RichKinds2 TH_runIO ClosedFam1TH TH_Promoted1Tuple T7276 T2674 T5358 TH_RichKinds T7484 T9209 TH_Roles1 T8987 TH_fail T7667a TH_dataD1 T8759 T7276a TH_linePragma TH_exn1 TH_TyInstWhere2 TH_exn2 TH_spliceD1 T9084 T5795 T7241 T8759a TH_StaticPointers02 TH_PromotedTuple T3395 TH_repPatSig TH_PromotedList TH_dupdecl T8577 T8932 T7477 T8028 T1476b TH_1tuple T2597b T8412 T3177a Dep06 Dep07 Dep05 Dep10 Dep08 Dep09 BadImport07 BadImport06 BadImport01 BadImport09 BadImport08 T7805 T6054 T7224 T6039 T7524 T7404 T7481 T9144 T8566 T5716a T9106 T7328 T7341 T9222 T9574 T8132 T6129 PolyKinds02 PolyKinds04 PolyKinds06 PolyKinds07 T9200b T7433 T7278 T7438 T6021 T7230 T5716 T8616 T7151 T7594 T7939a SimpleFail1a T7938 Overlap10 T4246 T1897b T8155 DerivUnsatFam NoGood T5439 ClosedFam4 ClosedFam3 TyFamUndec T7786 T9662 Over T2627b T2693 T7354 T7194 T9097 T4099 GADTwrong1 T1900 SimpleFail2a SimpleFail2b SimpleFail5a SimpleFail5b T9896 T3440 T7010 T5515 T7967 T6123 T7354a T9036 T7536 Overlap3 Overlap7 Overlap6 Overlap5 Overlap4 Overlap9 T6088 T9433 T2334A Overlap15 TyFamArity1 Overlap11 TyFamArity2 T2888 T5934 T2157 NotRelaxedExamples T4093b T4093a T7862 T4485 T3330b T3330a T2544 SimpleFail3a T2664 T9357 T8518 T2203a T9580 BadSock T4272 T9160 T9167 T3330c T2677 T7729a T8227 SimpleFail4 SimpleFail7 SimpleFail6 SimpleFail8 T8368a SimpleFail1b SimpleFail11d ExtraTcsUntch SimpleFail11a T3092 SimpleFail11c SimpleFail11b T9171 T4174 NoMatchErr T4179 T8368 T7729 SimpleFail15 SimpleFail14 SimpleFail16 T9371 SimpleFail13 SimpleFail12 T9915 prog006 WarningWildcardInstantiations sigof02dt sigof02dmt annfail11 annfail10 annfail13 annfail08 annfail09 annfail12 annfail04 annfail05 annfail06 annfail07 annfail01 annfail02 annfail03 p3 p1 p6 p4 p9 p10 p11 p12 p13 p14 p16 p17 bug1465 AnnotatedConstraint WildcardInDefaultSignature NamedExtraConstraintsWildcard WildcardInTypeBrackets NamedWildcardsNotEnabled WildcardsInPatternAndExprSig Forall1Bad WildcardInADT2 WildcardInADT3 WildcardInADT1 WildcardInInstanceSig AnnotatedConstraintNotForgotten InstantiatedNamedWildcardsInConstraints ExtraConstraintsWildcardNotEnabled NestedNamedExtraConstraintsWildcard UnnamedConstraintWildcard2 UnnamedConstraintWildcard1 WildcardInTypeSynonymRHS WildcardInGADT2 WildcardInDeriving ExtraConstraintsWildcardNotPresent WildcardInPatSynSig ExtraConstraintsWildcardNotLast WildcardInNewtype NamedWildcardsNotInMonotype WildcardInGADT1 WildcardInInstanceHead TidyClash WildcardInADTContext1 WildcardInTypeFamilyInstanceRHS WildcardInForeignExport WildcardInStandaloneDeriving PartialTypeSignaturesDisabled WildcardInADTContext2 NamedWildcardsEnabled PartialClassMethodSignature WildcardInTypeFamilyInstanceLHS Defaulting1MROff WildcardInTypeSynonymLHS NestedExtraConstraintsWildcard WildcardInForeignImport ScopedNamedWildcardsBad WildcardInDefault WildcardInstantiations rebindable6 T2182ghci ghci034 ghci019 ghci036 ghci031 T5979 T7627b ghci057 T2182ghci2 ghci052 ghci051 ghci038 T5820 T2816 T7894 ghci053 T1914 T8649 ghci050 T8485 T8959 T9878 T6106 ghci022 ghci021 ghci048 ghci044 ghci047 T6007 Defer02 T4127a T9293 T8639 T5564 T3263 T9140 T2452 T5836 T9975a rename.prog003 rename.prog002 bug1677 Simple14 T8889 T3418 PushedInAsGivens T3023 T3208b T9085 Class3 Simple2 WarnMinimalFail3 WarnMinimalFail2 WarnMinimalFail1 WarnMinimal T9161-1 unboxed-wrapper-naked T9161-2 mono unidir as-pattern T9705-1 unboxed-bind T9705-2 local prog012 T8542 T7881 T7895 T8101 T2182 driver063 T8959a T2507 T2464 werror T2499 T8984 T7959 T5686 T4846 T7148a T3101 T3621 T1133A drvfail011 T7148 drvfail013 drvfail012 drvfail015 drvfail016 drvfail-functor2 drvfail-functor1 T2851 T2701 T9071_2 T7800 drvfail-foldable-traversable1 T1496 T5922 T8851 T3833 T5478 T3834 T6147 T2721 T2604 T5498 T4528 T5287 T2394 T9071 T9687 T5863a drvfail002 drvfail003 drvfail001 drvfail007 drvfail004 drvfail005 drvfail009 haddock.Test dynbrk001 break019 break006 break003 print007 print019 T1357 T8773 RolesIArray Roles8 Roles7 Roles6 Roles5 T9204 Roles12 Roles11 Roles10 utf8_010 T2302 utf8_011 utf8_002 utf8_003 utf8_004 utf8_005 utf8_020 utf8_021 utf8_022 arrowfail004 arrowfail001 arrowfail003 arrowfail002 T2111 T5380 package09e package07e package01e package06e package08e T9576 T5147 GenCannotDoRep1_2 GenCannotDoRep1_3 GenCannotDoRep1_0 GenCannotDoRep1_1 GenCannotDoRep1_6 GenCannotDoRep1_7 GenCannotDoRep1_4 T8468 GenCannotDoRep1_8 GenShouldFail0 T5462No1 GenCannotDoRep0_2 GenShouldFail1_0 GenCannotDoRep0_1 GenCannotDoRep0_0 qq001 qq002 qq003 qq004 apirecomp001 T9681 prog013 tcfail185 tcfail184 tcfail187 tcfail186 tcfail181 tcfail180 tcfail183 tcfail182 mc24 tcfail189 T5978 T3966 mc25 T5084 T3102 T7264 FDsFromGivens tcfail214 tcfail178 tcfail179 T7734 tcfail207 tcfail170 tcfail171 tcfail173 tcfail174 tcfail175 tcfail176 tcfail177 tcfail070 tcfail073 tcfail072 tcfail075 T4875 tcfail077 tcfail076 tcfail079 tcfail078 T7175 T9305 T9415 tcfail203 tcfail196 tcfail197 tcfail195 tcfail193 tcfail190 tcfail191 T3468 tcfail201 tcfail198 tcfail199 T6069 T8306 T3613 T9612 T7019a TcNoNullaryTC T8392a T6022 tcfail159 tcfail109 tcfail108 tcfail204 T7453 tcfail104 tcfail107 tcfail106 tcfail101 tcfail100 tcfail103 tcfail102 tcfail062 tcfail063 tcfail217 tcfail061 tcfail211 tcfail067 tcfail213 tcfail065 T7368 tcfail068 tcfail069 tcfail219 tcfail218 T8142 T8603 T5957 T3323 T5300 FailDueToGivenOverlapping T7410 TcNullaryTCFail T3950 fd-loop T9739 T7525 T9497d T8570 T8883 mc21 tcfail215 LongWayOverlapping tcfail202 T3592 tcfail118 tcfail119 tcfail116 tcfail117 tcfail114 tcfail112 tcfail113 tcfail110 tcfail057 tcfail056 tcfail055 tcfail054 tcfail053 tcfail052 tcfail051 tcfail050 tcfail200 TcStaticPointersFail01 T5051 tcfail208 tcfail058 ContextStack2 T1633 tcfail212 T7778 T5691 T7809 AssocTyDef04 T2126 T7696 T7019 T5246 tcfail131 tcfail048 tcfail049 tcfail121 T7645 tcfail127 tcfail125 tcfail169 tcfail040 tcfail041 tcfail042 tcfail043 tcfail044 mc23 tcfail046 tcfail047 T8044 tcfail216 tcfail221 TcCoercibleFail3 T2538 T9318 T2534 T8428 T5689 T2714 T2247 T4921 TcCoercibleFail tcfail220 T5684 TcStaticPointersFail02 T2846b tcfail139 T2307 tcfail222 tcfail209 T6001 TcMultiWayIfFail tcfail134 tcfail135 tcfail136 tcfail137 tcfail130 tcfail038 tcfail132 tcfail133 tcfail035 tcfail034 tcfail037 tcfail036 tcfail031 tcfail030 tcfail033 tcfail032 T2994 tcfail206 T7856 T9634 T7609 T7748a tcfail123 T5570 T1897a tcfail122 T7210 T7869 T5853 T7368a T3155 T2688 tcfail210 T9033 T2806 T9196 tcfail203a T8806 T8450 T8262 tcfail028 tcfail029 tcfail027 T7989 tcfail023 tcfail020 tcfail021 T2414 tcfail140 tcfail143 tcfail142 AssocTyDef09 AssocTyDef08 tcfail147 tcfail146 AssocTyDef05 tcfail148 AssocTyDef07 AssocTyDef06 AssocTyDef01 tcfail129 AssocTyDef03 AssocTyDef02 T9323 T9201 tcfail128 T7697 T3540 T7857 mc22 T6078 T9109 T7851 T2354 T9605 mc20 T8514 tcfail162 tcfail013 tcfail012 tcfail011 tcfail010 tcfail017 tcfail016 tcfail015 tcfail014 tcfail019 tcfail018 T8912 TcStaticPointersFail03 tcfail152 tcfail153 tcfail099 tcfail098 tcfail156 tcfail157 tcfail154 tcfail155 tcfail092 tcfail158 tcfail090 tcfail097 tcfail096 tcfail095 tcfail094 T3406 FrozenErrorTests T6161 T7892 tcfail209a T5236 TcCoercibleFail2 tcfail151 T1899 IPFail T7279 T5095 ContextStack1 T3176 T1595 tcfail004 tcfail005 tcfail006 tcfail007 tcfail001 tcfail002 tcfail003 T5858 SCLoop tcfail008 tcfail009 T9774 tcfail167 tcfail166 tcfail165 tcfail164 tcfail088 tcfail089 tcfail161 tcfail160 tcfail084 tcfail085 tcfail086 tcfail168 tcfail080 mc19 tcfail082 tcfail083 T2636 T4325 drv-functor1 T4966 drv003 deriving-1935 drv-foldable-traversable1 T2245 T3303 read043 read064 read066 read014 read018"
-- parseFileNamesParser :: Parser (FilePath, FilePath)
-- parseFileNamesParser =
-- pure "Actual stderr output differs from expected:\n" *>
-- pure "--- " *>
-- many1 (msum [letter, alphaNum, oneOf "/."])
-- parseFileNames :: Text -> (FilePath, FilePath)
-- parseFileNames t = do
-- let (_, t') = T.breakOn "Actual stderr output differs from expected:\n" t
-- either (error . show) id
-- (runParser parseFileNamesParser () "<unknown>" t')
-- | This script will review changes made by previous script
-- (turtle_replace_stdout.hs) for some trivial cases, where output
-- only changed by some clear diff. For example, if a word "Warning:"
-- was lower-cased, if a word "error:" was added and nothing more has happened
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
import Debug.Trace
import qualified Control.Foldl as L
import Data.Foldable (forM_)
import qualified Data.List as DL
import Data.Maybe (catMaybes)
import qualified Data.Text as T
import qualified Filesystem.Path.CurrentOS as FP
import Prelude hiding (FilePath)
import Text.RawString.QQ
import Turtle
main :: IO ()
main = do
-- forM_ ["tests/ghci/scripts/ghci021.stderr"] $ \fp -> do
forM_ modified $ \fp -> do
diffLines <- readProcOutputLinesNI "git" ["diff", fpToText fp]
-- we're only interested in lines which are adding or removing things
let differing = filter isDiffLine diffLines
let (removed, added) = DL.partition (\l -> T.take 1 l == "-") differing
when (isTrivial removed added) $ do
gitAdd fp
where
isDiffLine l = let one = T.take 1 l
thr = T.take 3 l
in (one == "+" || one == "-")
&& (not (thr == "+++" || thr == "---"))
isTrivialD rems adds =
trace "> isTrivial" $ traceShow rems $ traceShow adds $
trace "> isTrivial result: " $ traceShowId $
isTrivial rems adds
-- | Does the actual check if this diff is trivial to review/accept
isTrivial :: [Text] -> [Text] -> Bool
isTrivial [] [] = True
isTrivial [] (_:_) = False
isTrivial (_:_) [] = False
isTrivial (x':xs) ys =
let vs = getAdditionVariants x'
checkVariant :: Text -> Bool
checkVariant v = case findSplit v ys of
(True, vs') -> isTrivial xs vs'
(False, _) -> False
in any (== True) (map checkVariant vs)
-- | Gets all possible candidates which might be for this
-- particular removal. Use your imagination here!
getAdditionVariants :: Text -> [Text]
getAdditionVariants l = let l' = "+" <> (T.tail l)
in catMaybes [ lowerWarning l'
, (lowerWarning . T.stripEnd) l'
, addErrorMsgSpace l'
, (addErrorMsgSpace . T.stripEnd) l'
, addErrorMsgSpaceEnd l'
, (addErrorMsgSpaceEnd . T.stripEnd) l'
, addErrorMsg l'
, (addErrorMsg . T.stripEnd) l'
, addErrorMsgStrip l'
, (addErrorMsgStrip . T.stripEnd) l'
, addErrorMsgAfterColon l'
, (addErrorMsgAfterColon . T.stripEnd) l'
, Just l'
, Just (T.stripEnd l') ]
where
lowerWarning l' =
let (bef,aft) = T.breakOn "Warning:" l'
in if T.isPrefixOf "Warning:" aft
then Just (bef <> "warning:" <> (T.drop (T.length "Warning:") aft))
else Nothing
addErrorMsg l' =
Just (l' <> "error:")
addErrorMsgSpace l' =
Just (l' <> " error:")
addErrorMsgSpaceEnd l' =
Just (l' <> " error: ")
addErrorMsgStrip = addErrorMsgSpace . T.stripEnd
addErrorMsgAfterColon l' =
let (b,e') = T.breakOn ": " l'
in Just (b <> ": error" <> e')
findSplit :: Text -> [Text] -> (Bool, [Text])
findSplit p xs = go xs []
where
go [] buf = (False, reverse buf)
go (x':xs') buf = if p == x' then (True, reverse buf ++ xs')
else go xs' (x':buf)
gitAdd :: FilePath -> IO ()
gitAdd fp = do
echo (format ("Adding "%s) (fpToText fp))
exitOnErr (proc "git" ["add", fpToText fp] empty)
modified :: [FilePath]
modified = map (fromString . T.unpack) (T.lines modifiedRaw)
-- utils
-- | NI stands for "no input"
readProcOutputNI :: Text -> [Text] -> IO Text
readProcOutputNI p args = T.unlines <$> fold (inproc p args empty) L.list
readProcOutputLinesNI :: Text -> [Text] -> IO [Text]
readProcOutputLinesNI p args = fold (inproc p args empty) L.list
fpToText :: FilePath -> Text
fpToText = either id id . FP.toText
-- TODO: implement properly
exitOnErr :: IO a -> IO ()
exitOnErr = void
-- big data
-- output of git status that wasn't
modifiedRaw :: Text
modifiedRaw = T.pack [r|../libraries/base/tests/T9681.stderr
tests/annotations/should_fail/annfail01.stderr
tests/annotations/should_fail/annfail02.stderr
tests/annotations/should_fail/annfail03.stderr
tests/annotations/should_fail/annfail04.stderr
tests/annotations/should_fail/annfail05.stderr
tests/annotations/should_fail/annfail06.stderr
tests/annotations/should_fail/annfail07.stderr
tests/annotations/should_fail/annfail08.stderr
tests/annotations/should_fail/annfail09.stderr
tests/annotations/should_fail/annfail10.stderr
tests/annotations/should_fail/annfail11.stderr
tests/annotations/should_fail/annfail12.stderr
tests/annotations/should_fail/annfail13.stderr
tests/arrows/should_fail/T2111.stderr
tests/arrows/should_fail/T5380.stderr
tests/arrows/should_fail/arrowfail001.stderr
tests/arrows/should_fail/arrowfail002.stderr
tests/arrows/should_fail/arrowfail003.stderr
tests/arrows/should_fail/arrowfail004.stderr
tests/cabal/cabal07/cabal07.stderr
tests/deSugar/should_compile/GadtOverlap.stderr
tests/deSugar/should_compile/T2395.stderr
tests/deSugar/should_compile/T3263-1.stderr
tests/deSugar/should_compile/T3263-2.stderr
tests/deSugar/should_compile/T4488.stderr
tests/deSugar/should_compile/T5117.stderr
tests/deSugar/should_compile/T5455.stderr
tests/deSugar/should_compile/ds002.stderr-ghc
tests/deSugar/should_compile/ds003.stderr-ghc
tests/deSugar/should_compile/ds019.stderr-ghc
tests/deSugar/should_compile/ds020.stderr-ghc
tests/deSugar/should_compile/ds022.stderr-ghc
tests/deSugar/should_compile/ds041.stderr-ghc
tests/deSugar/should_compile/ds043.stderr-ghc
tests/deSugar/should_compile/ds051.stderr-ghc
tests/deSugar/should_compile/ds053.stderr-ghc
tests/deSugar/should_compile/ds056.stderr
tests/deSugar/should_compile/ds058.stderr
tests/deriving/should_compile/T4325.stderr
tests/deriving/should_compile/T4966.stderr
tests/deriving/should_compile/deriving-1935.stderr
tests/deriving/should_compile/drv-foldable-traversable1.stderr
tests/deriving/should_compile/drv-functor1.stderr
tests/deriving/should_compile/drv003.stderr
tests/deriving/should_fail/T1133A.stderr
tests/deriving/should_fail/T1496.stderr
tests/deriving/should_fail/T2394.stderr
tests/deriving/should_fail/T2604.stderr
tests/deriving/should_fail/T2701.stderr
tests/deriving/should_fail/T2721.stderr
tests/deriving/should_fail/T2851.stderr
tests/deriving/should_fail/T3101.stderr
tests/deriving/should_fail/T3621.stderr
tests/deriving/should_fail/T3833.stderr
tests/deriving/should_fail/T3834.stderr
tests/deriving/should_fail/T4528.stderr
tests/deriving/should_fail/T4846.stderr
tests/deriving/should_fail/T5287.stderr
tests/deriving/should_fail/T5478.stderr
tests/deriving/should_fail/T5498.stderr
tests/deriving/should_fail/T5686.stderr
tests/deriving/should_fail/T5863a.stderr
tests/deriving/should_fail/T5922.stderr
tests/deriving/should_fail/T6147.stderr
tests/deriving/should_fail/T7148.stderr
tests/deriving/should_fail/T7148a.stderr
tests/deriving/should_fail/T7800.stderr
tests/deriving/should_fail/T7959.stderr
tests/deriving/should_fail/T8851.stderr
tests/deriving/should_fail/T8984.stderr
tests/deriving/should_fail/T9071.stderr
tests/deriving/should_fail/T9071_2.stderr
tests/deriving/should_fail/T9687.stderr
tests/deriving/should_fail/drvfail-foldable-traversable1.stderr
tests/deriving/should_fail/drvfail-functor1.stderr
tests/deriving/should_fail/drvfail-functor2.stderr
tests/deriving/should_fail/drvfail001.stderr
tests/deriving/should_fail/drvfail002.stderr
tests/deriving/should_fail/drvfail003.stderr
tests/deriving/should_fail/drvfail004.stderr
tests/deriving/should_fail/drvfail005.stderr
tests/deriving/should_fail/drvfail007.stderr
tests/deriving/should_fail/drvfail009.stderr
tests/deriving/should_fail/drvfail011.stderr
tests/deriving/should_fail/drvfail012.stderr
tests/deriving/should_fail/drvfail013.stderr
tests/deriving/should_fail/drvfail015.stderr
tests/deriving/should_fail/drvfail016.stderr
tests/deriving/should_run/T9576.stderr
tests/driver/T1372/T1372.stderr
tests/driver/T2182.stderr
tests/driver/T2464.stderr
tests/driver/T2499.stderr
tests/driver/T2507.stderr
tests/driver/T5147/T5147.stderr
tests/driver/T8101.stderr
tests/driver/T8959a.stderr
tests/driver/bug1677/bug1677.stderr
tests/driver/driver063.stderr
tests/driver/retc001/retc001.stderr
tests/driver/sigof02/sigof02dmt.stderr
tests/driver/sigof02/sigof02dt.stderr
tests/driver/sigof04/sigof04.stderr
tests/driver/werror.stderr
tests/ffi/should_compile/T1357.stderr
tests/ffi/should_fail/T3066.stderr
tests/ffi/should_fail/T5664.stderr
tests/ffi/should_fail/T7243.stderr
tests/ffi/should_fail/T7506.stderr
tests/ffi/should_fail/capi_value_function.stderr
tests/ffi/should_fail/ccall_value.stderr
tests/ffi/should_fail/ccfail001.stderr
tests/ffi/should_fail/ccfail002.stderr
tests/ffi/should_fail/ccfail003.stderr
tests/ffi/should_fail/ccfail004.stderr
tests/ffi/should_fail/ccfail005.stderr
tests/gadt/CasePrune.stderr
tests/gadt/T3163.stderr
tests/gadt/T3169.stderr
tests/gadt/T3651.stderr
tests/gadt/T7293.stderr
tests/gadt/T7294.stderr
tests/gadt/T7558.stderr
tests/gadt/gadt-escape1.stderr
tests/gadt/gadt10.stderr
tests/gadt/gadt11.stderr
tests/gadt/gadt13.stderr
tests/gadt/gadt21.stderr
tests/gadt/gadt7.stderr
tests/gadt/gadtSyntaxFail001.stderr
tests/gadt/gadtSyntaxFail002.stderr
tests/gadt/gadtSyntaxFail003.stderr
tests/gadt/lazypat.stderr
tests/gadt/records-fail1.stderr
tests/gadt/rw.stderr
tests/generics/GenCannotDoRep0_0.stderr
tests/generics/GenCannotDoRep0_1.stderr
tests/generics/GenCannotDoRep0_2.stderr
tests/generics/GenCannotDoRep1_0.stderr
tests/generics/GenCannotDoRep1_1.stderr
tests/generics/GenCannotDoRep1_2.stderr
tests/generics/GenCannotDoRep1_3.stderr
tests/generics/GenCannotDoRep1_4.stderr
tests/generics/GenCannotDoRep1_6.stderr
tests/generics/GenCannotDoRep1_7.stderr
tests/generics/GenCannotDoRep1_8.stderr
tests/generics/GenShouldFail0.stderr
tests/generics/GenShouldFail1_0.stderr
tests/generics/T5462No1.stderr
tests/generics/T8468.stderr
tests/ghc-api/apirecomp001/apirecomp001.stderr
tests/ghc-e/should_run/T2636.stderr
tests/ghci.debugger/scripts/break003.stderr
tests/ghci.debugger/scripts/break006.stderr
tests/ghci.debugger/scripts/break019.stderr
tests/ghci.debugger/scripts/dynbrk001.stderr
tests/ghci.debugger/scripts/print007.stderr
tests/ghci.debugger/scripts/print019.stderr
tests/ghci/prog006/prog006.stderr
tests/ghci/prog009/ghci.prog009.stderr
tests/ghci/prog012/prog012.stderr
tests/ghci/prog013/prog013.stderr
tests/ghci/scripts/Defer02.stderr
tests/ghci/scripts/T1914.stderr
tests/ghci/scripts/T2182ghci.stderr
tests/ghci/scripts/T2182ghci2.stderr
tests/ghci/scripts/T2452.stderr
tests/ghci/scripts/T2816.stderr
tests/ghci/scripts/T3263.stderr
tests/ghci/scripts/T4127a.stderr
tests/ghci/scripts/T5564.stderr
tests/ghci/scripts/T5820.stderr
tests/ghci/scripts/T5836.stderr
tests/ghci/scripts/T5979.stderr
tests/ghci/scripts/T6007.stderr
tests/ghci/scripts/T6106.stderr
tests/ghci/scripts/T7627b.stderr
tests/ghci/scripts/T7894.stderr
tests/ghci/scripts/T8485.stderr
tests/ghci/scripts/T8639.stderr
tests/ghci/scripts/T8649.stderr
tests/ghci/scripts/T8959.stderr
tests/ghci/scripts/T9293.stderr
tests/ghci/scripts/T9878.stderr
tests/ghci/scripts/ghci019.stderr
tests/ghci/scripts/ghci021.stderr
tests/ghci/scripts/ghci022.stderr
tests/ghci/scripts/ghci031.stderr
tests/ghci/scripts/ghci034.stderr
tests/ghci/scripts/ghci036.stderr
tests/ghci/scripts/ghci038.stderr
tests/ghci/scripts/ghci044.stderr
tests/ghci/scripts/ghci047.stderr
tests/ghci/scripts/ghci048.stderr
tests/ghci/scripts/ghci050.stderr
tests/ghci/scripts/ghci051.stderr
tests/ghci/scripts/ghci052.stderr
tests/ghci/scripts/ghci053.stderr
tests/ghci/scripts/ghci057.stderr
tests/ghci/should_run/T9915.stderr
tests/haddock/haddock_examples/haddock.Test.stderr
tests/haddock/should_fail_flag_haddock/haddockE004.stderr
tests/indexed-types/should_compile/Class3.stderr
tests/indexed-types/should_compile/PushedInAsGivens.stderr
tests/indexed-types/should_compile/Simple14.stderr
tests/indexed-types/should_compile/Simple2.stderr
tests/indexed-types/should_compile/T3023.stderr
tests/indexed-types/should_compile/T3208b.stderr
tests/indexed-types/should_compile/T3418.stderr
tests/indexed-types/should_compile/T8889.stderr
tests/indexed-types/should_compile/T9085.stderr
tests/indexed-types/should_fail/BadSock.stderr
tests/indexed-types/should_fail/ClosedFam3.stderr
tests/indexed-types/should_fail/ClosedFam4.stderr
tests/indexed-types/should_fail/DerivUnsatFam.stderr
tests/indexed-types/should_fail/ExtraTcsUntch.stderr
tests/indexed-types/should_fail/GADTwrong1.stderr
tests/indexed-types/should_fail/NoGood.stderr
tests/indexed-types/should_fail/NoMatchErr.stderr
tests/indexed-types/should_fail/NotRelaxedExamples.stderr
tests/indexed-types/should_fail/Over.stderr
tests/indexed-types/should_fail/Overlap10.stderr
tests/indexed-types/should_fail/Overlap11.stderr
tests/indexed-types/should_fail/Overlap15.stderr
tests/indexed-types/should_fail/Overlap3.stderr
tests/indexed-types/should_fail/Overlap4.stderr
tests/indexed-types/should_fail/Overlap5.stderr
tests/indexed-types/should_fail/Overlap6.stderr
tests/indexed-types/should_fail/Overlap7.stderr
tests/indexed-types/should_fail/Overlap9.stderr
tests/indexed-types/should_fail/SimpleFail11a.stderr
tests/indexed-types/should_fail/SimpleFail11b.stderr
tests/indexed-types/should_fail/SimpleFail11c.stderr
tests/indexed-types/should_fail/SimpleFail11d.stderr
tests/indexed-types/should_fail/SimpleFail12.stderr
tests/indexed-types/should_fail/SimpleFail13.stderr
tests/indexed-types/should_fail/SimpleFail14.stderr
tests/indexed-types/should_fail/SimpleFail15.stderr
tests/indexed-types/should_fail/SimpleFail16.stderr
tests/indexed-types/should_fail/SimpleFail1a.stderr
tests/indexed-types/should_fail/SimpleFail1b.stderr
tests/indexed-types/should_fail/SimpleFail2a.stderr
tests/indexed-types/should_fail/SimpleFail2b.stderr
tests/indexed-types/should_fail/SimpleFail3a.stderr
tests/indexed-types/should_fail/SimpleFail4.stderr
tests/indexed-types/should_fail/SimpleFail5a.stderr
tests/indexed-types/should_fail/SimpleFail5b.stderr
tests/indexed-types/should_fail/SimpleFail6.stderr
tests/indexed-types/should_fail/SimpleFail7.stderr
tests/indexed-types/should_fail/SimpleFail8.stderr
tests/indexed-types/should_fail/T1897b.stderr
tests/indexed-types/should_fail/T1900.stderr
tests/indexed-types/should_fail/T2157.stderr
tests/indexed-types/should_fail/T2203a.stderr
tests/indexed-types/should_fail/T2334A.stderr
tests/indexed-types/should_fail/T2544.stderr
tests/indexed-types/should_fail/T2627b.stderr
tests/indexed-types/should_fail/T2664.stderr
tests/indexed-types/should_fail/T2677.stderr
tests/indexed-types/should_fail/T2693.stderr
tests/indexed-types/should_fail/T2888.stderr
tests/indexed-types/should_fail/T3092.stderr
tests/indexed-types/should_fail/T3330a.stderr
tests/indexed-types/should_fail/T3330b.stderr
tests/indexed-types/should_fail/T3330c.stderr
tests/indexed-types/should_fail/T3440.stderr
tests/indexed-types/should_fail/T4093a.stderr
tests/indexed-types/should_fail/T4093b.stderr
tests/indexed-types/should_fail/T4099.stderr
tests/indexed-types/should_fail/T4174.stderr
tests/indexed-types/should_fail/T4179.stderr
tests/indexed-types/should_fail/T4246.stderr
tests/indexed-types/should_fail/T4272.stderr
tests/indexed-types/should_fail/T4485.stderr
tests/indexed-types/should_fail/T5439.stderr
tests/indexed-types/should_fail/T5515.stderr
tests/indexed-types/should_fail/T5934.stderr
tests/indexed-types/should_fail/T6088.stderr
tests/indexed-types/should_fail/T6123.stderr
tests/indexed-types/should_fail/T7010.stderr
tests/indexed-types/should_fail/T7194.stderr
tests/indexed-types/should_fail/T7354.stderr
tests/indexed-types/should_fail/T7354a.stderr
tests/indexed-types/should_fail/T7536.stderr
tests/indexed-types/should_fail/T7729.stderr
tests/indexed-types/should_fail/T7729a.stderr
tests/indexed-types/should_fail/T7786.stderr
tests/indexed-types/should_fail/T7862.stderr
tests/indexed-types/should_fail/T7938.stderr
tests/indexed-types/should_fail/T7967.stderr
tests/indexed-types/should_fail/T8155.stderr
tests/indexed-types/should_fail/T8227.stderr
tests/indexed-types/should_fail/T8368.stderr
tests/indexed-types/should_fail/T8368a.stderr
tests/indexed-types/should_fail/T8518.stderr
tests/indexed-types/should_fail/T9036.stderr
tests/indexed-types/should_fail/T9097.stderr
tests/indexed-types/should_fail/T9160.stderr
tests/indexed-types/should_fail/T9167.stderr
tests/indexed-types/should_fail/T9171.stderr
tests/indexed-types/should_fail/T9357.stderr
tests/indexed-types/should_fail/T9371.stderr
tests/indexed-types/should_fail/T9433.stderr
tests/indexed-types/should_fail/T9580.stderr
tests/indexed-types/should_fail/T9662.stderr
tests/indexed-types/should_fail/T9896.stderr
tests/indexed-types/should_fail/TyFamArity1.stderr
tests/indexed-types/should_fail/TyFamArity2.stderr
tests/indexed-types/should_fail/TyFamUndec.stderr
tests/mdo/should_fail/mdofail001.stderr
tests/mdo/should_fail/mdofail002.stderr
tests/mdo/should_fail/mdofail003.stderr
tests/mdo/should_fail/mdofail005.stderr
tests/module/T414.stderr
tests/module/mod1.stderr
tests/module/mod10.stderr
tests/module/mod101.stderr
tests/module/mod102.stderr
tests/module/mod110.stderr
tests/module/mod114.stderr
tests/module/mod116.stderr
tests/module/mod120.stderr
tests/module/mod121.stderr
tests/module/mod122.stderr
tests/module/mod123.stderr
tests/module/mod124.stderr
tests/module/mod125.stderr
tests/module/mod126.stderr
tests/module/mod127.stderr
tests/module/mod128.stderr-ghc
tests/module/mod130.stderr
tests/module/mod131.stderr
tests/module/mod132.stderr
tests/module/mod134.stderr
tests/module/mod135.stderr
tests/module/mod136.stderr
tests/module/mod138.stderr
tests/module/mod14.stderr-ghc
tests/module/mod142.stderr
tests/module/mod143.stderr
tests/module/mod144.stderr
tests/module/mod145.stderr
tests/module/mod146.stderr
tests/module/mod147.stderr
tests/module/mod150.stderr
tests/module/mod151.stderr
tests/module/mod152.stderr
tests/module/mod153.stderr
tests/module/mod155.stderr
tests/module/mod158.stderr
tests/module/mod160.stderr
tests/module/mod161.stderr
tests/module/mod164.stderr
tests/module/mod165.stderr
tests/module/mod17.stderr
tests/module/mod174.stderr
tests/module/mod176.stderr
tests/module/mod177.stderr
tests/module/mod178.stderr
tests/module/mod18.stderr
tests/module/mod180.stderr
tests/module/mod19.stderr
tests/module/mod2.stderr
tests/module/mod20.stderr
tests/module/mod21.stderr
tests/module/mod22.stderr
tests/module/mod23.stderr
tests/module/mod24.stderr
tests/module/mod25.stderr
tests/module/mod26.stderr
tests/module/mod27.stderr
tests/module/mod29.stderr
tests/module/mod3.stderr
tests/module/mod36.stderr
tests/module/mod38.stderr
tests/module/mod4.stderr
tests/module/mod40.stderr
tests/module/mod41.stderr
tests/module/mod42.stderr
tests/module/mod43.stderr
tests/module/mod44.stderr
tests/module/mod45.stderr
tests/module/mod46.stderr
tests/module/mod47.stderr
tests/module/mod48.stderr
tests/module/mod49.stderr
tests/module/mod5.stderr-ghc
tests/module/mod50.stderr
tests/module/mod51.stderr
tests/module/mod52.stderr
tests/module/mod53.stderr
tests/module/mod54.stderr
tests/module/mod55.stderr
tests/module/mod56.stderr
tests/module/mod58.stderr
tests/module/mod59.stderr
tests/module/mod60.stderr
tests/module/mod61.stderr
tests/module/mod62.stderr
tests/module/mod63.stderr
tests/module/mod66.stderr
tests/module/mod67.stderr
tests/module/mod68.stderr
tests/module/mod69.stderr
tests/module/mod7.stderr
tests/module/mod70.stderr
tests/module/mod71.stderr
tests/module/mod72.stderr
tests/module/mod73.stderr
tests/module/mod74.stderr
tests/module/mod76.stderr
tests/module/mod77.stderr
tests/module/mod79.stderr
tests/module/mod8.stderr
tests/module/mod80.stderr
tests/module/mod81.stderr
tests/module/mod87.stderr
tests/module/mod88.stderr
tests/module/mod89.stderr
tests/module/mod9.stderr
tests/module/mod90.stderr
tests/module/mod91.stderr
tests/module/mod97.stderr
tests/module/mod98.stderr
tests/numeric/should_compile/T7881.stderr
tests/numeric/should_compile/T7895.stderr
tests/numeric/should_compile/T8542.stderr
tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
tests/package/package01e.stderr
tests/package/package06e.stderr
tests/package/package07e.stderr
tests/package/package08e.stderr
tests/package/package09e.stderr
tests/parser/should_compile/T2245.stderr
tests/parser/should_compile/T3303.stderr
tests/parser/should_compile/read014.stderr-ghc
tests/parser/should_compile/read018.stderr
tests/parser/should_compile/read043.stderr
tests/parser/should_compile/read064.stderr
tests/parser/should_compile/read066.stderr
tests/parser/should_fail/ExportCommaComma.stderr
tests/parser/should_fail/NoDoAndIfThenElse.stderr
tests/parser/should_fail/NondecreasingIndentationFail.stderr
tests/parser/should_fail/ParserNoBinaryLiterals1.stderr
tests/parser/should_fail/ParserNoBinaryLiterals2.stderr
tests/parser/should_fail/ParserNoBinaryLiterals3.stderr
tests/parser/should_fail/ParserNoForallUnicode.stderr
tests/parser/should_fail/ParserNoLambdaCase.stderr
tests/parser/should_fail/ParserNoMultiWayIf.stderr
tests/parser/should_fail/T1344a.stderr
tests/parser/should_fail/T1344b.stderr
tests/parser/should_fail/T1344c.stderr
tests/parser/should_fail/T3095.stderr
tests/parser/should_fail/T3153.stderr
tests/parser/should_fail/T3751.stderr
tests/parser/should_fail/T3811.stderr
tests/parser/should_fail/T3811b.stderr
tests/parser/should_fail/T3811c.stderr
tests/parser/should_fail/T3811d.stderr
tests/parser/should_fail/T3811e.stderr
tests/parser/should_fail/T3811f.stderr
tests/parser/should_fail/T3811g.stderr
tests/parser/should_fail/T5425.stderr
tests/parser/should_fail/T7848.stderr
tests/parser/should_fail/T8431.stderr
tests/parser/should_fail/T8506.stderr
tests/parser/should_fail/T984.stderr
tests/parser/should_fail/position001.stderr
tests/parser/should_fail/position002.stderr
tests/parser/should_fail/readFail001.stderr
tests/parser/should_fail/readFail002.stderr
tests/parser/should_fail/readFail003.stderr
tests/parser/should_fail/readFail004.stderr
tests/parser/should_fail/readFail005.stderr
tests/parser/should_fail/readFail006.stderr
tests/parser/should_fail/readFail007.stderr
tests/parser/should_fail/readFail008.stderr
tests/parser/should_fail/readFail009.stderr
tests/parser/should_fail/readFail011.stderr
tests/parser/should_fail/readFail012.stderr
tests/parser/should_fail/readFail013.stderr
tests/parser/should_fail/readFail014.stderr
tests/parser/should_fail/readFail015.stderr
tests/parser/should_fail/readFail016.stderr
tests/parser/should_fail/readFail017.stderr
tests/parser/should_fail/readFail018.stderr
tests/parser/should_fail/readFail019.stderr
tests/parser/should_fail/readFail020.stderr
tests/parser/should_fail/readFail021.stderr
tests/parser/should_fail/readFail022.stderr
tests/parser/should_fail/readFail023.stderr
tests/parser/should_fail/readFail024.stderr
tests/parser/should_fail/readFail025.stderr
tests/parser/should_fail/readFail026.stderr
tests/parser/should_fail/readFail027.stderr
tests/parser/should_fail/readFail028.stderr
tests/parser/should_fail/readFail029.stderr
tests/parser/should_fail/readFail030.stderr
tests/parser/should_fail/readFail031.stderr
tests/parser/should_fail/readFail033.stderr
tests/parser/should_fail/readFail034.stderr
tests/parser/should_fail/readFail035.stderr
tests/parser/should_fail/readFail036.stderr
tests/parser/should_fail/readFail037.stderr
tests/parser/should_fail/readFail038.stderr
tests/parser/should_fail/readFail039.stderr
tests/parser/should_fail/readFail040.stderr
tests/parser/should_fail/readFail041.stderr
tests/parser/should_fail/readFail042.stderr
tests/parser/should_fail/readFail043.stderr
tests/parser/should_fail/readFail044.stderr
tests/parser/should_fail/readFail046.stderr
tests/parser/should_fail/readFail047.stderr
tests/parser/should_fail/readFailTraditionalRecords1.stderr
tests/parser/should_fail/readFailTraditionalRecords2.stderr
tests/parser/should_fail/readFailTraditionalRecords3.stderr
tests/parser/unicode/T2302.stderr
tests/parser/unicode/utf8_002.stderr
tests/parser/unicode/utf8_003.stderr
tests/parser/unicode/utf8_004.stderr
tests/parser/unicode/utf8_005.stderr
tests/parser/unicode/utf8_010.stderr
tests/parser/unicode/utf8_011.stderr
tests/parser/unicode/utf8_020.stderr
tests/parser/unicode/utf8_021.stderr
tests/parser/unicode/utf8_022.stderr
tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
tests/partial-sigs/should_fail/AnnotatedConstraint.stderr
tests/partial-sigs/should_fail/AnnotatedConstraintNotForgotten.stderr
tests/partial-sigs/should_fail/Defaulting1MROff.stderr
tests/partial-sigs/should_fail/ExtraConstraintsWildcardNotEnabled.stderr
tests/partial-sigs/should_fail/ExtraConstraintsWildcardNotLast.stderr
tests/partial-sigs/should_fail/ExtraConstraintsWildcardNotPresent.stderr
tests/partial-sigs/should_fail/Forall1Bad.stderr
tests/partial-sigs/should_fail/InstantiatedNamedWildcardsInConstraints.stderr
tests/partial-sigs/should_fail/NamedExtraConstraintsWildcard.stderr
tests/partial-sigs/should_fail/NamedWildcardsEnabled.stderr
tests/partial-sigs/should_fail/NamedWildcardsNotEnabled.stderr
tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.stderr
tests/partial-sigs/should_fail/NestedExtraConstraintsWildcard.stderr
tests/partial-sigs/should_fail/NestedNamedExtraConstraintsWildcard.stderr
tests/partial-sigs/should_fail/PartialClassMethodSignature.stderr
tests/partial-sigs/should_fail/PartialTypeSignaturesDisabled.stderr
tests/partial-sigs/should_fail/ScopedNamedWildcardsBad.stderr
tests/partial-sigs/should_fail/TidyClash.stderr
tests/partial-sigs/should_fail/UnnamedConstraintWildcard1.stderr
tests/partial-sigs/should_fail/UnnamedConstraintWildcard2.stderr
tests/partial-sigs/should_fail/WildcardInADT1.stderr
tests/partial-sigs/should_fail/WildcardInADT2.stderr
tests/partial-sigs/should_fail/WildcardInADT3.stderr
tests/partial-sigs/should_fail/WildcardInADTContext1.stderr
tests/partial-sigs/should_fail/WildcardInADTContext2.stderr
tests/partial-sigs/should_fail/WildcardInDefault.stderr
tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr
tests/partial-sigs/should_fail/WildcardInDeriving.stderr
tests/partial-sigs/should_fail/WildcardInForeignExport.stderr
tests/partial-sigs/should_fail/WildcardInForeignImport.stderr
tests/partial-sigs/should_fail/WildcardInGADT1.stderr
tests/partial-sigs/should_fail/WildcardInGADT2.stderr
tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr
tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr
tests/partial-sigs/should_fail/WildcardInNewtype.stderr
tests/partial-sigs/should_fail/WildcardInPatSynSig.stderr
tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr
tests/partial-sigs/should_fail/WildcardInTypeBrackets.stderr
tests/partial-sigs/should_fail/WildcardInTypeFamilyInstanceLHS.stderr
tests/partial-sigs/should_fail/WildcardInTypeFamilyInstanceRHS.stderr
tests/partial-sigs/should_fail/WildcardInTypeSynonymLHS.stderr
tests/partial-sigs/should_fail/WildcardInTypeSynonymRHS.stderr
tests/partial-sigs/should_fail/WildcardInstantiations.stderr
tests/partial-sigs/should_fail/WildcardsInPatternAndExprSig.stderr
tests/patsyn/should_compile/T9975a.stderr
tests/patsyn/should_fail/T9161-1.stderr
tests/patsyn/should_fail/T9161-2.stderr
tests/patsyn/should_fail/T9705-1.stderr
tests/patsyn/should_fail/T9705-2.stderr
tests/patsyn/should_fail/as-pattern.stderr
tests/patsyn/should_fail/local.stderr
tests/patsyn/should_fail/mono.stderr
tests/patsyn/should_fail/unboxed-bind.stderr
tests/patsyn/should_fail/unboxed-wrapper-naked.stderr
tests/patsyn/should_fail/unidir.stderr
tests/perf/compiler/T5837.stderr
tests/perf/compiler/T9872a.stderr
tests/perf/compiler/T9872b.stderr
tests/perf/compiler/T9872c.stderr
tests/perf/compiler/parsing001.stderr
tests/polykinds/PolyKinds02.stderr
tests/polykinds/PolyKinds04.stderr
tests/polykinds/PolyKinds06.stderr
tests/polykinds/PolyKinds07.stderr
tests/polykinds/T5716.stderr
tests/polykinds/T5716a.stderr
tests/polykinds/T6021.stderr
tests/polykinds/T6039.stderr
tests/polykinds/T6054.stderr
tests/polykinds/T6129.stderr
tests/polykinds/T7151.stderr
tests/polykinds/T7224.stderr
tests/polykinds/T7230.stderr
tests/polykinds/T7278.stderr
tests/polykinds/T7328.stderr
tests/polykinds/T7341.stderr
tests/polykinds/T7404.stderr
tests/polykinds/T7433.stderr
tests/polykinds/T7438.stderr
tests/polykinds/T7481.stderr
tests/polykinds/T7524.stderr
tests/polykinds/T7594.stderr
tests/polykinds/T7805.stderr
tests/polykinds/T7939a.stderr
tests/polykinds/T8132.stderr
tests/polykinds/T8566.stderr
tests/polykinds/T8616.stderr
tests/polykinds/T9106.stderr
tests/polykinds/T9144.stderr
tests/polykinds/T9200b.stderr
tests/polykinds/T9222.stderr
tests/polykinds/T9574.stderr
tests/profiling/should_fail/proffail001.stderr
tests/programs/hs-boot/hs-boot.stderr
tests/quasiquotation/T3953.stderr
tests/quasiquotation/T5204.stderr
tests/quasiquotation/qq001/qq001.stderr
tests/quasiquotation/qq002/qq002.stderr
tests/quasiquotation/qq003/qq003.stderr
tests/quasiquotation/qq004/qq004.stderr
tests/rebindable/rebindable6.stderr
tests/rename/prog002/rename.prog002.stderr
tests/rename/prog003/rename.prog003.stderr
tests/rename/should_compile/T1789.stderr
tests/rename/should_compile/T1972.stderr
tests/rename/should_compile/T3103/T3103.stderr
tests/rename/should_compile/T3262.stderr-ghc
tests/rename/should_compile/T3371.stderr
tests/rename/should_compile/T3449.stderr
tests/rename/should_compile/T3823.stderr
tests/rename/should_compile/T4426.stderr
tests/rename/should_compile/T4489.stderr
tests/rename/should_compile/T5331.stderr
tests/rename/should_compile/T5334.stderr
tests/rename/should_compile/T5867.stderr
tests/rename/should_compile/T7085.stderr
tests/rename/should_compile/T7145b.stderr
tests/rename/should_compile/T7167.stderr
tests/rename/should_compile/T9778.stderr
tests/rename/should_compile/mc10.stderr-ghc
tests/rename/should_compile/rn037.stderr-ghc
tests/rename/should_compile/rn039.stderr-ghc
tests/rename/should_compile/rn040.stderr-ghc
tests/rename/should_compile/rn041.stderr-ghc
tests/rename/should_compile/rn046.stderr-ghc
tests/rename/should_compile/rn047.stderr-ghc
tests/rename/should_compile/rn049.stderr
tests/rename/should_compile/rn050.stderr
tests/rename/should_compile/rn055.stderr-ghc
tests/rename/should_compile/rn063.stderr
tests/rename/should_compile/rn064.stderr
tests/rename/should_compile/rn066.stderr
tests/rename/should_fail/Misplaced.stderr
tests/rename/should_fail/RnStaticPointersFail01.stderr
tests/rename/should_fail/RnStaticPointersFail02.stderr
tests/rename/should_fail/RnStaticPointersFail03.stderr
tests/rename/should_fail/T1595a.stderr
tests/rename/should_fail/T2310.stderr
tests/rename/should_fail/T2490.stderr
tests/rename/should_fail/T2723.stderr
tests/rename/should_fail/T2901.stderr
tests/rename/should_fail/T2993.stderr
tests/rename/should_fail/T3265.stderr
tests/rename/should_fail/T3792.stderr
tests/rename/should_fail/T4042.stderr
tests/rename/should_fail/T5211.stderr
tests/rename/should_fail/T5281.stderr
tests/rename/should_fail/T5372.stderr
tests/rename/should_fail/T5385.stderr
tests/rename/should_fail/T5513.stderr
tests/rename/should_fail/T5533.stderr
tests/rename/should_fail/T5589.stderr
tests/rename/should_fail/T5657.stderr
tests/rename/should_fail/T5745.stderr
tests/rename/should_fail/T5892a.stderr
tests/rename/should_fail/T5892b.stderr
tests/rename/should_fail/T5951.stderr
tests/rename/should_fail/T6060.stderr
tests/rename/should_fail/T6148.stderr
tests/rename/should_fail/T7164.stderr
tests/rename/should_fail/T7338.stderr
tests/rename/should_fail/T7338a.stderr
tests/rename/should_fail/T7454.stderr
tests/rename/should_fail/T7906.stderr
tests/rename/should_fail/T7937.stderr
tests/rename/should_fail/T7943.stderr
tests/rename/should_fail/T8149.stderr
tests/rename/should_fail/T8448.stderr
tests/rename/should_fail/T9006.stderr
tests/rename/should_fail/T9032.stderr
tests/rename/should_fail/T9077.stderr
tests/rename/should_fail/T9156.stderr
tests/rename/should_fail/T9177.stderr
tests/rename/should_fail/T9436.stderr
tests/rename/should_fail/T9437.stderr
tests/rename/should_fail/T9815.stderr
tests/rename/should_fail/mc13.stderr
tests/rename/should_fail/mc14.stderr
tests/rename/should_fail/rn_dup.stderr
tests/rename/should_fail/rnfail001.stderr
tests/rename/should_fail/rnfail002.stderr
tests/rename/should_fail/rnfail003.stderr
tests/rename/should_fail/rnfail004.stderr
tests/rename/should_fail/rnfail007.stderr
tests/rename/should_fail/rnfail008.stderr
tests/rename/should_fail/rnfail009.stderr
tests/rename/should_fail/rnfail010.stderr
tests/rename/should_fail/rnfail011.stderr
tests/rename/should_fail/rnfail012.stderr
tests/rename/should_fail/rnfail013.stderr
tests/rename/should_fail/rnfail015.stderr
tests/rename/should_fail/rnfail016.stderr
tests/rename/should_fail/rnfail017.stderr
tests/rename/should_fail/rnfail018.stderr
tests/rename/should_fail/rnfail019.stderr
tests/rename/should_fail/rnfail021.stderr
tests/rename/should_fail/rnfail022.stderr
tests/rename/should_fail/rnfail023.stderr
tests/rename/should_fail/rnfail024.stderr
tests/rename/should_fail/rnfail025.stderr
tests/rename/should_fail/rnfail026.stderr
tests/rename/should_fail/rnfail027.stderr
tests/rename/should_fail/rnfail028.stderr
tests/rename/should_fail/rnfail029.stderr
tests/rename/should_fail/rnfail030.stderr
tests/rename/should_fail/rnfail031.stderr
tests/rename/should_fail/rnfail032.stderr
tests/rename/should_fail/rnfail033.stderr
tests/rename/should_fail/rnfail034.stderr
tests/rename/should_fail/rnfail035.stderr
tests/rename/should_fail/rnfail039.stderr
tests/rename/should_fail/rnfail040.stderr
tests/rename/should_fail/rnfail041.stderr
tests/rename/should_fail/rnfail042.stderr
tests/rename/should_fail/rnfail043.stderr
tests/rename/should_fail/rnfail044.stderr
tests/rename/should_fail/rnfail045.stderr
tests/rename/should_fail/rnfail046.stderr
tests/rename/should_fail/rnfail047.stderr
tests/rename/should_fail/rnfail048.stderr
tests/rename/should_fail/rnfail049.stderr
tests/rename/should_fail/rnfail050.stderr
tests/rename/should_fail/rnfail051.stderr
tests/rename/should_fail/rnfail052.stderr
tests/rename/should_fail/rnfail053.stderr
tests/rename/should_fail/rnfail054.stderr
tests/rename/should_fail/rnfail055.stderr
tests/rename/should_fail/rnfail056.stderr
tests/rename/should_fail/rnfail057.stderr
tests/roles/should_compile/T8958.stderr
tests/roles/should_fail/Roles10.stderr
tests/roles/should_fail/Roles11.stderr
tests/roles/should_fail/Roles12.stderr
tests/roles/should_fail/Roles5.stderr
tests/roles/should_fail/Roles6.stderr
tests/roles/should_fail/Roles7.stderr
tests/roles/should_fail/Roles8.stderr
tests/roles/should_fail/RolesIArray.stderr
tests/roles/should_fail/T8773.stderr
tests/roles/should_fail/T9204.stderr
tests/safeHaskell/check/Check01.stderr
tests/safeHaskell/check/Check05.stderr
tests/safeHaskell/check/Check06.stderr
tests/safeHaskell/check/Check08.stderr
tests/safeHaskell/check/Check09.stderr
tests/safeHaskell/check/pkg01/ImpSafe01.stderr
tests/safeHaskell/check/pkg01/ImpSafe03.stderr
tests/safeHaskell/check/pkg01/ImpSafe04.stderr
tests/safeHaskell/check/pkg01/ImpSafeOnly03.stderr
tests/safeHaskell/check/pkg01/ImpSafeOnly05.stderr
tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr
tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr
tests/safeHaskell/check/pkg01/ImpSafeOnly09.stderr
tests/safeHaskell/flags/SafeFlags03.stderr
tests/safeHaskell/flags/SafeFlags04.stderr
tests/safeHaskell/flags/SafeFlags07.stderr
tests/safeHaskell/flags/SafeFlags08.stderr
tests/safeHaskell/flags/SafeFlags09.stderr
tests/safeHaskell/flags/SafeFlags17.stderr
tests/safeHaskell/flags/SafeFlags18.stderr
tests/safeHaskell/flags/SafeFlags19.stderr
tests/safeHaskell/flags/SafeFlags22.stderr
tests/safeHaskell/flags/SafeFlags23.stderr
tests/safeHaskell/flags/SafeFlags25.stderr
tests/safeHaskell/flags/SafeFlags26.stderr
tests/safeHaskell/flags/SafeFlags28.stderr
tests/safeHaskell/flags/SafeFlags29.stderr
tests/safeHaskell/ghci/p1.stderr
tests/safeHaskell/ghci/p10.stderr
tests/safeHaskell/ghci/p11.stderr
tests/safeHaskell/ghci/p12.stderr
tests/safeHaskell/ghci/p13.stderr
tests/safeHaskell/ghci/p14.stderr
tests/safeHaskell/ghci/p16.stderr
tests/safeHaskell/ghci/p17.stderr
tests/safeHaskell/ghci/p3.stderr
tests/safeHaskell/ghci/p4.stderr
tests/safeHaskell/ghci/p6.stderr
tests/safeHaskell/ghci/p9.stderr
tests/safeHaskell/safeInfered/Mixed01.stderr
tests/safeHaskell/safeInfered/Mixed02.stderr
tests/safeHaskell/safeInfered/Mixed03.stderr
tests/safeHaskell/safeInfered/SafeWarn01.stderr
tests/safeHaskell/safeInfered/TrustworthySafe02.stderr
tests/safeHaskell/safeInfered/TrustworthySafe03.stderr
tests/safeHaskell/safeInfered/UnsafeInfered01.stderr
tests/safeHaskell/safeInfered/UnsafeInfered02.stderr
tests/safeHaskell/safeInfered/UnsafeInfered03.stderr
tests/safeHaskell/safeInfered/UnsafeInfered05.stderr
tests/safeHaskell/safeInfered/UnsafeInfered06.stderr
tests/safeHaskell/safeInfered/UnsafeInfered08.stderr
tests/safeHaskell/safeInfered/UnsafeInfered09.stderr
tests/safeHaskell/safeInfered/UnsafeInfered10.stderr
tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
tests/safeHaskell/safeInfered/UnsafeInfered13.stderr
tests/safeHaskell/safeInfered/UnsafeInfered14.stderr
tests/safeHaskell/safeInfered/UnsafeInfered15.stderr
tests/safeHaskell/safeInfered/UnsafeInfered16.stderr
tests/safeHaskell/safeInfered/UnsafeInfered17.stderr
tests/safeHaskell/safeInfered/UnsafeInfered18.stderr
tests/safeHaskell/safeInfered/UnsafeInfered19.stderr
tests/safeHaskell/safeInfered/UnsafeWarn01.stderr
tests/safeHaskell/safeInfered/UnsafeWarn02.stderr
tests/safeHaskell/safeInfered/UnsafeWarn03.stderr
tests/safeHaskell/safeInfered/UnsafeWarn04.stderr
tests/safeHaskell/safeInfered/UnsafeWarn05.stderr
tests/safeHaskell/safeInfered/UnsafeWarn06.stderr
tests/safeHaskell/safeInfered/UnsafeWarn07.stderr
tests/safeHaskell/safeLanguage/SafeLang01.stderr
tests/safeHaskell/safeLanguage/SafeLang02.stderr
tests/safeHaskell/safeLanguage/SafeLang03.stderr
tests/safeHaskell/safeLanguage/SafeLang07.stderr
tests/safeHaskell/safeLanguage/SafeLang08.stderr
tests/safeHaskell/safeLanguage/SafeLang10.stderr
tests/safeHaskell/safeLanguage/SafeLang12.stderr
tests/safeHaskell/safeLanguage/SafeLang16.stderr
tests/safeHaskell/safeLanguage/SafeLang17.stderr
tests/safeHaskell/unsafeLibs/BadImport01.stderr
tests/safeHaskell/unsafeLibs/BadImport06.stderr
tests/safeHaskell/unsafeLibs/BadImport07.stderr
tests/safeHaskell/unsafeLibs/BadImport08.stderr
tests/safeHaskell/unsafeLibs/BadImport09.stderr
tests/safeHaskell/unsafeLibs/Dep05.stderr
tests/safeHaskell/unsafeLibs/Dep06.stderr
tests/safeHaskell/unsafeLibs/Dep07.stderr
tests/safeHaskell/unsafeLibs/Dep08.stderr
tests/safeHaskell/unsafeLibs/Dep09.stderr
tests/safeHaskell/unsafeLibs/Dep10.stderr
tests/simplCore/should_compile/T4398.stderr
tests/simplCore/should_compile/T5359b.stderr
tests/simplCore/should_compile/T6082-RULE.stderr
tests/simplCore/should_compile/T8537.stderr
tests/simplCore/should_compile/simpl016.stderr
tests/simplCore/should_compile/simpl017.stderr
tests/simplCore/should_compile/simpl020.stderr
tests/stranal/should_compile/str001.stderr
tests/th/ClosedFam1TH.stderr
tests/th/T1476b.stderr
tests/th/T2597b.stderr
tests/th/T2674.stderr
tests/th/T2713.stderr
tests/th/T3177a.stderr
tests/th/T3395.stderr
tests/th/T5358.stderr
tests/th/T5795.stderr
tests/th/T5971.stderr
tests/th/T5976.stderr
tests/th/T7241.stderr
tests/th/T7276.stderr
tests/th/T7477.stderr
tests/th/T7484.stderr
tests/th/T7667a.stderr
tests/th/T8028.stderr
tests/th/T8412.stderr
tests/th/T8577.stderr
tests/th/T8759.stderr
tests/th/T8759a.stderr
tests/th/T8932.stderr
tests/th/T8987.stderr
tests/th/T9084.stderr
tests/th/T9209.stderr
tests/th/TH_1tuple.stderr
tests/th/TH_Promoted1Tuple.stderr
tests/th/TH_PromotedList.stderr
tests/th/TH_PromotedTuple.stderr
tests/th/TH_RichKinds.stderr
tests/th/TH_RichKinds2.stderr
tests/th/TH_Roles1.stderr
tests/th/TH_StaticPointers02.stderr
tests/th/TH_TyInstWhere2.stderr
tests/th/TH_dataD1.stderr
tests/th/TH_dupdecl.stderr
tests/th/TH_exn1.stderr
tests/th/TH_exn2.stderr
tests/th/TH_fail.stderr
tests/th/TH_linePragma.stderr
tests/th/TH_repPatSig.stderr
tests/th/TH_runIO.stderr
tests/th/TH_spliceD1.stderr
tests/th/TH_unresolvedInfix2.stderr
tests/typecheck/bug1465/bug1465.stderr
tests/typecheck/should_compile/FD1.stderr
tests/typecheck/should_compile/FD2.stderr
tests/typecheck/should_compile/FD3.stderr
tests/typecheck/should_compile/HasKey.stderr-ghc
tests/typecheck/should_compile/T2478.stderr
tests/typecheck/should_compile/T2494.stderr
tests/typecheck/should_compile/T2497.stderr
tests/typecheck/should_compile/T3696.stderr
tests/typecheck/should_compile/T4912.stderr
tests/typecheck/should_compile/T5481.stderr
tests/typecheck/should_compile/T7050.stderr
tests/typecheck/should_compile/T7220a.stderr
tests/typecheck/should_compile/T7562.stderr
tests/typecheck/should_compile/T7903.stderr-ghc
tests/typecheck/should_compile/T9497a.stderr
tests/typecheck/should_compile/T9834.stderr
tests/typecheck/should_compile/T9939.stderr
tests/typecheck/should_compile/holes.stderr
tests/typecheck/should_compile/holes2.stderr
tests/typecheck/should_compile/holes3.stderr
tests/typecheck/should_compile/tc056.stderr
tests/typecheck/should_compile/tc078.stderr-ghc
tests/typecheck/should_compile/tc115.stderr-ghc
tests/typecheck/should_compile/tc116.stderr-ghc
tests/typecheck/should_compile/tc125.stderr-ghc
tests/typecheck/should_compile/tc126.stderr-ghc
tests/typecheck/should_compile/tc141.stderr
tests/typecheck/should_compile/tc161.stderr-ghc
tests/typecheck/should_compile/tc167.stderr
tests/typecheck/should_compile/tc168.stderr
tests/typecheck/should_compile/tc175.stderr
tests/typecheck/should_compile/tc182.stderr
tests/typecheck/should_compile/tc211.stderr
tests/typecheck/should_compile/tc243.stderr
tests/typecheck/should_compile/tc254.stderr
tests/typecheck/should_fail/AssocTyDef01.stderr
tests/typecheck/should_fail/AssocTyDef02.stderr
tests/typecheck/should_fail/AssocTyDef03.stderr
tests/typecheck/should_fail/AssocTyDef04.stderr
tests/typecheck/should_fail/AssocTyDef05.stderr
tests/typecheck/should_fail/AssocTyDef06.stderr
tests/typecheck/should_fail/AssocTyDef07.stderr
tests/typecheck/should_fail/AssocTyDef08.stderr
tests/typecheck/should_fail/AssocTyDef09.stderr
tests/typecheck/should_fail/ContextStack1.stderr
tests/typecheck/should_fail/ContextStack2.stderr
tests/typecheck/should_fail/FDsFromGivens.stderr
tests/typecheck/should_fail/FailDueToGivenOverlapping.stderr
tests/typecheck/should_fail/FrozenErrorTests.stderr
tests/typecheck/should_fail/IPFail.stderr
tests/typecheck/should_fail/LongWayOverlapping.stderr
tests/typecheck/should_fail/SCLoop.stderr
tests/typecheck/should_fail/T1595.stderr
tests/typecheck/should_fail/T1633.stderr
tests/typecheck/should_fail/T1897a.stderr
tests/typecheck/should_fail/T1899.stderr
tests/typecheck/should_fail/T2126.stderr
tests/typecheck/should_fail/T2247.stderr
tests/typecheck/should_fail/T2307.stderr
tests/typecheck/should_fail/T2354.stderr
tests/typecheck/should_fail/T2414.stderr
tests/typecheck/should_fail/T2534.stderr
tests/typecheck/should_fail/T2538.stderr
tests/typecheck/should_fail/T2688.stderr
tests/typecheck/should_fail/T2714.stderr
tests/typecheck/should_fail/T2806.stderr
tests/typecheck/should_fail/T2846b.stderr
tests/typecheck/should_fail/T2994.stderr
tests/typecheck/should_fail/T3102.stderr
tests/typecheck/should_fail/T3155.stderr
tests/typecheck/should_fail/T3176.stderr
tests/typecheck/should_fail/T3323.stderr
tests/typecheck/should_fail/T3406.stderr
tests/typecheck/should_fail/T3468.stderr
tests/typecheck/should_fail/T3540.stderr
tests/typecheck/should_fail/T3592.stderr
tests/typecheck/should_fail/T3613.stderr
tests/typecheck/should_fail/T3950.stderr
tests/typecheck/should_fail/T3966.stderr
tests/typecheck/should_fail/T4875.stderr
tests/typecheck/should_fail/T4921.stderr
tests/typecheck/should_fail/T5051.stderr
tests/typecheck/should_fail/T5084.stderr
tests/typecheck/should_fail/T5095.stderr
tests/typecheck/should_fail/T5236.stderr
tests/typecheck/should_fail/T5246.stderr
tests/typecheck/should_fail/T5300.stderr
tests/typecheck/should_fail/T5570.stderr
tests/typecheck/should_fail/T5684.stderr
tests/typecheck/should_fail/T5689.stderr
tests/typecheck/should_fail/T5691.stderr
tests/typecheck/should_fail/T5853.stderr
tests/typecheck/should_fail/T5858.stderr
tests/typecheck/should_fail/T5957.stderr
tests/typecheck/should_fail/T5978.stderr
tests/typecheck/should_fail/T6001.stderr
tests/typecheck/should_fail/T6022.stderr
tests/typecheck/should_fail/T6069.stderr
tests/typecheck/should_fail/T6078.stderr
tests/typecheck/should_fail/T6161.stderr
tests/typecheck/should_fail/T7019.stderr
tests/typecheck/should_fail/T7019a.stderr
tests/typecheck/should_fail/T7175.stderr
tests/typecheck/should_fail/T7210.stderr
tests/typecheck/should_fail/T7264.stderr
tests/typecheck/should_fail/T7279.stderr
tests/typecheck/should_fail/T7368.stderr
tests/typecheck/should_fail/T7368a.stderr
tests/typecheck/should_fail/T7410.stderr
tests/typecheck/should_fail/T7453.stderr
tests/typecheck/should_fail/T7525.stderr
tests/typecheck/should_fail/T7609.stderr
tests/typecheck/should_fail/T7645.stderr
tests/typecheck/should_fail/T7696.stderr
tests/typecheck/should_fail/T7697.stderr
tests/typecheck/should_fail/T7734.stderr
tests/typecheck/should_fail/T7748a.stderr
tests/typecheck/should_fail/T7778.stderr
tests/typecheck/should_fail/T7809.stderr
tests/typecheck/should_fail/T7851.stderr
tests/typecheck/should_fail/T7856.stderr
tests/typecheck/should_fail/T7857.stderr
tests/typecheck/should_fail/T7869.stderr
tests/typecheck/should_fail/T7892.stderr
tests/typecheck/should_fail/T7989.stderr
tests/typecheck/should_fail/T8044.stderr
tests/typecheck/should_fail/T8142.stderr
tests/typecheck/should_fail/T8262.stderr
tests/typecheck/should_fail/T8306.stderr
tests/typecheck/should_fail/T8392a.stderr
tests/typecheck/should_fail/T8428.stderr
tests/typecheck/should_fail/T8450.stderr
tests/typecheck/should_fail/T8514.stderr
tests/typecheck/should_fail/T8570.stderr
tests/typecheck/should_fail/T8603.stderr
tests/typecheck/should_fail/T8806.stderr
tests/typecheck/should_fail/T8883.stderr
tests/typecheck/should_fail/T8912.stderr
tests/typecheck/should_fail/T9033.stderr
tests/typecheck/should_fail/T9109.stderr
tests/typecheck/should_fail/T9196.stderr
tests/typecheck/should_fail/T9201.stderr
tests/typecheck/should_fail/T9305.stderr
tests/typecheck/should_fail/T9318.stderr
tests/typecheck/should_fail/T9323.stderr
tests/typecheck/should_fail/T9415.stderr
tests/typecheck/should_fail/T9497d.stderr
tests/typecheck/should_fail/T9605.stderr
tests/typecheck/should_fail/T9612.stderr
tests/typecheck/should_fail/T9634.stderr
tests/typecheck/should_fail/T9739.stderr
tests/typecheck/should_fail/T9774.stderr
tests/typecheck/should_fail/TcCoercibleFail.stderr
tests/typecheck/should_fail/TcCoercibleFail2.stderr
tests/typecheck/should_fail/TcCoercibleFail3.stderr
tests/typecheck/should_fail/TcMultiWayIfFail.stderr
tests/typecheck/should_fail/TcNoNullaryTC.stderr
tests/typecheck/should_fail/TcNullaryTCFail.stderr
tests/typecheck/should_fail/TcStaticPointersFail01.stderr
tests/typecheck/should_fail/TcStaticPointersFail02.stderr
tests/typecheck/should_fail/TcStaticPointersFail03.stderr
tests/typecheck/should_fail/fd-loop.stderr
tests/typecheck/should_fail/mc19.stderr
tests/typecheck/should_fail/mc20.stderr
tests/typecheck/should_fail/mc21.stderr
tests/typecheck/should_fail/mc22.stderr
tests/typecheck/should_fail/mc23.stderr
tests/typecheck/should_fail/mc24.stderr
tests/typecheck/should_fail/mc25.stderr
tests/typecheck/should_fail/tcfail001.stderr
tests/typecheck/should_fail/tcfail002.stderr
tests/typecheck/should_fail/tcfail003.stderr
tests/typecheck/should_fail/tcfail004.stderr
tests/typecheck/should_fail/tcfail005.stderr
tests/typecheck/should_fail/tcfail006.stderr
tests/typecheck/should_fail/tcfail007.stderr
tests/typecheck/should_fail/tcfail008.stderr
tests/typecheck/should_fail/tcfail009.stderr
tests/typecheck/should_fail/tcfail010.stderr
tests/typecheck/should_fail/tcfail011.stderr
tests/typecheck/should_fail/tcfail012.stderr
tests/typecheck/should_fail/tcfail013.stderr
tests/typecheck/should_fail/tcfail014.stderr
tests/typecheck/should_fail/tcfail015.stderr
tests/typecheck/should_fail/tcfail016.stderr
tests/typecheck/should_fail/tcfail017.stderr
tests/typecheck/should_fail/tcfail018.stderr
tests/typecheck/should_fail/tcfail019.stderr
tests/typecheck/should_fail/tcfail020.stderr
tests/typecheck/should_fail/tcfail021.stderr
tests/typecheck/should_fail/tcfail023.stderr
tests/typecheck/should_fail/tcfail027.stderr
tests/typecheck/should_fail/tcfail028.stderr
tests/typecheck/should_fail/tcfail029.stderr
tests/typecheck/should_fail/tcfail030.stderr
tests/typecheck/should_fail/tcfail031.stderr
tests/typecheck/should_fail/tcfail032.stderr
tests/typecheck/should_fail/tcfail033.stderr
tests/typecheck/should_fail/tcfail034.stderr
tests/typecheck/should_fail/tcfail035.stderr
tests/typecheck/should_fail/tcfail036.stderr
tests/typecheck/should_fail/tcfail037.stderr
tests/typecheck/should_fail/tcfail038.stderr
tests/typecheck/should_fail/tcfail040.stderr
tests/typecheck/should_fail/tcfail041.stderr
tests/typecheck/should_fail/tcfail042.stderr
tests/typecheck/should_fail/tcfail043.stderr
tests/typecheck/should_fail/tcfail044.stderr
tests/typecheck/should_fail/tcfail046.stderr
tests/typecheck/should_fail/tcfail047.stderr
tests/typecheck/should_fail/tcfail048.stderr
tests/typecheck/should_fail/tcfail049.stderr
tests/typecheck/should_fail/tcfail050.stderr
tests/typecheck/should_fail/tcfail051.stderr
tests/typecheck/should_fail/tcfail052.stderr
tests/typecheck/should_fail/tcfail053.stderr
tests/typecheck/should_fail/tcfail054.stderr
tests/typecheck/should_fail/tcfail055.stderr
tests/typecheck/should_fail/tcfail056.stderr
tests/typecheck/should_fail/tcfail057.stderr
tests/typecheck/should_fail/tcfail058.stderr
tests/typecheck/should_fail/tcfail061.stderr
tests/typecheck/should_fail/tcfail062.stderr
tests/typecheck/should_fail/tcfail063.stderr
tests/typecheck/should_fail/tcfail065.stderr
tests/typecheck/should_fail/tcfail067.stderr
tests/typecheck/should_fail/tcfail068.stderr
tests/typecheck/should_fail/tcfail069.stderr
tests/typecheck/should_fail/tcfail070.stderr
tests/typecheck/should_fail/tcfail072.stderr
tests/typecheck/should_fail/tcfail073.stderr
tests/typecheck/should_fail/tcfail075.stderr
tests/typecheck/should_fail/tcfail076.stderr
tests/typecheck/should_fail/tcfail077.stderr
tests/typecheck/should_fail/tcfail078.stderr
tests/typecheck/should_fail/tcfail079.stderr
tests/typecheck/should_fail/tcfail080.stderr
tests/typecheck/should_fail/tcfail082.stderr
tests/typecheck/should_fail/tcfail083.stderr
tests/typecheck/should_fail/tcfail084.stderr
tests/typecheck/should_fail/tcfail085.stderr
tests/typecheck/should_fail/tcfail086.stderr
tests/typecheck/should_fail/tcfail088.stderr
tests/typecheck/should_fail/tcfail089.stderr
tests/typecheck/should_fail/tcfail090.stderr
tests/typecheck/should_fail/tcfail092.stderr
tests/typecheck/should_fail/tcfail094.stderr
tests/typecheck/should_fail/tcfail095.stderr
tests/typecheck/should_fail/tcfail096.stderr
tests/typecheck/should_fail/tcfail097.stderr
tests/typecheck/should_fail/tcfail098.stderr
tests/typecheck/should_fail/tcfail099.stderr
tests/typecheck/should_fail/tcfail100.stderr
tests/typecheck/should_fail/tcfail101.stderr
tests/typecheck/should_fail/tcfail102.stderr
tests/typecheck/should_fail/tcfail103.stderr
tests/typecheck/should_fail/tcfail104.stderr
tests/typecheck/should_fail/tcfail106.stderr
tests/typecheck/should_fail/tcfail107.stderr
tests/typecheck/should_fail/tcfail108.stderr
tests/typecheck/should_fail/tcfail109.stderr
tests/typecheck/should_fail/tcfail110.stderr
tests/typecheck/should_fail/tcfail112.stderr
tests/typecheck/should_fail/tcfail113.stderr
tests/typecheck/should_fail/tcfail114.stderr
tests/typecheck/should_fail/tcfail116.stderr
tests/typecheck/should_fail/tcfail117.stderr
tests/typecheck/should_fail/tcfail118.stderr
tests/typecheck/should_fail/tcfail119.stderr
tests/typecheck/should_fail/tcfail121.stderr
tests/typecheck/should_fail/tcfail122.stderr
tests/typecheck/should_fail/tcfail123.stderr
tests/typecheck/should_fail/tcfail125.stderr
tests/typecheck/should_fail/tcfail127.stderr
tests/typecheck/should_fail/tcfail128.stderr
tests/typecheck/should_fail/tcfail129.stderr
tests/typecheck/should_fail/tcfail130.stderr
tests/typecheck/should_fail/tcfail131.stderr
tests/typecheck/should_fail/tcfail132.stderr
tests/typecheck/should_fail/tcfail133.stderr
tests/typecheck/should_fail/tcfail134.stderr
tests/typecheck/should_fail/tcfail135.stderr
tests/typecheck/should_fail/tcfail136.stderr
tests/typecheck/should_fail/tcfail137.stderr
tests/typecheck/should_fail/tcfail139.stderr
tests/typecheck/should_fail/tcfail140.stderr
tests/typecheck/should_fail/tcfail142.stderr
tests/typecheck/should_fail/tcfail143.stderr
tests/typecheck/should_fail/tcfail146.stderr
tests/typecheck/should_fail/tcfail147.stderr
tests/typecheck/should_fail/tcfail148.stderr
tests/typecheck/should_fail/tcfail151.stderr
tests/typecheck/should_fail/tcfail152.stderr
tests/typecheck/should_fail/tcfail153.stderr
tests/typecheck/should_fail/tcfail154.stderr
tests/typecheck/should_fail/tcfail155.stderr
tests/typecheck/should_fail/tcfail156.stderr
tests/typecheck/should_fail/tcfail157.stderr
tests/typecheck/should_fail/tcfail158.stderr
tests/typecheck/should_fail/tcfail159.stderr
tests/typecheck/should_fail/tcfail160.stderr
tests/typecheck/should_fail/tcfail161.stderr
tests/typecheck/should_fail/tcfail162.stderr
tests/typecheck/should_fail/tcfail164.stderr
tests/typecheck/should_fail/tcfail165.stderr
tests/typecheck/should_fail/tcfail166.stderr
tests/typecheck/should_fail/tcfail167.stderr
tests/typecheck/should_fail/tcfail168.stderr
tests/typecheck/should_fail/tcfail169.stderr
tests/typecheck/should_fail/tcfail170.stderr
tests/typecheck/should_fail/tcfail171.stderr
tests/typecheck/should_fail/tcfail173.stderr
tests/typecheck/should_fail/tcfail174.stderr
tests/typecheck/should_fail/tcfail175.stderr
tests/typecheck/should_fail/tcfail176.stderr
tests/typecheck/should_fail/tcfail177.stderr
tests/typecheck/should_fail/tcfail178.stderr
tests/typecheck/should_fail/tcfail179.stderr
tests/typecheck/should_fail/tcfail180.stderr
tests/typecheck/should_fail/tcfail181.stderr
tests/typecheck/should_fail/tcfail182.stderr
tests/typecheck/should_fail/tcfail183.stderr
tests/typecheck/should_fail/tcfail184.stderr
tests/typecheck/should_fail/tcfail185.stderr
tests/typecheck/should_fail/tcfail186.stderr
tests/typecheck/should_fail/tcfail187.stderr
tests/typecheck/should_fail/tcfail189.stderr
tests/typecheck/should_fail/tcfail190.stderr
tests/typecheck/should_fail/tcfail191.stderr
tests/typecheck/should_fail/tcfail193.stderr
tests/typecheck/should_fail/tcfail195.stderr
tests/typecheck/should_fail/tcfail196.stderr
tests/typecheck/should_fail/tcfail197.stderr
tests/typecheck/should_fail/tcfail198.stderr
tests/typecheck/should_fail/tcfail199.stderr
tests/typecheck/should_fail/tcfail200.stderr
tests/typecheck/should_fail/tcfail201.stderr
tests/typecheck/should_fail/tcfail202.stderr
tests/typecheck/should_fail/tcfail203.stderr
tests/typecheck/should_fail/tcfail203a.stderr
tests/typecheck/should_fail/tcfail204.stderr
tests/typecheck/should_fail/tcfail206.stderr
tests/typecheck/should_fail/tcfail207.stderr
tests/typecheck/should_fail/tcfail208.stderr
tests/typecheck/should_fail/tcfail209.stderr
tests/typecheck/should_fail/tcfail209a.stderr
tests/typecheck/should_fail/tcfail210.stderr
tests/typecheck/should_fail/tcfail211.stderr
tests/typecheck/should_fail/tcfail212.stderr
tests/typecheck/should_fail/tcfail213.stderr
tests/typecheck/should_fail/tcfail214.stderr
tests/typecheck/should_fail/tcfail215.stderr
tests/typecheck/should_fail/tcfail216.stderr
tests/typecheck/should_fail/tcfail217.stderr
tests/typecheck/should_fail/tcfail218.stderr
tests/typecheck/should_fail/tcfail219.stderr
tests/typecheck/should_fail/tcfail220.stderr
tests/typecheck/should_fail/tcfail221.stderr
tests/typecheck/should_fail/tcfail222.stderr
tests/warnings/minimal/WarnMinimal.stderr
tests/warnings/minimal/WarnMinimalFail1.stderr
tests/warnings/minimal/WarnMinimalFail2.stderr
tests/warnings/minimal/WarnMinimalFail3.stderr
tests/warnings/should_compile/T2526.stderr
tests/warnings/should_compile/T9178.stderr
tests/warnings/should_compile/T9230.stderr|]
-- Cases that were not covered by this script:
-- modified: ../compiler/main/ErrUtils.hs
-- modified: tests/annotations/should_fail/annfail13.stderr
-- modified: tests/arrows/should_fail/arrowfail002.stderr
-- modified: tests/cabal/cabal07/cabal07.stderr
-- modified: tests/deSugar/should_compile/T4488.stderr
-- modified: tests/deSugar/should_compile/T5455.stderr
-- modified: tests/deSugar/should_compile/ds043.stderr-ghc
-- modified: tests/deSugar/should_compile/ds058.stderr
-- modified: tests/deriving/should_compile/T4325.stderr
-- modified: tests/deriving/should_compile/drv-foldable-traversable1.stderr
-- modified: tests/deriving/should_compile/drv-functor1.stderr
-- modified: tests/deriving/should_fail/T4846.stderr
-- modified: tests/deriving/should_fail/drvfail011.stderr
-- modified: tests/driver/T1372/T1372.stderr
-- modified: tests/driver/T2464.stderr
-- modified: tests/driver/T2499.stderr
-- modified: tests/driver/retc001/retc001.stderr
-- modified: tests/ffi/should_compile/T1357.stderr
-- modified: tests/ffi/should_fail/ccall_value.stderr
-- modified: tests/ghci.debugger/scripts/break019.stderr
-- modified: tests/ghci/prog009/ghci.prog009.stderr
-- modified: tests/ghci/prog012/prog012.stderr
-- modified: tests/ghci/scripts/T2452.stderr
-- modified: tests/ghci/scripts/T2816.stderr
-- modified: tests/ghci/scripts/T5979.stderr
-- modified: tests/ghci/scripts/T7894.stderr
-- modified: tests/ghci/scripts/ghci021.stderr
-- modified: tests/ghci/scripts/ghci034.stderr
-- modified: tests/ghci/scripts/ghci036.stderr
-- modified: tests/ghci/scripts/ghci038.stderr
-- modified: tests/ghci/should_run/T9915.stderr
-- modified: tests/haddock/should_fail_flag_haddock/haddockE004.stderr
-- modified: tests/indexed-types/should_compile/T3418.stderr
-- modified: tests/indexed-types/should_fail/T4179.stderr
-- modified: tests/indexed-types/should_fail/T5439.stderr
-- modified: tests/module/T414.stderr
-- modified: tests/module/mod10.stderr
-- modified: tests/module/mod114.stderr
-- modified: tests/module/mod116.stderr
-- modified: tests/module/mod120.stderr
-- modified: tests/module/mod122.stderr
-- modified: tests/module/mod123.stderr
-- modified: tests/module/mod124.stderr
-- modified: tests/module/mod125.stderr
-- modified: tests/module/mod126.stderr
-- modified: tests/module/mod127.stderr
-- modified: tests/module/mod130.stderr
-- modified: tests/module/mod135.stderr
-- modified: tests/module/mod138.stderr
-- modified: tests/module/mod147.stderr
-- modified: tests/module/mod158.stderr
-- modified: tests/module/mod161.stderr
-- modified: tests/module/mod25.stderr
-- modified: tests/module/mod26.stderr
-- modified: tests/module/mod29.stderr
-- modified: tests/module/mod36.stderr
-- modified: tests/module/mod48.stderr
-- modified: tests/module/mod49.stderr
-- modified: tests/module/mod50.stderr
-- modified: tests/module/mod58.stderr
-- modified: tests/module/mod59.stderr
-- modified: tests/module/mod62.stderr
-- modified: tests/module/mod69.stderr
-- modified: tests/module/mod7.stderr
-- modified: tests/module/mod70.stderr
-- modified: tests/module/mod72.stderr
-- modified: tests/module/mod73.stderr
-- modified: tests/module/mod74.stderr
-- modified: tests/module/mod76.stderr
-- modified: tests/module/mod79.stderr
-- modified: tests/module/mod8.stderr
-- modified: tests/module/mod80.stderr
-- modified: tests/module/mod87.stderr
-- modified: tests/module/mod88.stderr
-- modified: tests/module/mod89.stderr
-- modified: tests/module/mod9.stderr
-- modified: tests/module/mod97.stderr
-- modified: tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
-- modified: tests/package/package06e.stderr
-- modified: tests/package/package07e.stderr
-- modified: tests/package/package08e.stderr
-- modified: tests/parser/should_compile/read018.stderr
-- modified: tests/parser/should_fail/ExportCommaComma.stderr
-- modified: tests/parser/should_fail/NondecreasingIndentationFail.stderr
-- modified: tests/parser/should_fail/ParserNoLambdaCase.stderr
-- modified: tests/parser/should_fail/T3811c.stderr
-- modified: tests/parser/should_fail/T3811f.stderr
-- modified: tests/parser/should_fail/T8431.stderr
-- modified: tests/parser/should_fail/position001.stderr
-- modified: tests/parser/should_fail/position002.stderr
-- modified: tests/parser/should_fail/readFail001.stderr
-- modified: tests/parser/should_fail/readFail006.stderr
-- modified: tests/parser/should_fail/readFail011.stderr
-- modified: tests/parser/should_fail/readFail012.stderr
-- modified: tests/parser/should_fail/readFail013.stderr
-- modified: tests/parser/should_fail/readFail014.stderr
-- modified: tests/parser/should_fail/readFail015.stderr
-- modified: tests/parser/should_fail/readFail017.stderr
-- modified: tests/parser/should_fail/readFail018.stderr
-- modified: tests/parser/should_fail/readFail019.stderr
-- modified: tests/parser/should_fail/readFail022.stderr
-- modified: tests/parser/should_fail/readFail024.stderr
-- modified: tests/parser/should_fail/readFail026.stderr
-- modified: tests/parser/should_fail/readFail027.stderr
-- modified: tests/parser/should_fail/readFail030.stderr
-- modified: tests/parser/should_fail/readFail034.stderr
-- modified: tests/parser/should_fail/readFail042.stderr
-- modified: tests/parser/should_fail/readFail043.stderr
-- modified: tests/parser/should_fail/readFail047.stderr
-- modified: tests/parser/unicode/T2302.stderr
-- modified: tests/parser/unicode/utf8_002.stderr
-- modified: tests/parser/unicode/utf8_003.stderr
-- modified: tests/parser/unicode/utf8_004.stderr
-- modified: tests/parser/unicode/utf8_005.stderr
-- modified: tests/profiling/should_fail/proffail001.stderr
-- modified: tests/programs/hs-boot/hs-boot.stderr
-- modified: tests/quasiquotation/T3953.stderr
-- modified: tests/quasiquotation/T5204.stderr
-- modified: tests/rename/prog002/rename.prog002.stderr
-- modified: tests/rename/prog003/rename.prog003.stderr
-- modified: tests/rename/should_compile/T9778.stderr
-- modified: tests/rename/should_fail/RnStaticPointersFail02.stderr
-- modified: tests/rename/should_fail/T1595a.stderr
-- modified: tests/rename/should_fail/T2901.stderr
-- modified: tests/rename/should_fail/T3792.stderr
-- modified: tests/rename/should_fail/T5372.stderr
-- modified: tests/rename/should_fail/T5513.stderr
-- modified: tests/rename/should_fail/T5657.stderr
-- modified: tests/rename/should_fail/T5745.stderr
-- modified: tests/rename/should_fail/T5892b.stderr
-- modified: tests/rename/should_fail/T5951.stderr
-- modified: tests/rename/should_fail/T7943.stderr
-- modified: tests/rename/should_fail/T8448.stderr
-- modified: tests/rename/should_fail/T9006.stderr
-- modified: tests/rename/should_fail/T9032.stderr
-- modified: tests/rename/should_fail/T9077.stderr
-- modified: tests/rename/should_fail/T9437.stderr
-- modified: tests/rename/should_fail/mc13.stderr
-- modified: tests/rename/should_fail/mc14.stderr
-- modified: tests/rename/should_fail/rnfail008.stderr
-- modified: tests/rename/should_fail/rnfail016.stderr
-- modified: tests/rename/should_fail/rnfail018.stderr
-- modified: tests/rename/should_fail/rnfail021.stderr
-- modified: tests/rename/should_fail/rnfail024.stderr
-- modified: tests/rename/should_fail/rnfail028.stderr
-- modified: tests/rename/should_fail/rnfail030.stderr
-- modified: tests/rename/should_fail/rnfail031.stderr
-- modified: tests/rename/should_fail/rnfail034.stderr
-- modified: tests/rename/should_fail/rnfail035.stderr
-- modified: tests/rename/should_fail/rnfail039.stderr
-- modified: tests/rename/should_fail/rnfail042.stderr
-- modified: tests/rename/should_fail/rnfail046.stderr
-- modified: tests/rename/should_fail/rnfail049.stderr
-- modified: tests/rename/should_fail/rnfail050.stderr
-- modified: tests/rename/should_fail/rnfail056.stderr
-- modified: tests/roles/should_compile/T8958.stderr
-- modified: tests/safeHaskell/check/Check05.stderr
-- modified: tests/safeHaskell/check/Check09.stderr
-- modified: tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr
-- modified: tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr
-- modified: tests/safeHaskell/check/pkg01/ImpSafeOnly09.stderr
-- modified: tests/safeHaskell/flags/SafeFlags03.stderr
-- modified: tests/safeHaskell/flags/SafeFlags04.stderr
-- modified: tests/safeHaskell/flags/SafeFlags07.stderr
-- modified: tests/safeHaskell/flags/SafeFlags08.stderr
-- modified: tests/safeHaskell/flags/SafeFlags09.stderr
-- modified: tests/safeHaskell/flags/SafeFlags18.stderr
-- modified: tests/safeHaskell/ghci/p10.stderr
-- modified: tests/safeHaskell/ghci/p12.stderr
-- modified: tests/safeHaskell/ghci/p14.stderr
-- modified: tests/safeHaskell/ghci/p16.stderr
-- modified: tests/safeHaskell/ghci/p17.stderr
-- modified: tests/safeHaskell/ghci/p3.stderr
-- modified: tests/safeHaskell/ghci/p4.stderr
-- modified: tests/safeHaskell/ghci/p9.stderr
-- modified: tests/safeHaskell/safeLanguage/SafeLang01.stderr
-- modified: tests/safeHaskell/safeLanguage/SafeLang02.stderr
-- modified: tests/safeHaskell/safeLanguage/SafeLang16.stderr
-- modified: tests/stranal/should_compile/str001.stderr
-- modified: tests/th/T5976.stderr
-- modified: tests/th/T7276.stderr
-- modified: tests/th/T9084.stderr
-- modified: tests/th/TH_exn2.stderr
-- modified: tests/th/TH_fail.stderr
-- modified: tests/th/TH_linePragma.stderr
-- modified: tests/typecheck/should_compile/T2478.stderr
-- modified: tests/typecheck/should_compile/T3696.stderr
-- modified: tests/typecheck/should_compile/T5481.stderr
-- modified: tests/typecheck/should_compile/tc182.stderr
-- modified: tests/typecheck/should_fail/T7892.stderr
-- modified: tests/typecheck/should_fail/tcfail011.stderr
-- modified: tests/typecheck/should_fail/tcfail048.stderr
-- modified: tests/typecheck/should_fail/tcfail049.stderr
-- modified: tests/typecheck/should_fail/tcfail050.stderr
-- modified: tests/typecheck/should_fail/tcfail051.stderr
-- modified: tests/typecheck/should_fail/tcfail052.stderr
-- modified: tests/typecheck/should_fail/tcfail053.stderr
-- modified: tests/typecheck/should_fail/tcfail054.stderr
-- modified: tests/typecheck/should_fail/tcfail056.stderr
-- modified: tests/typecheck/should_fail/tcfail061.stderr
-- modified: tests/typecheck/should_fail/tcfail077.stderr
-- modified: tests/typecheck/should_fail/tcfail089.stderr
-- modified: tests/typecheck/should_fail/tcfail201.stderr
-- modified: tests/typecheck/should_fail/tcfail206.stderr
-- modified: tests/typecheck/should_fail/tcfail219.stderr
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment