From 2daace0cc31c883d855e19edb034f18714038641 Mon Sep 17 00:00:00 2001 From: Artin Ghasivand <ghasivand.artin@gmail.com> Date: Sat, 15 Mar 2025 12:55:44 +0330 Subject: [PATCH] Retain literal values when translating, use Integer instead of Int --- typechecker/src/Initial.hs | 10 +++++----- typechecker/src/Parser.hs | 8 ++++---- typechecker/src/Tc/Gen/Expr.hs | 6 +++--- typechecker/src/Tc/Solver.hs | 6 +++--- typechecker/src/Term.hs | 6 +++--- typechecker/src/Type.hs | 12 ++++++------ .../test/cases/parser/leftPlusTwo-parser.output | 2 +- typechecker/test/cases/parser/plusPlus-parser.output | 2 +- .../test/cases/should-fail/constFail-infer.output | 2 +- .../test/cases/should-fail/notTo3-infer.output | 2 +- .../test/cases/should-fail/plus3ToBool-infer.output | 2 +- .../test/cases/should-typecheck/Just-3-tuple-pb.hs | 2 +- .../cases/should-typecheck/Just-3-tuple-pb.output | 2 +- .../test/cases/should-typecheck/JustXfmap.output | 2 +- typechecker/test/cases/should-typecheck/absMaybe.hs | 2 +- .../test/cases/should-typecheck/absMaybe.output | 2 +- .../test/cases/should-typecheck/absMaybeMaybe.hs | 2 +- .../test/cases/should-typecheck/absMaybeMaybe.output | 2 +- .../test/cases/should-typecheck/apply-infer.output | 2 +- .../should-typecheck/ifTrueThenPlusTwo-infer.output | 2 +- .../test/cases/should-typecheck/inParenSig.hs | 2 +- .../test/cases/should-typecheck/inParenSig.output | 2 +- .../should-typecheck/int-functions-infer.output | 6 +++--- .../test/cases/should-typecheck/intToBool-check.hs | 2 +- .../cases/should-typecheck/intToBool-check.output | 2 +- .../cases/should-typecheck/intToBool-infer.output | 2 +- .../test/cases/should-typecheck/myConst-required.hs | 4 ++-- .../cases/should-typecheck/myConst-required.output | 4 ++-- .../should-typecheck/plusNineLambda-infer.output | 2 +- typechecker/test/cases/should-typecheck/silly1.hs | 2 +- .../test/cases/should-typecheck/silly1.output | 2 +- .../test/cases/should-typecheck/tyAbsCaseIllegal.hs | 2 +- .../test/cases/should-typecheck/tyAbsCaseLegal.hs | 2 +- .../cases/should-typecheck/tyAbsCaseLegal.output | 2 +- .../unwrapMaybeAndEither-infer.output | 4 ++-- typechecker/test/cases/should-typecheck/weirdDecl.hs | 4 ++-- .../test/cases/should-typecheck/weirdDecl.output | 2 +- typechecker/test/other/Rep.hs | 2 +- 38 files changed, 62 insertions(+), 62 deletions(-) diff --git a/typechecker/src/Initial.hs b/typechecker/src/Initial.hs index ee9acb8..3e3c9ac 100644 --- a/typechecker/src/Initial.hs +++ b/typechecker/src/Initial.hs @@ -41,8 +41,8 @@ initialTyCons = do ,(ttFoldableCt, (tyConFoldableCt, appArrowTS [typeTau, typeTau] constraintTau)) -- Foldable ,(ttArrow, (tyConArrow, appArrowTS [typeTau, typeTau] typeTau)) -- (->) ,(ttList, (tyConList, typeToTypeSigma)) -- List - ,(ttChar, (tyConChar, typeSigma)) -- Char - ,(ttInt, (tyConInt, typeSigma)) -- Int + ,(ttChar, (tyConChar, typeSigma)) -- Char + ,(ttInt, (tyConInteger, typeSigma)) -- Integer ,(ttNat, (tyConNat, typeSigma)) ,(ttBool, (tyConBool, typeSigma)) -- Bool ,(ttString, (tyConString, typeSigma)) -- String @@ -299,7 +299,7 @@ undefinedBD = do ((tauToSigma (AlphaT al)))) plusBD :: (TVar, Sigma) -plusBD = (mkTVar "plus", tauToSigma $ appArrowT [intTau, intTau] intTau) +plusBD = (mkTVar "plus", tauToSigma $ appArrowT [integerTau, integerTau] integerTau) constBD :: Tc (TVar, Sigma) constBD = do @@ -325,7 +325,7 @@ minusBD = do appPsiSigmas [Specified (al, typeSigma), FatArrow (AppT numCtQ (AlphaT al))] . tauToSigma $ appArrowT [AlphaT al, AlphaT al] (AlphaT al)) minusIntBD :: (TVar, Sigma) -minusIntBD = (mkTVar "minusInt", tauToSigma $ appArrowT [intTau, intTau] intTau) +minusIntBD = (mkTVar "minusInt", tauToSigma $ appArrowT [integerTau, integerTau] integerTau) takeBD :: Tc (TVar, Sigma) takeBD = do @@ -333,7 +333,7 @@ takeBD = do let listOfAl = AppT listTau (AlphaT al) pure (mkTVar "take", QuantifiedSg (Specified (al, tauToSigma typeTau)) . tauToSigma - $ appArrowT [intTau, listOfAl] listOfAl) + $ appArrowT [integerTau, listOfAl] listOfAl) singletonBD :: Tc (TVar, Sigma) singletonBD = do diff --git a/typechecker/src/Parser.hs b/typechecker/src/Parser.hs index a19b2d9..46766a7 100644 --- a/typechecker/src/Parser.hs +++ b/typechecker/src/Parser.hs @@ -60,10 +60,10 @@ caseArmToMatch (pat, E.EAlts alts _) = <*> (toTerm =<< rhs) toLit :: E.Lit -> Either String Lit -toLit (E.LInt _) = Right LitInt -toLit (E.LInteger _) = Right LitInt -toLit (E.LStr _) = Right LitString -toLit (E.LChar _) = Right LitChar +toLit (E.LInt v) = Right (LitInteger (toInteger v)) +toLit (E.LInteger v) = Right (LitInteger v) +toLit (E.LStr v) = Right (LitString v) +toLit (E.LChar v) = Right (LitChar v) toLit _ = Left "Unsupported literal!" toValDecls :: [E.EBind] -> Either String ValDecls diff --git a/typechecker/src/Tc/Gen/Expr.hs b/typechecker/src/Tc/Gen/Expr.hs index d4a555d..46d7b18 100644 --- a/typechecker/src/Tc/Gen/Expr.hs +++ b/typechecker/src/Tc/Gen/Expr.hs @@ -180,9 +180,9 @@ tcArg gamma expr sigma = do ********************************************************************* -} litType :: Lit -> Tau -litType LitChar = chatTau -litType LitInt = intTau -litType LitString = stringTau +litType (LitChar _) = chatTau +litType (LitInteger _) = integerTau +litType (LitString _) = stringTau tcLit :: Lit -> ExpType -> Tc () tcLit lit (Infer ires) = fillInferResult (tauToRho $ litType lit) ires diff --git a/typechecker/src/Tc/Solver.hs b/typechecker/src/Tc/Solver.hs index 5db77bb..089ef8d 100644 --- a/typechecker/src/Tc/Solver.hs +++ b/typechecker/src/Tc/Solver.hs @@ -226,8 +226,8 @@ tryInertEqs :: CanEqCt -> Cs () tryInertEqs _ = pure () -- TODO: Fix me -- TODO: Fix me -solveIrred :: CanIrredCt -> Cs () -solveIrred ir = throwErrorCs (IrreducibleCt $ pprCanIrredCt ir) +solveCanIrredCt :: CanIrredCt -> Cs () +solveCanIrredCt ir = throwErrorCs (IrreducibleCt $ pprCanIrredCt ir) solveEquality :: CtFlavour -> TcTau -> TcTau -> Cs () solveEquality flv lhs rhs = do @@ -239,6 +239,6 @@ solveEquality flv lhs rhs = do traceCs "solveEquality - constraints" $ vsep [pretty "Canonicals:" <+> pprList (vsep . map pprCanEqCt) canons ,pretty "Irreducibles:" <+> pprList (vsep . map pprCanIrredCt) irreds] - mapM_ solveIrred irreds + mapM_ solveCanIrredCt irreds mapM_ tryInertEqs canons mapM_ updInertEqs canons diff --git a/typechecker/src/Term.hs b/typechecker/src/Term.hs index 0e4e3fa..0229109 100644 --- a/typechecker/src/Term.hs +++ b/typechecker/src/Term.hs @@ -111,9 +111,9 @@ data Binder -- Literals data Lit - = LitChar -- Character literal - | LitInt -- Int literal - | LitString -- String literal + = LitChar Char -- Character literal + | LitInteger Integer -- Integer literal + | LitString String -- String literal deriving (Show, Eq) data TVar = MkTVar Ident -- A term varible diff --git a/typechecker/src/Type.hs b/typechecker/src/Type.hs index b89611e..3a838dc 100644 --- a/typechecker/src/Type.hs +++ b/typechecker/src/Type.hs @@ -36,7 +36,7 @@ module Type( typeTau, showCtQ, foldableCtQ, - intTau, + integerTau, natTau, maybeTau, eitherTau, @@ -147,7 +147,7 @@ module Type( tyConEither, tyConEqCt, tyConFoldableCt, - tyConInt, + tyConInteger, tyConNat, tyConList, tyConMaybe, @@ -924,8 +924,8 @@ constraintTau = TyConT tyConConstraint arrowTau :: Tau arrowTau = TyConT tyConArrow -intTau :: Tau -intTau = TyConT tyConInt +integerTau :: Tau +integerTau = TyConT tyConInteger natTau :: Tau natTau = TyConT tyConNat @@ -1004,8 +1004,8 @@ tyConFoldableCt = MkTyCon (pack "Foldable") tyConNumCt :: TyCon tyConNumCt = MkTyCon (pack "Num") -tyConInt :: TyCon -tyConInt = MkTyCon (pack "Int") +tyConInteger :: TyCon +tyConInteger = MkTyCon (pack "Integer") tyConNat :: TyCon tyConNat = MkTyCon (pack "Nat") diff --git a/typechecker/test/cases/parser/leftPlusTwo-parser.output b/typechecker/test/cases/parser/leftPlusTwo-parser.output index 7e9e31b..57598d7 100644 --- a/typechecker/test/cases/parser/leftPlusTwo-parser.output +++ b/typechecker/test/cases/parser/leftPlusTwo-parser.output @@ -1 +1 @@ -MkValDecls [] [FunBind (MkTVar leftPlusTwo) [MkMatch [VisArg (TApp (HVar (MkTVar x)) [])] (TApp (HConLike (MkConLike Left)) [VisArg (TApp (HVar (MkTVar plus)) [VisArg (TLit LitInt),VisArg (TApp (HVar (MkTVar x)) [])])])]] \ No newline at end of file +MkValDecls [] [FunBind (MkTVar leftPlusTwo) [MkMatch [VisArg (TApp (HVar (MkTVar x)) [])] (TApp (HConLike (MkConLike Left)) [VisArg (TApp (HVar (MkTVar plus)) [VisArg (TLit (LitInteger 2)),VisArg (TApp (HVar (MkTVar x)) [])])])]] \ No newline at end of file diff --git a/typechecker/test/cases/parser/plusPlus-parser.output b/typechecker/test/cases/parser/plusPlus-parser.output index ab5a13c..e23c8b8 100644 --- a/typechecker/test/cases/parser/plusPlus-parser.output +++ b/typechecker/test/cases/parser/plusPlus-parser.output @@ -1 +1 @@ -MkValDecls [] [FunBind (MkTVar plusPlus) [MkMatch [] (TApp (HVar (MkTVar plus)) [VisArg (TApp (HVar (MkTVar plus)) [VisArg (TLit LitInt),VisArg (TLit LitInt)]),VisArg (TApp (HVar (MkTVar plus)) [VisArg (TLit LitInt),VisArg (TLit LitInt)])])]] \ No newline at end of file +MkValDecls [] [FunBind (MkTVar plusPlus) [MkMatch [] (TApp (HVar (MkTVar plus)) [VisArg (TApp (HVar (MkTVar plus)) [VisArg (TLit (LitInteger 3)),VisArg (TLit (LitInteger 2))]),VisArg (TApp (HVar (MkTVar plus)) [VisArg (TLit (LitInteger 1)),VisArg (TLit (LitInteger 3))])])]] \ No newline at end of file diff --git a/typechecker/test/cases/should-fail/constFail-infer.output b/typechecker/test/cases/should-fail/constFail-infer.output index 17d9297..2e6a537 100644 --- a/typechecker/test/cases/should-fail/constFail-infer.output +++ b/typechecker/test/cases/should-fail/constFail-infer.output @@ -2,4 +2,4 @@ Expected no more arguments: Instantiated type of application head: Bool - Left over arguments: [VisArg (TLit LitChar)] \ No newline at end of file + Left over arguments: [VisArg (TLit (LitChar 'c'))] \ No newline at end of file diff --git a/typechecker/test/cases/should-fail/notTo3-infer.output b/typechecker/test/cases/should-fail/notTo3-infer.output index 92636c3..84b965a 100644 --- a/typechecker/test/cases/should-fail/notTo3-infer.output +++ b/typechecker/test/cases/should-fail/notTo3-infer.output @@ -1,3 +1,3 @@ [DifferentTyCons] -Can't unify different type constructors: Bool and Int \ No newline at end of file +Can't unify different type constructors: Bool and Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-fail/plus3ToBool-infer.output b/typechecker/test/cases/should-fail/plus3ToBool-infer.output index f0c2a6e..d4d5bc8 100644 --- a/typechecker/test/cases/should-fail/plus3ToBool-infer.output +++ b/typechecker/test/cases/should-fail/plus3ToBool-infer.output @@ -1,3 +1,3 @@ [DifferentTyCons] -Can't unify different type constructors: Int and Bool \ No newline at end of file +Can't unify different type constructors: Integer and Bool \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.hs b/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.hs index a7e78e4..c26c7ed 100644 --- a/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.hs +++ b/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.hs @@ -1,6 +1,6 @@ x :: forall a. a -> a y :: Double -z :: Bool -> Either Bool Int +z :: Bool -> Either Bool Integer Just (x, y, z) = pure (fp 1, gp 2, hp 3) where diff --git a/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.output b/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.output index 257a0d3..68ca409 100644 --- a/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.output +++ b/typechecker/test/cases/should-typecheck/Just-3-tuple-pb.output @@ -1,3 +1,3 @@ x : forall a1:Type. a1 -> a1 y : Double -z : Bool -> Either Bool Int \ No newline at end of file +z : Bool -> Either Bool Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/JustXfmap.output b/typechecker/test/cases/should-typecheck/JustXfmap.output index 0c794d2..7162fdc 100644 --- a/typechecker/test/cases/should-typecheck/JustXfmap.output +++ b/typechecker/test/cases/should-typecheck/JustXfmap.output @@ -1 +1 @@ -x : Int \ No newline at end of file +x : Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/absMaybe.hs b/typechecker/test/cases/should-typecheck/absMaybe.hs index 11f1ba0..d6468df 100644 --- a/typechecker/test/cases/should-typecheck/absMaybe.hs +++ b/typechecker/test/cases/should-typecheck/absMaybe.hs @@ -1,3 +1,3 @@ -absMaybe :: Maybe Int -> Int +absMaybe :: Maybe Integer -> Integer absMaybe (Just @a x) = x :: a absMaybe Nothing = 0 diff --git a/typechecker/test/cases/should-typecheck/absMaybe.output b/typechecker/test/cases/should-typecheck/absMaybe.output index 24fda04..4ae1fe5 100644 --- a/typechecker/test/cases/should-typecheck/absMaybe.output +++ b/typechecker/test/cases/should-typecheck/absMaybe.output @@ -1 +1 @@ -absMaybe :: Maybe Int -> Int +absMaybe :: Maybe Integer -> Integer diff --git a/typechecker/test/cases/should-typecheck/absMaybeMaybe.hs b/typechecker/test/cases/should-typecheck/absMaybeMaybe.hs index 5e1dfe4..5b9a180 100644 --- a/typechecker/test/cases/should-typecheck/absMaybeMaybe.hs +++ b/typechecker/test/cases/should-typecheck/absMaybeMaybe.hs @@ -1,3 +1,3 @@ -absMaybeMaybe :: Maybe (Maybe Int) -> Maybe Int +absMaybeMaybe :: Maybe (Maybe Integer) -> Maybe Integer absMaybeMaybe (Just @(p q) _) = (Just 1) :: (p q) absMaybeMaybe Nothing = Nothing diff --git a/typechecker/test/cases/should-typecheck/absMaybeMaybe.output b/typechecker/test/cases/should-typecheck/absMaybeMaybe.output index 7296d7a..5a6368a 100644 --- a/typechecker/test/cases/should-typecheck/absMaybeMaybe.output +++ b/typechecker/test/cases/should-typecheck/absMaybeMaybe.output @@ -1 +1 @@ -absMaybeMaybe : Maybe (Maybe Int) -> Maybe Int \ No newline at end of file +absMaybeMaybe : Maybe (Maybe Integer) -> Maybe Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/apply-infer.output b/typechecker/test/cases/should-typecheck/apply-infer.output index 265b513..7a0499d 100644 --- a/typechecker/test/cases/should-typecheck/apply-infer.output +++ b/typechecker/test/cases/should-typecheck/apply-infer.output @@ -1 +1 @@ -apply : forall {a1:Type}. Int -> (a1 -> a1) -> a1 -> a1 \ No newline at end of file +apply : forall {a1:Type}. Integer -> (a1 -> a1) -> a1 -> a1 \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/ifTrueThenPlusTwo-infer.output b/typechecker/test/cases/should-typecheck/ifTrueThenPlusTwo-infer.output index 43c8a58..f051f1b 100644 --- a/typechecker/test/cases/should-typecheck/ifTrueThenPlusTwo-infer.output +++ b/typechecker/test/cases/should-typecheck/ifTrueThenPlusTwo-infer.output @@ -1 +1 @@ -ifTrueThenPlusTwo : Bool -> Int \ No newline at end of file +ifTrueThenPlusTwo : Bool -> Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/inParenSig.hs b/typechecker/test/cases/should-typecheck/inParenSig.hs index 89e7389..3964ae2 100644 --- a/typechecker/test/cases/should-typecheck/inParenSig.hs +++ b/typechecker/test/cases/should-typecheck/inParenSig.hs @@ -1,2 +1,2 @@ -inParenSig :: Int +inParenSig :: Integer (inParenSig) = 3 diff --git a/typechecker/test/cases/should-typecheck/inParenSig.output b/typechecker/test/cases/should-typecheck/inParenSig.output index dec86d6..b2aa20a 100644 --- a/typechecker/test/cases/should-typecheck/inParenSig.output +++ b/typechecker/test/cases/should-typecheck/inParenSig.output @@ -1 +1 @@ -inParenSig : Int \ No newline at end of file +inParenSig : Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/int-functions-infer.output b/typechecker/test/cases/should-typecheck/int-functions-infer.output index a2fa7de..6385cd1 100644 --- a/typechecker/test/cases/should-typecheck/int-functions-infer.output +++ b/typechecker/test/cases/should-typecheck/int-functions-infer.output @@ -1,3 +1,3 @@ -plusTwo : Int -> Int -plusItself : Int -> Int -fourPlusTwos : Int -> Int \ No newline at end of file +plusTwo : Integer -> Integer +plusItself : Integer -> Integer +fourPlusTwos : Integer -> Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/intToBool-check.hs b/typechecker/test/cases/should-typecheck/intToBool-check.hs index 1a4d260..c6bbd2d 100644 --- a/typechecker/test/cases/should-typecheck/intToBool-check.hs +++ b/typechecker/test/cases/should-typecheck/intToBool-check.hs @@ -1,4 +1,4 @@ -intToBool :: Int -> Bool +intToBool :: Integer -> Bool intToBool 1 = True intToBool 0 = False intToBool _ = False diff --git a/typechecker/test/cases/should-typecheck/intToBool-check.output b/typechecker/test/cases/should-typecheck/intToBool-check.output index 85c4815..36896d4 100644 --- a/typechecker/test/cases/should-typecheck/intToBool-check.output +++ b/typechecker/test/cases/should-typecheck/intToBool-check.output @@ -1 +1 @@ -intToBool : Int -> Bool \ No newline at end of file +intToBool : Integer -> Bool \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/intToBool-infer.output b/typechecker/test/cases/should-typecheck/intToBool-infer.output index 85c4815..36896d4 100644 --- a/typechecker/test/cases/should-typecheck/intToBool-infer.output +++ b/typechecker/test/cases/should-typecheck/intToBool-infer.output @@ -1 +1 @@ -intToBool : Int -> Bool \ No newline at end of file +intToBool : Integer -> Bool \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/myConst-required.hs b/typechecker/test/cases/should-typecheck/myConst-required.hs index 7b59f77..be823ee 100644 --- a/typechecker/test/cases/should-typecheck/myConst-required.hs +++ b/typechecker/test/cases/should-typecheck/myConst-required.hs @@ -1,6 +1,6 @@ myConst :: forall a -> forall b -> a -> b -> a myConst p q x y = y :: q -myConstInt = myConst Int +myConstInt = myConst Integer -myConstIntBool = myConst Int Bool +myConstIntBool = myConst Integer Bool diff --git a/typechecker/test/cases/should-typecheck/myConst-required.output b/typechecker/test/cases/should-typecheck/myConst-required.output index f55788f..610ac70 100644 --- a/typechecker/test/cases/should-typecheck/myConst-required.output +++ b/typechecker/test/cases/should-typecheck/myConst-required.output @@ -1,3 +1,3 @@ myConst : forall a1:Type -> forall b1:Type -> a1 -> b1 -> a1 -myConstInt : forall a1:Type -> Int -> a1 -> Int -myConstIntBool : Int -> Bool -> Int \ No newline at end of file +myConstInt : forall a1:Type -> Integer -> a1 -> Integer +myConstIntBool : Integer -> Bool -> Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/plusNineLambda-infer.output b/typechecker/test/cases/should-typecheck/plusNineLambda-infer.output index 9754abf..08456e0 100644 --- a/typechecker/test/cases/should-typecheck/plusNineLambda-infer.output +++ b/typechecker/test/cases/should-typecheck/plusNineLambda-infer.output @@ -1 +1 @@ -plusNineLambda : Int -> Int -> Int -> Int \ No newline at end of file +plusNineLambda : Integer -> Integer -> Integer -> Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/silly1.hs b/typechecker/test/cases/should-typecheck/silly1.hs index 9f811d5..ecf4efe 100644 --- a/typechecker/test/cases/should-typecheck/silly1.hs +++ b/typechecker/test/cases/should-typecheck/silly1.hs @@ -1,3 +1,3 @@ -silly1 :: forall a. Show a => a -> Int +silly1 :: forall a. Show a => a -> Integer silly1 (show -> "Matched") = 4 silly1 _ = 0 diff --git a/typechecker/test/cases/should-typecheck/silly1.output b/typechecker/test/cases/should-typecheck/silly1.output index 881f144..1c7fc10 100644 --- a/typechecker/test/cases/should-typecheck/silly1.output +++ b/typechecker/test/cases/should-typecheck/silly1.output @@ -1 +1 @@ -silly1 : forall a1:Type. Show a1 => a1 -> Int \ No newline at end of file +silly1 : forall a1:Type. Show a1 => a1 -> Integer \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/tyAbsCaseIllegal.hs b/typechecker/test/cases/should-typecheck/tyAbsCaseIllegal.hs index cb299a1..6d1bb41 100644 --- a/typechecker/test/cases/should-typecheck/tyAbsCaseIllegal.hs +++ b/typechecker/test/cases/should-typecheck/tyAbsCaseIllegal.hs @@ -1,4 +1,4 @@ -tyAbsCaseIllegal :: forall a. (a -> a) -> Int +tyAbsCaseIllegal :: forall a. (a -> a) -> Integer tyAbsCaseIllegal g = case g of -- g has type 'a' @b x -> let y = 0 -- There is no correcsponding invisibly-specified quantifee to bound b to! z :: b -> b -- 'b' is not in scope diff --git a/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.hs b/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.hs index 2137fb5..52f31a4 100644 --- a/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.hs +++ b/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.hs @@ -1,4 +1,4 @@ -tyAbsCaseLegal :: forall a. (a -> a) -> Int +tyAbsCaseLegal :: forall a. (a -> a) -> Integer tyAbsCaseLegal @b g = case g of x -> let y = 0 z :: b -> b -- b is in scope diff --git a/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.output b/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.output index 86732df..7725993 100644 --- a/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.output +++ b/typechecker/test/cases/should-typecheck/tyAbsCaseLegal.output @@ -1 +1 @@ -tyAbsCaseLegal : forall a1:Type. (a1 -> a1) -> Int +tyAbsCaseLegal : forall a1:Type. (a1 -> a1) -> Integer diff --git a/typechecker/test/cases/should-typecheck/unwrapMaybeAndEither-infer.output b/typechecker/test/cases/should-typecheck/unwrapMaybeAndEither-infer.output index 0c9534b..0415756 100644 --- a/typechecker/test/cases/should-typecheck/unwrapMaybeAndEither-infer.output +++ b/typechecker/test/cases/should-typecheck/unwrapMaybeAndEither-infer.output @@ -1,4 +1,4 @@ unwrapMaybeBool : Maybe Bool -> Bool -unwrapEitherIntBoolCase : Either Int Bool -> Either Int Bool -unwrapEitherIntBool : Either Int Bool -> Either Int Bool +unwrapEitherIntBoolCase : Either Integer Bool -> Either Integer Bool +unwrapEitherIntBool : Either Integer Bool -> Either Integer Bool idEither : forall {a1:Type}. forall {b1:Type}. Either a1 b1 -> Either a1 b1 \ No newline at end of file diff --git a/typechecker/test/cases/should-typecheck/weirdDecl.hs b/typechecker/test/cases/should-typecheck/weirdDecl.hs index e98f903..1903230 100644 --- a/typechecker/test/cases/should-typecheck/weirdDecl.hs +++ b/typechecker/test/cases/should-typecheck/weirdDecl.hs @@ -1,2 +1,2 @@ -weirdDecl :: forall a. a -> a ~ Int => a -- The goal is to reject this, -weirdDecl @Int x = x -- but for now, we need to accept it +weirdDecl :: forall a. a -> a ~ Integer => a -- The goal is to reject this, +weirdDecl @Integer x = x -- but for now, we need to accept it diff --git a/typechecker/test/cases/should-typecheck/weirdDecl.output b/typechecker/test/cases/should-typecheck/weirdDecl.output index e42ebb9..f9a9207 100644 --- a/typechecker/test/cases/should-typecheck/weirdDecl.output +++ b/typechecker/test/cases/should-typecheck/weirdDecl.output @@ -1 +1 @@ -weirdDecl : forall a1:Type. a1 -> a1 ~ Int => a1 \ No newline at end of file +weirdDecl : forall a1:Type. a1 -> a1 ~ Integer => a1 \ No newline at end of file diff --git a/typechecker/test/other/Rep.hs b/typechecker/test/other/Rep.hs index ef9b4ef..c673a93 100644 --- a/typechecker/test/other/Rep.hs +++ b/typechecker/test/other/Rep.hs @@ -12,4 +12,4 @@ idType = Quantified (Specified (fooVar, tyConType)) (Quantified (Arrow (Alpha fo idTypeToIdType = (Quantified (Arrow idType) idType) -intToIntArg = Quantified (Arrow (Quantified (Arrow tyConInt) tyConInt)) tyConBool +intToIntArg = Quantified (Arrow (Quantified (Arrow tyConInteger) tyConInt)) tyConBool -- GitLab