From 77317dd6b49caa16466b8f90ad9570ac2b9d291d Mon Sep 17 00:00:00 2001 From: gnumonik Date: Mon, 16 Dec 2024 22:43:28 -0500 Subject: [PATCH 1/4] Reorganized test structure --- purs-lib/Command/Compile.hs | 6 +- tests/TestPurus.hs | 75 +- tests/purus/passing/CoreFn/Misc/Lib.purs | 7 + .../passing/CoreFn/Misc/output/Lib/Lib.cfn | 1 - .../CoreFn/Misc/output/Lib/Lib.cfn.pretty | 1057 ----------------- .../CoreFn/Misc/output/Lib/externs.cbor | Bin 74204 -> 0 bytes 6 files changed, 56 insertions(+), 1090 deletions(-) delete mode 100644 tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn delete mode 100644 tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty delete mode 100644 tests/purus/passing/CoreFn/Misc/output/Lib/externs.cbor diff --git a/purs-lib/Command/Compile.hs b/purs-lib/Command/Compile.hs index 9cd29b37..7b6fb8f6 100644 --- a/purs-lib/Command/Compile.hs +++ b/purs-lib/Command/Compile.hs @@ -23,6 +23,7 @@ import System.Directory (getCurrentDirectory) import System.FilePath.Glob (glob) import System.IO (hPutStr, hPutStrLn, stderr, stdout) import System.IO.UTF8 (readUTF8FilesT) +import Language.PureScript.Errors (MultipleErrors(..)) data PSCMakeOptions = PSCMakeOptions { pscmInput :: [FilePath] @@ -72,6 +73,7 @@ compile PSCMakeOptions{..} = do printWarningsAndErrors (P.optionsVerboseErrors pscmOpts) pscmJSONErrors moduleFiles makeWarnings makeErrors exitSuccess +-- No warnings (makes tests output impossible to read) compileForTests :: PSCMakeOptions -> IO () compileForTests PSCMakeOptions{..} = do included <- globWarningOnMisses warnFileTypeNotFound pscmInput @@ -83,13 +85,13 @@ compileForTests PSCMakeOptions{..} = do ] else do moduleFiles <- readUTF8FilesT input - (makeErrors, makeWarnings) <- runMake pscmOpts $ do + (makeErrors, _) <- runMake pscmOpts $ do ms <- CST.parseModulesFromFiles id moduleFiles let filePathMap = M.fromList $ map (\(fp, pm) -> (P.getModuleName $ CST.resPartial pm, Right fp)) ms foreigns <- inferForeignModules filePathMap let makeActions = buildMakeActions pscmOutputDir filePathMap foreigns pscmUsePrefix P.make makeActions (map snd ms) - printWarningsAndErrors (P.optionsVerboseErrors pscmOpts) pscmJSONErrors moduleFiles makeWarnings makeErrors + printWarningsAndErrors (P.optionsVerboseErrors pscmOpts) pscmJSONErrors moduleFiles (MultipleErrors []) makeErrors warnFileTypeNotFound :: String -> IO () warnFileTypeNotFound = hPutStrLn stderr . ("purs compile: No files found using pattern: " ++) diff --git a/tests/TestPurus.hs b/tests/TestPurus.hs index 0402deba..99ba046f 100644 --- a/tests/TestPurus.hs +++ b/tests/TestPurus.hs @@ -3,13 +3,14 @@ module TestPurus where import Prelude import Data.Text (Text) +import Data.Text qualified as T import Command.Compile ( compileForTests, PSCMakeOptions(..) ) -import Control.Monad (when,unless) +import Control.Monad (when,unless, void) import System.FilePath import Language.PureScript qualified as P import Data.Set qualified as S import Data.Foldable (traverse_) -import System.Directory +import System.Directory import System.FilePath.Glob qualified as Glob import Data.Function (on) import Data.List (sortBy, stripPrefix, groupBy) @@ -18,19 +19,25 @@ import Language.Purus.Eval import Language.Purus.Types import PlutusCore.Evaluation.Result import PlutusIR.Core.Instance.Pretty.Readable (prettyPirReadable) -import Test.Tasty +import Test.Tasty import Test.Tasty.HUnit import Language.Purus.Make.Prim (syntheticPrim) +import Language.PureScript (ModuleName, runModuleName) +import Control.Concurrent ( threadDelay ) +import Test.Tasty.Providers +import Control.Exception shouldPassTests :: IO () -shouldPassTests = do +shouldPassTests = defaultShouldPassTests >>= defaultMain +{- + do cfn <- coreFnTests pirNoEval <- pirTestsNoEval pirEval <- pirTestsEval let validatorTest = testCase "validator apply/eval" mkValidatorTest policyTest = testCase "minting policy apply/eval" mkMintingPolicyTest defaultMain $ sequentialTestGroup "Purus Tests" AllFinish [cfn,pirNoEval,pirEval,validatorTest,policyTest] - +-} runPurusCoreFn :: P.CodegenTarget -> FilePath -> IO () runPurusCoreFn target dir = do outDirExists <- doesDirectoryExist outputDir @@ -56,36 +63,44 @@ runPurusCoreFn target dir = do purusOpts :: P.Options purusOpts = P.Options { - optionsVerboseErrors = True, + optionsVerboseErrors = False, optionsNoComments = True, optionsCodegenTargets = S.singleton target } --- TODO: Move modules into a directory specifically for PIR non-eval tests (for now this should be OK) -pirTestsNoEval :: IO TestTree -pirTestsNoEval = do - let coreFnTestPath = "tests/purus/passing/CoreFn" - allTestDirectories <- listDirectory coreFnTestPath - trees <- mapM (\dir -> compileDirNoEvalTest (coreFnTestPath dir)) allTestDirectories-- allTestDirectories - pure $ sequentialTestGroup "PIR Tests (No Evaluation)" AllFinish trees - -pirTestsEval :: IO TestTree -pirTestsEval = do - let coreFnTestPath = "tests/purus/passing/CoreFn" - allTestDirectories <- listDirectory coreFnTestPath - trees <- mapM (\dir -> compileDirEvalTest (coreFnTestPath dir)) allTestDirectories-- allTestDirectories - pure $ sequentialTestGroup "PIR Tests (Evaluation)" AllFinish trees --- path to a Purus project directory, outputs serialized CoreFn -compileToCoreFnTest :: FilePath -> TestTree -compileToCoreFnTest path = testCase (path) $ runPurusCoreFnDefault path - -coreFnTests :: IO TestTree -coreFnTests = do - let coreFnTestPath = "tests/purus/passing/CoreFn" - allTestDirectories <- listDirectory coreFnTestPath - let trees = map (\dir -> compileToCoreFnTest (coreFnTestPath dir)) allTestDirectories - pure $ sequentialTestGroup "CoreFn Tests" AllFinish trees +mkPIRTests :: FilePath -> IO [(ModuleName,Text)] -> (PIRTerm -> IO ()) -> IO [TestTree] +mkPIRTests path ioInput f = map mkCase <$> ioInput + where + mkCase :: (ModuleName, Text) -> TestTree + mkCase (runModuleName -> mn,dn) = testCase testName $ do + f =<< make path mn dn (Just syntheticPrim) + where + testName = T.unpack mn <> "." <> T.unpack dn + +defaultShouldPassTests :: IO TestTree +defaultShouldPassTests = mkShouldPassTests "tests/purus/passing/CoreFn" + + + +mkShouldPassTests :: FilePath -> IO TestTree +mkShouldPassTests testDirPath = do + allProjectDirectories <- listDirectory testDirPath + testGroup "Purus Passing" <$> traverse (go . (testDirPath )) allProjectDirectories + where + + go :: FilePath -> IO TestTree + go path = do --let coreFnTest = testCase ("CoreFn: " <> path) (void $ runPurusCoreFnDefault path) -- this is stupid but idk how to get it to show up in the output unless we do it twice + pirNoEval <- testGroup "No Eval" <$> mkPIRTests path initialize (void . pure) + pirEval <- testGroup "Eval" <$> mkPIRTests path initialize (void . evaluateTerm) + pure $ testGroup ("PIR: " <> show path) [pirNoEval,pirEval] + + where + initialize :: IO [(ModuleName,Text)] + initialize = do + void $ runPurusCoreFnDefault path + threadDelay 5000 -- not sure if the write will complete before the previous line finishes evaluating + allValueDeclarations path runPurusCoreFnDefault :: FilePath -> IO () runPurusCoreFnDefault path = runPurusCoreFn P.CoreFn path diff --git a/tests/purus/passing/CoreFn/Misc/Lib.purs b/tests/purus/passing/CoreFn/Misc/Lib.purs index 99415087..f4ef92c3 100644 --- a/tests/purus/passing/CoreFn/Misc/Lib.purs +++ b/tests/purus/passing/CoreFn/Misc/Lib.purs @@ -509,3 +509,10 @@ testNestedSmaller = case _ of Nothing -> 0 Just Nothing -> 1 Just (Just x) -> x + +testIncompleteCases :: Int -> Int +testIncompleteCases = case _ of + 0 -> 0 + 1 -> 1 + 2 -> 2 + 3 -> 3 diff --git a/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn b/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn deleted file mode 100644 index 4441725b..00000000 --- a/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn +++ /dev/null @@ -1 +0,0 @@ -{"builtWith":"0.0.1","comments":[],"dataTypes":{"_ctorDict":[[[["Lib"],{"Ident":"ADataRec"}],[["Lib"],"ADataRec"]],[[["Lib"],{"Ident":"ANewTypeRec"}],[["Lib"],"ANewtypeRec"]],[[["Lib"],{"Ident":"C"}],[["Lib"],"C"]],[[["Lib"],{"Ident":"ConChar"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConConstrained"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConInt"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConNested"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConObject"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConObjectQuantified"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConQuantified"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConString"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"Constr1"}],[["Lib"],"ASum"]],[[["Lib"],{"Ident":"Constr2"}],[["Lib"],"ASum"]],[[["Lib"],{"Ident":"Identitee"}],[["Lib"],"Identitee"]],[[["Lib"],{"Ident":"Nada"}],[["Lib"],"Option"]],[[["Lib"],{"Ident":"Some"}],[["Lib"],"Option"]]],"_tyDict":[[[["Lib"],"ADataRec"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["hello",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["world",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ADataRec"}]}],"_dDataTyName":[["Lib"],"ADataRec"],"_dDeclType":"data"}],[[["Lib"],"ANewtypeRec"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ANewTypeRec"}]}],"_dDataTyName":[["Lib"],"ANewtypeRec"],"_dDeclType":"newtype"}],[[["Lib"],"ASum"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"Constr1"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"Constr2"}]}],"_dDataTyName":[["Lib"],"ASum"],"_dDeclType":"data"}],[[["Lib"],"C"],{"_dDataArgs":[["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],["b",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],["c",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}]],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],[{"Ident":"value1"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],[{"Ident":"value2"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}]],"_cdCtorName":[["Lib"],{"Ident":"C"}]}],"_dDataTyName":[["Lib"],"C"],"_dDeclType":"data"}],[[["Lib"],"Identitee"],{"_dDataArgs":[["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}]],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}]],"_cdCtorName":[["Lib"],{"Ident":"Identitee"}]}],"_dDataTyName":[["Lib"],"Identitee"],"_dDeclType":"data"}],[[["Lib"],"Option"],{"_dDataArgs":[["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}]],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}]],"_cdCtorName":[["Lib"],{"Ident":"Some"}]},{"_cdCtorFields":[],"_cdCtorName":[["Lib"],{"Ident":"Nada"}]}],"_dDataTyName":[["Lib"],"Option"],"_dDeclType":"data"}],[[["Lib"],"TestBinderSum"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConInt"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConString"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Char"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConChar"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConNested"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}]],"_cdCtorName":[["Lib"],{"Ident":"ConQuantified"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}]],"_cdCtorName":[["Lib"],{"Ident":"ConConstrained"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objField",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ConObject"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objFieldQ",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ConObjectQuantified"}]}],"_dDataTyName":[["Lib"],"TestBinderSum"],"_dDeclType":"data"}]]},"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["testMethod",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}}]]}},"identifier":"testClassInt"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["eq",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}}]]}},"identifier":"eqInt"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["Eq",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}}],["compare",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":42}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}}]]}},"identifier":"ordInt"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["eq2",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}}]]}},"identifier":"eq2IntBoolean"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[46,29],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[46,26]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Identitee","moduleName":["Lib"]},"typeName":{"identifier":"Identitee","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[48,13]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"unIdentitee"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[138,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[138,21]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Constr1","moduleName":["Lib"]},"typeName":{"identifier":"ASum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"z","type":{"annotation":[{"end":[138,42],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[138,35]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Constr2","moduleName":["Lib"]},"typeName":{"identifier":"ASum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"ASum"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[151,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"ASum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testasum"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"datum","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"redeemer","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"context","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":7,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":6,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"c","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":5,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"testValidator"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":7,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":6,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"c","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":5,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"testValidator","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"datum"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"redeemer"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"context"}},"kind":"App"},"identifier":"testValidatorApplied"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x1","type":{"annotation":[{"end":[490,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[490,21]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[491,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testRedundantLit"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x1","type":{"annotation":[{"end":[476,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[476,29]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"x","sourcePos":[477,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testRedundantCtors"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[507,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[507,35]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[511,14]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testNestedSmaller"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[500,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[500,35]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[505,20]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testNested"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[11,3]}},"fieldName":"testMethod","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":11,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"testMethod"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":11,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"testMethod","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"testClassInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"identifier":"testTestClass"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"DCert"],"tag":"TypeConstructor"},"value":{"identifier":"DCertMir","moduleName":["Prim"]}},"identifier":"testLedgerTypes"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"unIdentitee","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":12,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"Identitee","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":101}},"kind":"App"},"kind":"App"},"identifier":"testIdentitee"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[331,1]}},"identifier":"q"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"y","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"c","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"d","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"d","sourcePos":[343,5]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[345,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"c","sourcePos":[343,5]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"d","sourcePos":[343,5]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"j"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"z","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":16,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"i"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":16,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"i","sourcePos":[339,9]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"q","sourcePos":[333,5]}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"j","sourcePos":[342,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"a","sourcePos":[337,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[337,5]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[345,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"a","sourcePos":[337,5]}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"h"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[336,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[331,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":13,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"testForLiftPoly"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":13,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"testForLiftPoly","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"identifier":"testForLiftPolyApplied"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":17,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"testCons"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"addInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"testBuiltin"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"constructorName":{"identifier":"Identitee","moduleName":["Lib"]},"typeName":{"identifier":"Identitee","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[485,36],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[485,33]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Identitee","moduleName":["Lib"]},"typeName":{"identifier":"Identitee","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testBrokenCollapse"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"a","type":{"annotation":[{"end":[65,15],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[65,12]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConInt","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[78,10]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"constructorName":{"identifier":"ConChar","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"conNest","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConNested","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"n","type":{"annotation":[{"end":[65,15],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[65,12]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConInt","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[81,12]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"},"value":{"identifier":"conNest","sourcePos":[80,13]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"f","type":{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,20]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[71,37],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,33]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,40]},[]],"contents":[{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,40]},[]],"contents":[{"annotation":[{"end":[71,44],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,42]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[71,41],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,40]},[]],"contents":{"kind":{"annotation":[{"end":[71,37],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,33]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,45]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}}],"constructorName":{"identifier":"ConQuantified","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"f","sourcePos":[83,17]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"g","type":{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,21]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,9]},[]],"contents":[{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,9]},[]],"contents":[{"annotation":[{"end":[20,13],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,11]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[72,45],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,44]},[]],"contents":{"kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,14]},[]],"contents":[{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,14]},[]],"contents":[{"annotation":[{"end":[20,18],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,16]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[72,45],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,44]},[]],"contents":{"kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,19]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,49]},[]],"contents":[{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,49]},[]],"contents":[{"annotation":[{"end":[72,53],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,51]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[72,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,49]},[]],"contents":{"kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,54]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}}],"constructorName":{"identifier":"ConConstrained","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"g","sourcePos":[84,18]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"other","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConNested","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":7}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"obj","type":{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[{"annotation":[{"end":[73,16],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,16]},[]],"contents":["objField",{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"contents":[{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"tag":"REmpty"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"}}],"constructorName":{"identifier":"ConObject","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objField",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"obj","sourcePos":[86,13]}},"fieldName":"objField","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"objQ","type":{"annotation":[{"end":[74,68],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,25]},[]],"contents":[{"annotation":[{"end":[74,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,25]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,26]},[]],"contents":["objFieldQ",{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,39]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[74,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,52]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,59]},[]],"contents":[{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,59]},[]],"contents":[{"annotation":[{"end":[74,63],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,61]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[74,60],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,59]},[]],"contents":{"kind":{"annotation":[{"end":[74,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,52]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,64]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[74,68],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,67]},[]],"contents":[{"annotation":[{"end":[74,68],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,67]},[]],"tag":"REmpty"},{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,39]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"}}],"constructorName":{"identifier":"ConObjectQuantified","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objFieldQ",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"objQ","sourcePos":[87,23]}},"fieldName":"objFieldQ","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"world"}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"objs","type":{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[{"annotation":[{"end":[73,16],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,16]},[]],"contents":["objField",{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"contents":[{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"tag":"REmpty"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"}}],"constructorName":{"identifier":"ConObject","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"ObjectLiteral","value":[["objField",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"f","type":{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}]]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"f","sourcePos":[89,16]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objField",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"objs","sourcePos":[88,13]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"other","type":{"annotation":[{"end":[76,29],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[76,16]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[77,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testBinders"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"testBinders","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"ConInt","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"identifier":"testBindersCase"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"iData","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"identifier":"someData"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"mkCons","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"},"value":{"identifier":"someData","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"mkNilData","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"identifier":"someDataList"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"deserializeInt","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"},"value":{"identifier":"someData","moduleName":["Lib"]}},"kind":"App"},"identifier":"testPrelude1"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":25,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"go"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["bar",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["baz",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["baz",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":100}}],["bar",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":25,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"go","sourcePos":[254,5]}}]]}},"kind":"Let"},"identifier":"polyInObj"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"ObjectLiteral","value":[["bar",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"f","type":{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,22]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[251,39],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,35]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,42]},[]],"contents":[{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,42]},[]],"contents":[{"annotation":[{"end":[251,46],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,44]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[251,43],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,42]},[]],"contents":{"kind":{"annotation":[{"end":[251,39],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,35]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,47]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}}],["baz",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}]]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"f","sourcePos":[259,9]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["bar",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["baz",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"polyInObj","moduleName":["Lib"]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"identifier":"polyInObjMatch"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"addInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[210,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[210,1]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"plus"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[468,46],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,43]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[470,35]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[468,33],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,30]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[471,27]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[468,33],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,30]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[468,46],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,43]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[472,27]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[472,36]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"testMultiCaseSimple"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"identifier":"testPlus"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b2","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b2","sourcePos":[351,1]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b1","sourcePos":[351,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"or"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i","type":{"annotation":[{"end":[36,22],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[36,19]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Some","moduleName":["Lib"]},"typeName":{"identifier":"Option","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i","sourcePos":[38,8]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nada","moduleName":["Lib"]},"typeName":{"identifier":"Option","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"opt2Int"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"opt2Int","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":27,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"Some","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"kind":"App"},"identifier":"testOpt2Int"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[356,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"not"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":29,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"g"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"f"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":29,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"g","sourcePos":[125,8]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"identifier":"i"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"f","sourcePos":[122,8]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i","sourcePos":[128,16]}},"kind":"App"},"identifier":"j"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"f","sourcePos":[122,8]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"j","sourcePos":[129,16]}},"kind":"App"},"kind":"Let"},"identifier":"h"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"h","sourcePos":[128,8]}},"kind":"Let"},"identifier":"nestedBinds"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[236,5]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"i"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":2}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"h"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[237,5]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"f"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"i","sourcePos":[236,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"f","sourcePos":[237,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[238,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[239,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"kind":"Let"},"identifier":"nestedApplications"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":42}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"minus"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"r","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"var":"r"},"tag":"TypeVar"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"r","sourcePos":[206,5]}},"fieldName":"a","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"r","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"skolem":31,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"var":"r"},"tag":"TypeVar"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"aFunction4"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"r","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"skolem":31,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"var":"r"},"tag":"TypeVar"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"aFunction4","sourcePos":[205,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["b",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["b",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}}],["a",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":101}}]]}},"kind":"App"},"kind":"Let"},"identifier":"main"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"n","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":0}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":2}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":3}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":4}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[395,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"litPattern"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"litPattern","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"App"},"identifier":"litPatternApplied"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"nullList","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"someDataList","moduleName":["Lib"]}},"kind":"App"},"identifier":"isNullSomeDataList"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"n","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"irrPattern"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[427,1]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":33,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"identitea"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"p","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"q","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"p","sourcePos":[436,5]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":37,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":35,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"const"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":33,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"identitea","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":37,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":35,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"const","sourcePos":[435,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"kind":"Let"},"identifier":"testIdConst"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[277,1]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"id"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":42,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":41,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["getIdA",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["getIdB",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"literalType":"ObjectLiteral","value":[["getIdB",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}}],["getIdA",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}}]]}},"identifier":"objForall"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"testId"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"fakeLT"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"c","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"d","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"c","sourcePos":[323,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[324,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"d","sourcePos":[323,5]}},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"j"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"fakeLT","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[324,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[322,5]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"j","sourcePos":[323,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[322,5]}},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"h"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"j","sourcePos":[323,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"multiplyInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[322,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[324,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[322,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testForLift"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"fakeLT","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[442,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[441,5]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"h"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"multiplyInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[441,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[442,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[441,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testForLift'"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"False","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"False","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v","sourcePos":[0,0]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"eqBool"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[53,3]}},"fieldName":"eq2","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":46,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":45,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"eq2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":46,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":45,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq2","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"eq2IntBoolean","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":101}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"kind":"App"},"identifier":"testEq2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[20,3]}},"fieldName":"eq","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"eq"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$36","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$36"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"v"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"ObjectLiteral","value":[["bar",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],["baz",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[251,62],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,59]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}]]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[289,17]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"identifier":"v1"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[289,17]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$36","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$36"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$36","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$36"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["bar",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["baz",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"polyInObj","moduleName":["Lib"]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"identifier":"guardedCase2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dictOrd","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dictOrd","sourcePos":[0,0]}},"fieldName":"Eq","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"a","sourcePos":[307,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"b","sourcePos":[307,1]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":48,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"testEqViaOrd"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":48,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"testEqViaOrd","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"ordInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"testSuperClass"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"xs","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[265,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":50,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"cons"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":50,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"cons","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"consEmptyList1"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":50,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"cons","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"consEmptyList2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[301,3]}},"fieldName":"compare","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":52,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"compare"},{"bindType":"Rec","binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"n","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"brokenEven","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"minus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[29,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[29,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"brokenEven"}]},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":53,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"arrForall"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":33,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"identitea","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"apIdentitea"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"p","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"q","body":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"or","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"p","sourcePos":[359,1]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"q","sourcePos":[359,1]}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"and"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i1","type":{"annotation":[{"end":[460,17],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,14]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s1","type":{"annotation":[{"end":[460,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,18]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"b1","type":{"annotation":[{"end":[460,39],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,32]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i2","type":{"annotation":[{"end":[460,49],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,46]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s2","type":{"annotation":[{"end":[460,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,50]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"b2","type":{"annotation":[{"end":[460,71],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,64]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i1","sourcePos":[461,12]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i2","sourcePos":[461,32]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsString","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s1","sourcePos":[461,15]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s2","sourcePos":[461,35]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"eqBool","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b1","sourcePos":[461,24]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b2","sourcePos":[461,44]}},"kind":"App"},"kind":"App"},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i1","type":{"annotation":[{"end":[460,17],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,14]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s1","type":{"annotation":[{"end":[460,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,18]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i2","type":{"annotation":[{"end":[460,49],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,46]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s2","type":{"annotation":[{"end":[460,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,50]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i1","sourcePos":[465,12]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i2","sourcePos":[465,30]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsString","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s1","sourcePos":[465,15]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s2","sourcePos":[465,33]}},"kind":"App"},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"equalsC"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"p","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"q","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"or","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"p","sourcePos":[364,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"q","sourcePos":[364,1]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"p","sourcePos":[364,1]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"q","sourcePos":[364,1]}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"iff"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["foo",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}}]]}},"identifier":"anObj"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"anObj","moduleName":["Lib"]}},"identifier":"v"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"copy":[],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[249,1]}},"kind":"ObjectUpdate","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"updates":[["foo",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}}]]},"kind":"Let"},"identifier":"objUpdate"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"identifier":"anIntLit"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"identifier":"aVal"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"woop"}},"identifier":"aStringLit"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"aPred"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"w","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"v"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[225,19],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[225,16]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"z","type":{"annotation":[{"end":[225,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[225,23]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[227,3]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"v1"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"aPred","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[227,3]}},"kind":"App"},"identifier":"v2"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"z","sourcePos":[227,6]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"App"},"identifier":"v3"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[227,3]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"nestedBinds","moduleName":["Lib"]}},"kind":"App"},"identifier":"v4"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v4","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v3","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v2","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"w","sourcePos":[226,1]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[226,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"guardedCase"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":55,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":56,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"identifier":"aList2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"App"},"identifier":"aList"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[173,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"aFunction3"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[170,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"aFunction2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"any","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"f","body":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":58,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"f","sourcePos":[167,1]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"},"value":{"identifier":"any","sourcePos":[167,1]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":58,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":59,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":58,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"aFunction"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"identifier":"aBool"}],"exports":["compare","eq","eq2","testMethod","testCons","testTestClass","minus","brokenEven","Some","Nada","opt2Int","testOpt2Int","Identitee","unIdentitee","testIdentitee","testEq2","ConInt","ConString","ConChar","ConNested","ConQuantified","ConConstrained","ConObject","ConObjectQuantified","testBinders","testBindersCase","nestedBinds","ADataRec","ANewTypeRec","Constr1","Constr2","anIntLit","aStringLit","aVal","testasum","aBool","aList","aList2","aFunction","aFunction2","aFunction3","testBuiltin","main","plus","fakeLT","testPlus","guardedCase","nestedApplications","anObj","objUpdate","polyInObj","polyInObjMatch","aPred","cons","consEmptyList1","consEmptyList2","id","testId","objForall","arrForall","guardedCase2","testEqViaOrd","testSuperClass","testValidator","testValidatorApplied","testForLift","testForLiftPoly","testForLiftPolyApplied","or","not","and","iff","testLedgerTypes","litPattern","litPatternApplied","irrPattern","someData","testPrelude1","someDataList","isNullSomeDataList","identitea","apIdentitea","testIdConst","testForLift'","C","eqBool","equalsC","testMultiCaseSimple","testRedundantCtors","testBrokenCollapse","testRedundantLit","testNested","testNestedSmaller","testClassInt","eqInt","eq2IntBoolean","ordInt"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[511,21],"start":[1,1]}},"moduleName":["Builtin"]},{"annotation":{"meta":null,"sourceSpan":{"end":[511,21],"start":[1,1]}},"moduleName":["Lib"]},{"annotation":{"meta":null,"sourceSpan":{"end":[511,21],"start":[1,1]}},"moduleName":["Prim"]}],"moduleName":["Lib"],"modulePath":"tests/purus/passing/CoreFn/Misc/Lib.purs","reExports":{},"sourceSpan":{"end":[511,21],"start":[1,1]}} \ No newline at end of file diff --git a/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty b/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty deleted file mode 100644 index d91a4a99..00000000 --- a/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty +++ /dev/null @@ -1,1057 +0,0 @@ -Lib (tests/purus/passing/CoreFn/Misc/Lib.purs) - -Imported Modules: ------------------------------- - Builtin, - Lib, - Prim - -Exports: ------------------------------- - compare, - eq, - eq2, - testMethod, - testCons, - testTestClass, - minus, - brokenEven, - Some, - Nada, - opt2Int, - testOpt2Int, - Identitee, - unIdentitee, - testIdentitee, - testEq2, - ConInt, - ConString, - ConChar, - ConNested, - ConQuantified, - ConConstrained, - ConObject, - ConObjectQuantified, - testBinders, - testBindersCase, - nestedBinds, - ADataRec, - ANewTypeRec, - Constr1, - Constr2, - anIntLit, - aStringLit, - aVal, - testasum, - aBool, - aList, - aList2, - aFunction, - aFunction2, - aFunction3, - testBuiltin, - main, - plus, - fakeLT, - testPlus, - guardedCase, - nestedApplications, - anObj, - objUpdate, - polyInObj, - polyInObjMatch, - aPred, - cons, - consEmptyList1, - consEmptyList2, - id, - testId, - objForall, - arrForall, - guardedCase2, - testEqViaOrd, - testSuperClass, - testValidator, - testValidatorApplied, - testForLift, - testForLiftPoly, - testForLiftPolyApplied, - or, - not, - and, - iff, - testLedgerTypes, - litPattern, - litPatternApplied, - irrPattern, - someData, - testPrelude1, - someDataList, - isNullSomeDataList, - identitea, - apIdentitea, - testIdConst, - testForLift', - C, - eqBool, - equalsC, - testMultiCaseSimple, - testRedundantCtors, - testBrokenCollapse, - testRedundantLit, - testNested, - testNestedSmaller, - testClassInt, - eqInt, - eq2IntBoolean, - ordInt - -Re-Exports: ------------------------------- - - -Foreign: ------------------------------- - - -Datatypes: ------------------------------- -data ADataRec = - ADataRec ({ hello :: Prim.Int, world :: Prim.Boolean }) - -newtype ANewtypeRec = - ANewTypeRec ({ foo :: Prim.Int }) - -data ASum = - Constr1 (Prim.Int) - | Constr2 (Prim.Boolean) - -data C (a :: Prim.Type) (b :: Prim.Type) (c :: Prim.Type) = - C ((a :: Prim.Type)) ((b :: Prim.Type)) ((c :: Prim.Type)) - -data Identitee (a :: Prim.Type) = - Identitee ((a :: Prim.Type)) - -data Option (a :: Prim.Type) = - Some ((a :: Prim.Type)) - | Nada - -data TestBinderSum = - ConInt (Prim.Int) - | ConString (Prim.String) - | ConChar (Prim.Char) - | ConNested (Lib.TestBinderSum) - | ConQuantified (forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int))) - | ConConstrained (forall (x :: Prim.Type). ({ eq :: ((x :: Prim.Type) -> (((x :: Prim.Type) -> (Prim.Boolean)))) } -> (((x :: Prim.Type) -> (Prim.Int))))) - | ConObject ({ objField :: Prim.Int }) - | ConObjectQuantified ({ objFieldQ :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)) }) - - -Declarations: ------------------------------- -testClassInt :: { testMethod :: (Prim.Int -> (Prim.Boolean)) } -testClassInt = - ({ - testMethod: \(x: Prim.Int) -> - (True: Prim.Boolean) - }: { testMethod :: (Prim.Int -> (Prim.Boolean)) }) - -eqInt :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } -eqInt = - ({ - eq: \(v: Prim.Int) -> - \(v1: Prim.Int) -> - (True: Prim.Boolean) - }: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) - -ordInt :: { compare :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))), Eq :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } } -ordInt = - ({ - Eq: (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }), - compare: \(v: Prim.Int) -> - \(v1: Prim.Int) -> - (42: Prim.Int) - }: { - compare :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))), - Eq :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } - }) - -eq2IntBoolean :: { eq2 :: (Prim.Int -> ((Prim.Boolean -> (Prim.Boolean)))) } -eq2IntBoolean = - ({ - eq2: \(v: Prim.Int) -> - \(v1: Prim.Boolean) -> - (True: Prim.Boolean) - }: { eq2 :: (Prim.Int -> ((Prim.Boolean -> (Prim.Boolean)))) }) - -unIdentitee :: ((Lib.Identitee (Prim.Int)) -> (Prim.Int)) -unIdentitee = - \(v: (Lib.Identitee (Prim.Int))) -> - case (v: (Lib.Identitee (Prim.Int))) of - Identitee x -> (x: Prim.Int) - -testasum :: (Lib.ASum -> (Prim.Int)) -testasum = - \(x: Lib.ASum) -> - case (x: Lib.ASum) of - Constr1 y -> (1: Prim.Int) - Constr2 z -> (2: Prim.Int) - -testValidator :: forall (a :: Prim.Type) (b :: Prim.Type) (c :: Prim.Type). ((a :: Prim.Type) -> (((b :: Prim.Type) -> (((c :: Prim.Type) -> (Prim.Boolean)))))) -testValidator = - \(datum: (a :: Prim.Type)) -> - \(redeemer: (b :: Prim.Type)) -> - \(context: (c :: Prim.Type)) -> - (True: Prim.Boolean) - -testValidatorApplied :: Prim.Boolean -testValidatorApplied = - (testValidator: forall (a :: Prim.Type) - (b :: Prim.Type) - (c :: Prim.Type). ((a :: Prim.Type) -> - (((b :: Prim.Type) -> (((c :: Prim.Type) -> (Prim.Boolean))))))) - ("datum": Prim.String) - ("redeemer": Prim.String) - ("context": Prim.String) - -testRedundantLit :: (Prim.Int -> (Prim.Int)) -testRedundantLit = - \(x: Prim.Int) -> - case (x: Prim.Int) of - 1 -> (1: Prim.Int) - 1 -> (2: Prim.Int) - 1 -> (3: Prim.Int) - _ -> (4: Prim.Int) - x1 -> (5: Prim.Int) - -testRedundantCtors :: ((Prim.Maybe (Prim.Int)) -> (Prim.Unit)) -testRedundantCtors = - \(x: (Prim.Maybe (Prim.Int))) -> - case (x: (Prim.Maybe (Prim.Int))) of - Just 1 -> (unit: Prim.Unit) - Just x1 -> (unit: Prim.Unit) - Nothing -> (unit: Prim.Unit) - -testNestedSmaller :: ((Prim.Maybe ((Prim.Maybe (Prim.Int)))) -> (Prim.Int)) -testNestedSmaller = - \(v: (Prim.Maybe ((Prim.Maybe (Prim.Int))))) -> - case (v: (Prim.Maybe ((Prim.Maybe (Prim.Int))))) of - Nothing -> (0: Prim.Int) - Just Nothing -> (1: Prim.Int) - Just Just x -> (x: Prim.Int) - -testNested :: ((Prim.Maybe ((Prim.Maybe ((Prim.Maybe (Prim.Int)))))) -> (Prim.Int)) -testNested = - \(v: (Prim.Maybe ((Prim.Maybe ((Prim.Maybe (Prim.Int))))))) -> - case (v: (Prim.Maybe ((Prim.Maybe ((Prim.Maybe (Prim.Int))))))) of - Nothing -> (0: Prim.Int) - Just Nothing -> (1: Prim.Int) - Just Just Nothing -> (2: Prim.Int) - Just Just Just x -> (x: Prim.Int) - -testMethod :: forall (@a :: Prim.Type). ({ testMethod :: ((a :: Prim.Type) -> (Prim.Boolean)) } -> (((a :: Prim.Type) -> (Prim.Boolean)))) -testMethod = - \(dict: { testMethod :: ((a :: Prim.Type) -> (Prim.Boolean)) }) -> - (dict: { testMethod :: ((a :: Prim.Type) -> (Prim.Boolean)) }) - .testMethod - -testTestClass :: Prim.Boolean -testTestClass = - (testMethod: forall (@a :: Prim.Type). ({ - testMethod :: ((a :: Prim.Type) -> - (Prim.Boolean)) - } -> - (((a :: Prim.Type) -> (Prim.Boolean))))) - (testClassInt: { testMethod :: (Prim.Int -> (Prim.Boolean)) }) - (3: Prim.Int) - -testLedgerTypes :: Prim.DCert -testLedgerTypes = (DCertMir: Prim.DCert) - -testIdentitee :: Prim.Int -testIdentitee = - (unIdentitee: ((Lib.Identitee (Prim.Int)) -> (Prim.Int))) - ((Identitee: forall (@a :: Prim.Type). ((a :: Prim.Type) -> - ((Lib.Identitee ((a :: Prim.Type)))))) - (101: Prim.Int)) - -testForLiftPoly :: forall (a :: Prim.Type). ((a :: Prim.Type) -> (Prim.Boolean)) -testForLiftPoly = - \(x: (a :: Prim.Type)) -> - let - q :: (a :: Prim.Type) - q = (x: (a :: Prim.Type)) - g :: (a*3 -> (Prim.Boolean)) - g = \(y: a*3) -> (True: Prim.Boolean) - j :: (a*3 -> ((Prim.Boolean -> (Prim.Boolean)))) - j = - \(c: a*3) -> - \(d: Prim.Boolean) -> - case (d: Prim.Boolean) of - True -> (d: Prim.Boolean) - _ -> (g: (a*3 -> (Prim.Boolean))) (c: a*3) - h :: (a*3 -> ((Prim.Boolean -> (Prim.Boolean)))) - h = - \(a: a*3) -> - \(b: Prim.Boolean) -> - let - i :: forall (b :: Prim.Type). ((b :: Prim.Type) -> (Prim.Boolean)) - i = \(z: (b :: Prim.Type)) -> (False: Prim.Boolean) - in case ((g: (a*3 -> (Prim.Boolean))) (a: a*3)) of - True -> - (i: forall (b :: Prim.Type). ((b :: Prim.Type) -> - (Prim.Boolean))) - (q: a*3) - _ -> - (j: (a*3 -> ((Prim.Boolean -> (Prim.Boolean))))) - (a: a*3) - (b: Prim.Boolean) - in (h: (a*3 -> ((Prim.Boolean -> (Prim.Boolean))))) - (x: (a :: Prim.Type)) - (True: Prim.Boolean) - -testForLiftPolyApplied :: Prim.Boolean -testForLiftPolyApplied = - (testForLiftPoly: forall (a :: Prim.Type). ((a :: Prim.Type) -> - (Prim.Boolean))) - ("hello": Prim.String) - -testCons :: List (Prim.Int) -testCons = - (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (1: Prim.Int) - (Nil: List (Prim.Int)) - -testBuiltin :: Prim.Int -testBuiltin = - (addInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (1: Prim.Int) - (2: Prim.Int) - -testBrokenCollapse :: ((Lib.Identitee (Prim.Int)) -> (Prim.Unit)) -testBrokenCollapse = - \(v: (Lib.Identitee (Prim.Int))) -> - case (v: (Lib.Identitee (Prim.Int))) of - Identitee 1 -> (unit: Prim.Unit) - Identitee x -> (unit: Prim.Unit) - -testBinders :: (Lib.TestBinderSum -> (Prim.Int)) -testBinders = - \(x: Lib.TestBinderSum) -> - case (x: Lib.TestBinderSum) of - ConInt a -> (a: Prim.Int) - ConChar _ -> (5: Prim.Int) - ConNested conNest -> - case (conNest: Lib.TestBinderSum) of - ConInt n -> (n: Prim.Int) - _ -> (2: Prim.Int) - ConQuantified f -> - (f: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int))) - ("hello": Prim.String) - ConConstrained g -> - (g: forall (x :: Prim.Type). ({ - eq :: ((x :: Prim.Type) -> - (((x :: Prim.Type) -> (Prim.Boolean)))) - } -> - (((x :: Prim.Type) -> (Prim.Int))))) - (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) - (2: Prim.Int) - ConNested other -> (7: Prim.Int) - ConObject obj -> (obj: { objField :: Prim.Int }).objField - ConObjectQuantified objQ -> - ((objQ: { - objFieldQ :: forall (x :: Prim.Type). ((x :: Prim.Type) -> - (Prim.Int)) - }) - .objFieldQ) - ("world": Prim.String) - ConObject objs -> - case (objs: { objField :: Prim.Int }) of - { objField: f } -> (f: Prim.Int) - other -> (0: Prim.Int) - -testBindersCase :: Prim.Int -testBindersCase = - (testBinders: (Lib.TestBinderSum -> (Prim.Int))) - ((ConInt: (Prim.Int -> (Lib.TestBinderSum))) (2: Prim.Int)) - -someData :: Builtin.BuiltinData -someData = (iData: (Prim.Int -> (Builtin.BuiltinData))) (1: Prim.Int) - -someDataList :: (Builtin.BuiltinList (Builtin.BuiltinData)) -someDataList = - (mkCons: forall (a :: Prim.Type). ((a :: Prim.Type) -> - (((Builtin.BuiltinList ((a :: Prim.Type))) -> - ((Builtin.BuiltinList ((a :: Prim.Type)))))))) - (someData: Builtin.BuiltinData) - ((mkNilData: (Prim.Unit -> ((Builtin.BuiltinList (Builtin.BuiltinData))))) - (unit: Prim.Unit)) - -testPrelude1 :: Prim.Int -testPrelude1 = - (deserializeInt: (Builtin.BuiltinData -> (Prim.Int))) - (someData: Builtin.BuiltinData) - -polyInObj :: { bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), baz :: Prim.Int } -polyInObj = - let - go :: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int)) - go = \(v: (y :: Prim.Type)) -> (5: Prim.Int) - in ({ - baz: (100: Prim.Int), - bar: (go: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int))) - }: { - bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), - baz :: Prim.Int - }) - -polyInObjMatch :: Prim.Int -polyInObjMatch = - case (polyInObj: { bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), baz :: Prim.Int }) of - { bar: f, baz: _ } -> - (f: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int))) - ("hello": Prim.String) - -plus :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) -plus = - \(a: Prim.Int) -> - \(b: Prim.Int) -> - (addInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (a: Prim.Int) - (b: Prim.Int) - -testMultiCaseSimple :: ((Prim.Maybe (Prim.Int)) -> (((Prim.Maybe (Prim.Int)) -> (Prim.Int)))) -testMultiCaseSimple = - \(v: (Prim.Maybe (Prim.Int))) -> - \(v1: (Prim.Maybe (Prim.Int))) -> - case (v: (Prim.Maybe (Prim.Int))) (v1: (Prim.Maybe (Prim.Int))) of - Nothing Nothing -> (0: Prim.Int) - Nothing Just y -> (y: Prim.Int) - Just x Nothing -> (x: Prim.Int) - Just x Just y -> - (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (x: Prim.Int) - (y: Prim.Int) - -testPlus :: Prim.Int -testPlus = - (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) (1: Prim.Int) (1: Prim.Int) - -or :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) -or = - \(b1: Prim.Boolean) -> - \(b2: Prim.Boolean) -> - case (b1: Prim.Boolean) of - True -> (True: Prim.Boolean) - _ -> (b2: Prim.Boolean) - -opt2Int :: ((Lib.Option (Prim.Int)) -> (Prim.Int)) -opt2Int = - \(v: (Lib.Option (Prim.Int))) -> - case (v: (Lib.Option (Prim.Int))) of - Some i -> (i: Prim.Int) - Nada -> (0: Prim.Int) - -testOpt2Int :: Prim.Int -testOpt2Int = - (opt2Int: ((Lib.Option (Prim.Int)) -> (Prim.Int))) - ((Some: forall (@a :: Prim.Type). ((a :: Prim.Type) -> - ((Lib.Option ((a :: Prim.Type)))))) - (3: Prim.Int)) - -not :: (Prim.Boolean -> (Prim.Boolean)) -not = - \(b: Prim.Boolean) -> - case (b: Prim.Boolean) of - True -> (False: Prim.Boolean) - _ -> (True: Prim.Boolean) - -nestedBinds :: Prim.Int -nestedBinds = - let - g :: forall (a :: Prim.Type). ((a :: Prim.Type) -> (Prim.Int)) - g = \(v: (a :: Prim.Type)) -> (5: Prim.Int) - f :: (Prim.Int -> (Prim.Int)) - f = \(v: Prim.Int) -> (4: Prim.Int) - h :: Prim.Int - h = - let - i :: Prim.Int - i = - (g: forall (a :: Prim.Type). ((a :: Prim.Type) -> (Prim.Int))) - ("hello": Prim.String) - j :: Prim.Int - j = (f: (Prim.Int -> (Prim.Int))) (i: Prim.Int) - in (f: (Prim.Int -> (Prim.Int))) (j: Prim.Int) - in (h: Prim.Int) - -nestedApplications :: Prim.Int -nestedApplications = - let - i :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) - i = \(x: Prim.Int) -> \(v: Prim.Int) -> (x: Prim.Int) - h :: (Prim.Int -> (Prim.Int)) - h = - \(v: Prim.Int) -> - case (v: Prim.Int) of - 2 -> (3: Prim.Int) - _ -> (5: Prim.Int) - g :: (Prim.Int -> (Prim.Int)) - g = \(v: Prim.Int) -> (5: Prim.Int) - f :: (Prim.Int -> (Prim.Int)) - f = \(x: Prim.Int) -> (x: Prim.Int) - in (i: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - ((f: (Prim.Int -> (Prim.Int))) - ((g: (Prim.Int -> (Prim.Int))) - ((h: (Prim.Int -> (Prim.Int))) (2: Prim.Int)))) - (4: Prim.Int) - -minus :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) -minus = \(v: Prim.Int) -> \(v1: Prim.Int) -> (42: Prim.Int) - -main :: Prim.Int -main = - let - aFunction4 :: forall (r :: (Prim.Row (Prim.Type))). ({ a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) } -> (Prim.Int)) - aFunction4 = - \(r: { a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) }) -> - (r: { a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) }) - .a - in (aFunction4: forall (r :: (Prim.Row - (Prim.Type))). ({ a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) } -> - (Prim.Int))) - ({ b: ("hello": Prim.String), a: (101: Prim.Int) }: { - a :: Prim.Int, - b :: Prim.String - }) - -litPattern :: (Prim.Int -> (Prim.Boolean)) -litPattern = - \(n: Prim.Int) -> - case (n: Prim.Int) of - 0 -> (False: Prim.Boolean) - 1 -> (True: Prim.Boolean) - 2 -> (True: Prim.Boolean) - 3 -> (True: Prim.Boolean) - 4 -> (True: Prim.Boolean) - _ -> (False: Prim.Boolean) - -litPatternApplied :: Prim.Boolean -litPatternApplied = (litPattern: (Prim.Int -> (Prim.Boolean))) (5: Prim.Int) - -isNullSomeDataList :: Prim.Boolean -isNullSomeDataList = - (nullList: forall (a :: Prim.Type). ((Builtin.BuiltinList - ((a :: Prim.Type))) -> - (Prim.Boolean))) - (someDataList: (Builtin.BuiltinList (Builtin.BuiltinData))) - -irrPattern :: (Prim.Int -> (Prim.Int)) -irrPattern = \(n: Prim.Int) -> (2: Prim.Int) - -identitea :: forall (x :: Prim.Type). ((x :: Prim.Type) -> ((x :: Prim.Type))) -identitea = \(x: (x :: Prim.Type)) -> (x: (x :: Prim.Type)) - -testIdConst :: Prim.Int -testIdConst = - let - const :: forall (a :: Prim.Type) (b :: Prim.Type). ((a :: Prim.Type) -> (((b :: Prim.Type) -> ((a :: Prim.Type))))) - const = - \(p: (a :: Prim.Type)) -> \(q: (b :: Prim.Type)) -> (p: (a :: Prim.Type)) - in (identitea: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((x :: Prim.Type)))) - ((const: forall (a :: Prim.Type) - (b :: Prim.Type). ((a :: Prim.Type) -> - (((b :: Prim.Type) -> ((a :: Prim.Type)))))) - (5: Prim.Int) - (2: Prim.Int)) - -id :: forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type))) -id = \(x: (t :: Prim.Type)) -> (x: (t :: Prim.Type)) - -objForall :: forall (a :: Prim.Type) (b :: Prim.Type). { getIdA :: ((a :: Prim.Type) -> ((a :: Prim.Type))), getIdB :: ((b :: Prim.Type) -> ((b :: Prim.Type))) } -objForall = - ({ - getIdB: (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> - ((t :: Prim.Type)))), - getIdA: (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> - ((t :: Prim.Type)))) - }: forall (a :: Prim.Type) - (b :: Prim.Type). { - getIdA :: ((a :: Prim.Type) -> ((a :: Prim.Type))), - getIdB :: ((b :: Prim.Type) -> ((b :: Prim.Type))) - }) - -testId :: Prim.Int -testId = - (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type)))) - (2: Prim.Int) - -fakeLT :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) -fakeLT = \(v: Prim.Int) -> \(v1: Prim.Int) -> (True: Prim.Boolean) - -testForLift :: (Prim.Int -> (Prim.Boolean)) -testForLift = - \(x: Prim.Int) -> - let - j :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) - j = - \(c: Prim.Int) -> - \(d: Prim.Int) -> - (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (c: Prim.Int) - ((g: (Prim.Int -> (Prim.Int))) (d: Prim.Int)) - h :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) - h = - \(a: Prim.Int) -> - \(b: Prim.Int) -> - (fakeLT: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) - ((g: (Prim.Int -> (Prim.Int))) (a: Prim.Int)) - ((j: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (4: Prim.Int) - (b: Prim.Int)) - g :: (Prim.Int -> (Prim.Int)) - g = - \(a: Prim.Int) -> - case ((h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) (a: Prim.Int) (x: Prim.Int)) of - True -> - (j: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (x: Prim.Int) - (1: Prim.Int) - _ -> - (multiplyInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (x: Prim.Int) - (x: Prim.Int) - in (h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) - (x: Prim.Int) - (3: Prim.Int) - -testForLift' :: (Prim.Int -> (Prim.Boolean)) -testForLift' = - \(x: Prim.Int) -> - let - h :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) - h = - \(a: Prim.Int) -> - \(b: Prim.Int) -> - (fakeLT: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) - ((g: (Prim.Int -> (Prim.Int))) (a: Prim.Int)) - (4: Prim.Int) - g :: (Prim.Int -> (Prim.Int)) - g = - \(a: Prim.Int) -> - case ((h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) (a: Prim.Int) (x: Prim.Int)) of - True -> - (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (x: Prim.Int) - (x: Prim.Int) - _ -> - (multiplyInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (x: Prim.Int) - (x: Prim.Int) - in (h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) - (x: Prim.Int) - (3: Prim.Int) - -eqBool :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) -eqBool = - \(v: Prim.Boolean) -> - \(v1: Prim.Boolean) -> - case (v: Prim.Boolean) (v1: Prim.Boolean) of - True True -> (True: Prim.Boolean) - False False -> (True: Prim.Boolean) - _ _ -> (False: Prim.Boolean) - -eq2 :: forall (@a :: Prim.Type) (@b :: Prim.Type). ({ eq2 :: ((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))))) -eq2 = - \(dict: { - eq2 :: ((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))) - }) -> - (dict: { - eq2 :: ((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))) - }) - .eq2 - -testEq2 :: Prim.Boolean -testEq2 = - (eq2: forall (@a :: Prim.Type) - (@b :: Prim.Type). ({ - eq2 :: ((a :: Prim.Type) -> - (((b :: Prim.Type) -> (Prim.Boolean)))) - } -> - (((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean))))))) - (eq2IntBoolean: ({ - eq2 :: (Prim.Int -> (((b :: Prim.Type) -> (Prim.Boolean)))) - } (Prim.Boolean))) - (101: Prim.Int) - (False: Prim.Boolean) - -eq :: forall (@a :: Prim.Type). ({ eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))))) -eq = - \(dict: { - eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) - }) -> - (dict: { - eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) - }) - .eq - -guardedCase2 :: Prim.Int -guardedCase2 = - let - v :: forall ($36 :: Prim.Type). (($36 :: Prim.Type) -> (Prim.Int)) - v = \(v1: ($36 :: Prim.Type)) -> (0: Prim.Int) - in case (polyInObj: { bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), baz :: Prim.Int }) of - { bar: _, baz: x } -> - let - v1 :: Prim.Boolean - v1 = - (eq: forall (@a :: Prim.Type). ({ - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean)))) - } -> - (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) - (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) - (x: Prim.Int) - (4: Prim.Int) - in case (v1: Prim.Boolean) of - True -> (x: Prim.Int) - _ -> - (v: forall ($36 :: Prim.Type). (($36 :: Prim.Type) -> - (Prim.Int))) - (True: Prim.Boolean) - _ -> - (v: forall ($36 :: Prim.Type). (($36 :: Prim.Type) -> (Prim.Int))) - (True: Prim.Boolean) - -testEqViaOrd :: forall (a :: Prim.Type). ({ compare :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))), Eq :: { eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))))) -testEqViaOrd = - \(dictOrd: { - compare :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Int)))), - Eq :: { - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Boolean)))) - } - }) -> - \(a: (a :: Prim.Type)) -> - \(b: (a :: Prim.Type)) -> - (eq: forall (@a :: Prim.Type). ({ - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean)))) - } -> - (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) - ((dictOrd: { - compare :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Int)))), - Eq :: { - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Boolean)))) - } - }) - .Eq) - (a: (a :: Prim.Type)) - (b: (a :: Prim.Type)) - -testSuperClass :: Prim.Boolean -testSuperClass = - (testEqViaOrd: forall (a :: Prim.Type). ({ - compare :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Int)))), - Eq :: { - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean)))) - } - } -> - (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) - (ordInt: { - compare :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))), - Eq :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } - }) - (1: Prim.Int) - (2: Prim.Int) - -cons :: forall (a :: Prim.Type). ((a :: Prim.Type) -> ((List ((a :: Prim.Type)) -> (List ((a :: Prim.Type)))))) -cons = - \(x: (a :: Prim.Type)) -> - \(xs: List ((a :: Prim.Type))) -> - (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (x: (a :: Prim.Type)) - (Nil: List ((a :: Prim.Type))) - -consEmptyList1 :: List (Prim.Int) -consEmptyList1 = - (cons: forall (a :: Prim.Type). ((a :: Prim.Type) -> - ((List ((a :: Prim.Type)) -> (List ((a :: Prim.Type))))))) - (1: Prim.Int) - (Nil: List (Prim.Int)) - -consEmptyList2 :: List (Prim.String) -consEmptyList2 = - (cons: forall (a :: Prim.Type). ((a :: Prim.Type) -> - ((List ((a :: Prim.Type)) -> (List ((a :: Prim.Type))))))) - ("hello": Prim.String) - (Nil: List (Prim.String)) - -compare :: forall (@a :: Prim.Type). ({ compare :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))), Eq :: { eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))))) -compare = - \(dict: { - compare :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))), - Eq :: { - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Boolean)))) - } - }) -> - (dict: { - compare :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Int)))), - Eq :: { - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Boolean)))) - } - }) - .compare - -brokenEven :: (Prim.Int -> (Prim.Int)) -brokenEven = - \(n: Prim.Int) -> - case ((eq: forall (@a :: Prim.Type). ({ eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) (n: Prim.Int) (0: Prim.Int)) of - True -> (1: Prim.Int) - _ -> - (brokenEven: (Prim.Int -> (Prim.Int))) - ((minus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) - (n: Prim.Int) - (2: Prim.Int)) - -arrForall :: List (forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type)))) -arrForall = - (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type)))) - (Nil: List (forall (a :: Prim.Type). ((a :: Prim.Type) -> - ((a :: Prim.Type))))) - -apIdentitea :: Prim.Int -apIdentitea = - (identitea: forall (x :: Prim.Type). ((x :: Prim.Type) -> ((x :: Prim.Type)))) - (2: Prim.Int) - -and :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) -and = - \(p: Prim.Boolean) -> - \(q: Prim.Boolean) -> - (not: (Prim.Boolean -> (Prim.Boolean))) - ((or: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - ((not: (Prim.Boolean -> (Prim.Boolean))) (p: Prim.Boolean)) - ((not: (Prim.Boolean -> (Prim.Boolean))) (q: Prim.Boolean))) - -equalsC :: ((((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean)))) -> (((((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean)))) -> (Prim.Boolean)))) -equalsC = - \(v: (((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) -> - \(v1: (((Lib.C - (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) -> - case (v: (((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) (v1: (((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) of - C i1 s1 Just b1 C i2 s2 Just b2 -> - (and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - ((equalsInteger: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) - (i1: Prim.Int) - (i2: Prim.Int)) - ((and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - ((equalsString: (Prim.String -> ((Prim.String -> (Prim.Boolean))))) - (s1: Prim.String) - (s2: Prim.String)) - ((eqBool: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - (b1: Prim.Boolean) - (b2: Prim.Boolean))) - C i1 s1 Nothing C i2 s2 Nothing -> - (and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - ((equalsInteger: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) - (i1: Prim.Int) - (i2: Prim.Int)) - ((equalsString: (Prim.String -> ((Prim.String -> (Prim.Boolean))))) - (s1: Prim.String) - (s2: Prim.String)) - _ _ -> (False: Prim.Boolean) - -iff :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) -iff = - \(p: Prim.Boolean) -> - \(q: Prim.Boolean) -> - (or: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - ((and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - (p: Prim.Boolean) - (q: Prim.Boolean)) - ((and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) - ((not: (Prim.Boolean -> (Prim.Boolean))) (p: Prim.Boolean)) - ((not: (Prim.Boolean -> (Prim.Boolean))) (q: Prim.Boolean))) - -anObj :: { foo :: Prim.Int } -anObj = ({ foo: (3: Prim.Int) }: { foo :: Prim.Int }) - -objUpdate :: { foo :: Prim.Int } -objUpdate = - let - v :: { foo :: Prim.Int } - v = (anObj: { foo :: Prim.Int }) - in (v: { foo :: Prim.Int }) { foo = (4: Prim.Int) } - -anIntLit :: Prim.Int -anIntLit = (1: Prim.Int) - -aVal :: Prim.Int -aVal = (1: Prim.Int) - -aStringLit :: Prim.String -aStringLit = ("woop": Prim.String) - -aPred :: (Prim.Int -> (Prim.Boolean)) -aPred = \(v: Prim.Int) -> (True: Prim.Boolean) - -guardedCase :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) -guardedCase = - \(w: Prim.Int) -> - \(x: Prim.Int) -> - let - v :: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> (Prim.Int)) - v = \(v1: ($39 :: Prim.Type)) -> (0: Prim.Int) - in case (w: Prim.Int) (x: Prim.Int) of - y z -> - let - v1 :: Prim.Boolean - v1 = - (eq: forall (@a :: Prim.Type). ({ - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean)))) - } -> - (((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Boolean))))))) - (eqInt: { - eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) - }) - (y: Prim.Int) - (2: Prim.Int) - in case (v1: Prim.Boolean) of - True -> - let - v2 :: Prim.Boolean - v2 = (aPred: (Prim.Int -> (Prim.Boolean))) (y: Prim.Int) - in case (v2: Prim.Boolean) of - True -> - let - v3 :: Prim.Boolean - v3 = - (eq: forall (@a :: Prim.Type). ({ - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean)))) - } -> - (((a :: Prim.Type) -> - (((a :: Prim.Type) -> (Prim.Boolean))))))) - (eqInt: { - eq :: (Prim.Int -> - ((Prim.Int -> (Prim.Boolean)))) - }) - (z: Prim.Int) - (0: Prim.Int) - in case (v3: Prim.Boolean) of - True -> - let - v4 :: Prim.Boolean - v4 = - (eq: forall (@a :: Prim.Type). ({ - eq :: ((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean)))) - } -> - (((a :: Prim.Type) -> - (((a :: Prim.Type) -> - (Prim.Boolean))))))) - (eqInt: { - eq :: (Prim.Int -> - ((Prim.Int -> - (Prim.Boolean)))) - }) - (y: Prim.Int) - (nestedBinds: Prim.Int) - in case (v4: Prim.Boolean) of - True -> (2: Prim.Int) - _ -> - (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> - (Prim.Int))) - (True: Prim.Boolean) - _ -> - (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> - (Prim.Int))) - (True: Prim.Boolean) - _ -> - (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> - (Prim.Int))) - (True: Prim.Boolean) - _ -> - (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> - (Prim.Int))) - (True: Prim.Boolean) - -aList2 :: List (Prim.Int) -aList2 = - (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (1: Prim.Int) - ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (2: Prim.Int) - (Nil: List (Prim.Int))) - -aList :: List (Prim.Int) -aList = - (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (1: Prim.Int) - ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (2: Prim.Int) - ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (3: Prim.Int) - ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (4: Prim.Int) - ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (5: Prim.Int) - (Nil: List (Prim.Int)))))) - -aFunction3 :: (Prim.Int -> (Prim.Int)) -aFunction3 = - \(x: Prim.Int) -> - case ((eq: forall (@a :: Prim.Type). ({ eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) (x: Prim.Int) (2: Prim.Int)) of - True -> (4: Prim.Int) - _ -> (1: Prim.Int) - -aFunction2 :: (Prim.Int -> (List (Prim.Int))) -aFunction2 = - \(x: Prim.Int) -> - (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (x: Prim.Int) - ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> - ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) - (1: Prim.Int) - (Nil: List (Prim.Int))) - -aFunction :: forall (x :: Prim.Type). ((x :: Prim.Type) -> ((forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int)) -> (Prim.Int)))) -aFunction = - \(any: (x :: Prim.Type)) -> - \(f: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int))) -> - (f: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int))) - (any: (x :: Prim.Type)) - -aBool :: Prim.Boolean -aBool = (True: Prim.Boolean) \ No newline at end of file diff --git a/tests/purus/passing/CoreFn/Misc/output/Lib/externs.cbor b/tests/purus/passing/CoreFn/Misc/output/Lib/externs.cbor deleted file mode 100644 index 067aab035d14614177e86273c81adbf871f512d6..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 74204 zcmeG_&u?7S)iboAl#oKfggdQUD5OBZjuR7q`O(lcaU5dT2`QnhD#Y{58~fSgnep=s zC7-$&|7hS#RjCqE7Oh$rRf*{$~s6$Uidrb+;`u*cV?dL zd+tk!gcor4+xUtjF77;uLIwg14Qxq z#I#=obo24|35bgtk#$M9gZtGqEW_TsLr|Zol2DMMdA>TPj-But-Wz@qH4%SU<0G6o zcEx87_z2#N- zv4Q4CZ@xLpN8x+NYc&TFd~ZCMcMxNl;2jc;z&qKj7I9YM3t>9O;Xp`&lm>`Q#I%VlrIAAgfS_{5P{`Ji?H*Fy(kR8X2Db8iKn6PhZbIoGWFVHWFVNN@u1|60hm)dmt2m5eDzg_%z-Rv+%HY~A+DDkX6xxn&^YUXyMzwe-&}&k*%GINFmxtpY91<0 zxLW0_mm(uf+?8g@cbGIQiW0XqPZ-RfX;vy&Kts0NkOe_hxN;EBj8|6`CKoIi$3{!E zPIpvQ6b)bCmm|DkENpng4n=~pKj*eKp7iIMUS)omFAS)DK^46Tt3g~7oC{{_6^BGR zL~L*PrDnARrL6YT;?-ShT6Kdmr;-Y7Jjl8sU+!~Ak3@2A7LrRp zT;8^vn>jM+SN#wcGo_y|<#IXvx0s{YLYWejlos;of9U&j8~nvAY`MUnpw+>`Ydu`$ zT38}vYb(pS(%CSWUC1ra|I4|_sD1!HQQyXY(^^~keQqJY4P4{prQBj3x2P6@30m^2 z-@JssQK0zS+ANx29amuuAEv434{^P$;fU7X>X(p5XupJ<1b^}1Vr~NFY3&y{>BDax z0Fr1L)qe$(@>*+U>08NO*!$mIT+Y3tgx^}odEU}C_>s*HTOr>k3b@JECw|mIQb=wf z1Dt)AA2tTKkTX6egkz@OT3OB;zs{PNwbt@?teNZo9`e>Ne&`0w5NrQqH1gxRP^VON zjzndrrihbATUpDMBh@Edq#6Trr1~U{{8VOAmBjR9E>#Y1LMX9nj#$LVwwM$9(eq&s zI}4|O0&Me%9$ki3?haeGS$KO26%0S``R-D#NBqFv#}%NpwtBY1h&yx%@_n0#c$i~> zDH62y=pKlYJo!a{_VNP@?8zuL67{UOm?A%WZXk-F{4}?nRCx=y?f|+jc93M@yJG+M zmmnHEsSifp+lhR_nh~*I{0Om&pLC$#bS?lJ<5@(9R6g6&j7+&?1RpW@c1V{azt|xv7iU`@x2}0?LvQ5{-(4%}wDo}Q($V!q#$YU)pQ@dnv)f34w zB`Eb{Qn3dklh&Qq8AI$>6c0bOlzSMwK^xa9yGWYUvIrw-)G!=P6O@#LB?34o3EJK?nx1%l6#xWMntcCpGj-}j#AS>GiFu{G_ zuvV%;TH|?Kj-M={F>_yrf5jw6qjSrQ?|ML6x`7_S-&^hLSL?p@{`=t;F>za$Se&nyyZc z%<=NnCm?HN6+#uDJ;Tw6UytHAi|coF+{ zHh0c?Jx$u=P0H`>1Mb#FBA$2eN#97kHvwZ~*ORLq6-L@OHS!Y1}k&K|Y`wB}_eg#4Y4 z>8sB;0kFq~)En(MwE1Fdo;zWOk0*o((4KJUXWQAmo6Q~<5@B?8p%CoRU>h1rL0gg% zBHSw0?#-|juIR;`@m?r6SQ}>oYR!%41(y-M-8WGg*oX(Cafu~l(F=Q_B#bsGW922f zSj1jT&q6UlJS$#gNH_+ymq`Me?0xcGSv-phd)Dv?TFVe&T^A0jijiY&wxtdj)iLO9 z7unowlL~_#o*`}ggtOH3L{!Mg4F zE(vjC%4L?T9MQR!pDI#JbIb2~m8QQ}>Jx7e`kM6FMS=HB3@xl@tLu;K1K%!ehTFyI z%@HxEec;;#olY>SQ9(~^-FkkMl6Vy64*)Q6J8pePTCb_KZR8nMptsiN{97K!~y5Gv4m+YN#CY^Nc|*#)l+ zY%}_{kDG8`d)cL(_-Gru?c?1cCG~tr`f%-A^ifag6bO^IOE320OwBuS5rZ<+phnfq zF7{0ZIw;q4JI6z6v|4G#JUM_e=+9Uj49ijre_oeu>cN$T{8F~3H=;}^w)o6iBE+D5 zQ$%v;$lhGyqfYkbvUOfbzt}oC>co&F299skd8Lf^K1CN>q);N41+klAzeM~YlSM(= zOx}q+)6-*ZnL*n}vcL_N9GH1(e}ZY1_AyzxZqSjj6|d|!$Wx~&M)+2TBppDv;uUqc ziJ^7QSKh05)#k`;AG`RqT*t*REraEFT10C{ooPI4ncX3{EMv8Yq`KB(w)r3Ro8Sci z48PktT%OS?Y3p!#+SLw>kiJgvQ;jI~e2hjBOOuuZ+Oi+3O}G=AJl4R#dje{B)6tAJdye9Ux7V_SE_9}Rds&cQ1pXy4GtAFd7 z=xem4fV9|0;{=w&!%HNCKAnfSeq>+NSG4SIWh+q*XZ?|O+gzlDw$t`J3B!0!L6ej? zB@Qu-=ahJs;Gfq8FO3K9x3jY2Q(|{S3tfiCg6$_dq^m(=Yjn$nC8|Cmqo1Ywbb&B# z#Q??Zi$r4YPYJBO)twTr(6~doS{?jJ(K48^OgWtWPbAT9{*=7#Bg=?ZhBJzD&ZvO> zCF`9L32HQK>Z^S_GH`coR6O01cMsIWgqRj5MF4jXRN&qL263V{!q_GaPJnA_Nxc$Ax~*1JHx{S39W z4u&egH*X!xv){Ir^L=5!TWj&QC#qrnyR{boCa%SKKAo)I?}9tquQaym0UJF*k7Wv2 zDqzjTeyNbalC@aY61tQ$XsN)nylxeQ`@#lQU16&x;h(Gyv`;VTD`WY}0`HwUPLJE$U*jysu{1mmJAL-%9fR7- zV4Q;dxcTluTs33hlU&FrmAaKj7$|8Q3ninKj?}RSdNwhVIlY){UEcod5WoH_~aj4N=#VIGCOrSA*khai#*;)SU6Jw@9d6;Wesd|VK_B3x}&L6~iVMY!HL`1Omw%b*@TDdm1M@*#R56-n(`_QKh zbj!GhYhkxEYRkAgGRt)1?h=mW92T3nR^7)yK6C7h|Jw$<7`Uleo~MQ^g27h?0frII zKM>D>TYn%17~x#O?$VR|nb^VoVneB6NjIam$W%IZt~uKUuxomW zyLj`Ba37=R@*?)AT@<3-cd-L5LOaMoOHuBkcuB{r@+f&+NfC`H2yyG|NcMi8#(fvT z%ZY>t)l`Lh-%3nhDjdW zUw`V>aEt_(ytllHJ+U9cm6+ngM|AsC#L{C<-h6Y`KA*jWBDe(Z@Rq(PH|a`GkfMPQ!(Q*^m1x+QOaj;J(sD(g|xW9+Uw{tW$>4U(IFmt zzI|)H;^R41&s??=#o8`cq6(HH(UUapDcve!i873o4sBe9zEwCta-Kua5Yc1Qqu5q@ zgm9f;S*e2M@bGgQ_ZMAd%CS;O%d4$yCCcIKSR_#`hG5KIfHz7HbMTE4zHwbr3g6Fg zew&U1CSx-A7$=yI#g7^Kk3sF3`WSEK``F0dVuxa2BOW>?N&C3_F<$?M!eG!KL5+TL z=G^!(%|b**=j@m$`xSfsK0!f!!n(CM2DKN>C#dXCvQoArq(j*ZvQT3vj5a?-m!dlz zk2ix#BdFSA{x>E!|L&UHlxE>EQhSX5p+@-s2qRpoM6gt^G#Q(dpW$NXGq_#R-i~5W zdrm&X#n5L)3hChal8}xC8-pWM8B-VvlpzegCh(XOkpTchA=2ox@BI(>0r^fBq^PN&)TGK(dDNo5Y433 zgdNHrlwm1 z%O@RoAiu=u1X$YSZ-2b*ORQLeQ0#Y(6r{a!yAV$ce9TRQ+Qjs)>m{$jh*@7@ee5eV z8f%M|phn`x*6>$2D}M#4w`|VgZZdy`^BJOX)-fQ71Y@t|1ePJxE*vC^uGcE(M|qyS zii%#vgR|C(mY~@vdKDGDDh4A(PY6$hjI+?IC?-V1yK!ZeHo{h+M@=&nX2EQgPJAIP z_Te>wWoU&?=B%0x74cMOUoca&yv!==rc0E=*+8USO*=SMLc#1Q`_8{rI`_URey-Wv z|1z2pSLw_<;%Otxeg**~kvG~$mjsp}S>-kw2XS<%#?j@p*C%FGL`hz4$TljJZgM}uaF_#teX$FYr!J=VW< zfYrG9G3U`NfX`O6aBq}@Xk%!WXm`u8U)DouB3j#9&ybCXo)_)&8x7jnBBf$IOUWbnE2JX_5v@qVg0l-xI$DOo6Tnbe&?2XLU8|SeVVjnAL z+$DjL_}_`|IML#^nj%f&?YHhwwD+9&=u$@%{zOn>%s4&YL8It_Fblc7eLoq1LIDgB z7#&318K(yeNRk|e@o3NtZ|jk>U60vql7vNksL$qL39=D!)7#2gv>aldQKHS578`jo>hEFl@Nn8g2%M$5lRIFHtV6YnK)Y>naK1w3#i z@wq`W0z?5#_lo0ew68->*6>=Qz)D zeyQ-WEGLF$S`~0$=2S-du3jMx@OG| z>rjJEF@#Q0(HZ~-89I2H>T*vThb(Y;NAD}X9?JUXJMkirY$W+e18N_WX1`dA44V3I zE31(2GdIP_!qW$Af7Wn~ZZrT6c#j&w@bI8sA>S{4XunOO19SL~N7mNd_gtVdqU08M zulb?+Qnjca;8WU>=Z!Tx!W}>DV`5f%TAloX+=DH`LEl+X#|=8+bMl>jS|%|yo&Ym6 z-Vcp9U~5K8XsmEXUK$beC@=1;qdCSL(NB9UT&c#u9I4V&+izT=;v`i`Oi$)g5p&Wbl3&oE+DC9Qc`R;nWKPCR`x&o~HjMhVXD%Vyu}p}iO~~XU zM}A#Ajv`+4=%5Ns^yr}aK_Uz;t#9OB$pH4V?WQ5N0_i610E3V$r-ZFQiqq3p zAYBn#fplJfI2WuUEs$;;ilR$wRCJ|0CkcL8$JVw-3Sm^%BZccGw)C>#WU)3|_d@&L z#yH&Y)*M?IXxF=@K&o*P>6E^5vW#zJ2D-Ll{Tdf|7451*>WJyAj10WjxB%7N%0ky# zYppv}b-``Bk-4`555fqe2slVpmqFO#VQ$C`Vsm~WKPa9hc^TK|*uJ8MXnrcO9c?i* z7emWiais2wAQ;9|YDfzeBnRP+9o7u6j$|0msUbbIIf%MqL=O#`5k3aRUa6NsUCS;@ z*q9z>NpcR7b95}BiXrT z-4BN=-n{)Go>cBU&DWb1;ScA!vSQM$3b;GxDH# zPS-Up_c`Q<=QVmb?F$Fx#>YXtEitKW^644W=#iKA+I8I=6bBH)LGiN=dKi9rh$c5w zmlH6<<`0o69x_f$xkSr|lgD}fypGjz1Vg=qT&c#u9I47u;~~?-o#ZOXd5X6YzmE5C zjh8G>mzI zj+XkeGtMrW9g!PPN74^t)7==*N-!Rj?N7cJ@<*xUag=l8j1J5Y=uzq%J!+g+iOq$B zPjX^3Hc)e~?U6g+3l8(bSG;*9nbMT1QN460ekAm>a4e89^Ntbw@B{}p5g5aV%M1B2 z^VWX3(`nzsKZdtpA-4UTnNEXdXl@J-@!{ARy_D4(7ej_-Q~aPYCe|Ad$C{{xjOpcVDr>wgc5zH30cJ?>ZR&V>JEMz33i*f_zB~c^h+aKZxrEWTBXW#m+)6eq3Mnr@;dC*6G{$1J#+kW_4!n!aIRotV2)s9id;6k%Us-F@zULR>{F?-EbgLk(yTEkml;BzA#0rB zSz`js5c&*R<4k7O7!i||HO`PhaRn0ta|9!;aV9%!RJ>$mjWg03Q8+2qNSXb(Uz+qo zd_aU#M0}qz`}fU@Q2Z0ae%Qe2Zn_dQ&U&yw466*Yzet(TMG&zQFhjc+$uur@FGz9l zNlpwmVy@RNQVj-$lA_hQMCSao`a>G!!}L+6gD~W4_7chC5||A`vk5Rm6PHM{mon3A zL`)W%y+krcp=g>VD*;cMny=0J_{6mxcVFqq@pubh#*8H5z?KXkm;BuFBx@ zj7qcQ?_-SfS1KU?wWB8;BSA&c&$zGF0$S$~*trS>Qy}7^X%`^vDnc^}h)9zq+EP2pH9+USQbW zrxc|=1s8AvW^nZ>bu4|_z15S0Pjb>3%k7s%pUQnGl!`X7sYO2?_wj}q;<`$wZLW$T zj;s@4hHNz8q+}k42M$7ty;qGSf*Uv!;+$m4;UZRure-Ix$b#QhbH>{eO#Z6uWVmX+ zXGVe{y}c8k`_nWb<(6B>tt@$*Eb?lakuKzySVy6+rmGiGa<)O&5lnP;%^O}}%->gK zL)TTYkGIE?DmxY})HZTeyu#atUq|dLYW8EUgkd;qjmZ-|-Y`C7=M7Uzn;16p3{R>e zI?;0)gw~O5=KvWSIEDK}Ky4q><3b#vS=!$#wV%0P;I8gHXXfrX*4M($UGvN~+gkr) z7t52a#*p>l+9lC)w$oBO@{Ikt9eu{$+-l*um-4$_rRncg-|SQ046flCtL)F=tA!+f zyH=ZP+tF>W@fOz!Fe6F4M)kLAnbqGSVvN)|URv099J+gFh?-5Tz}2%eu{%L z2V+D|_e!z-I_{cm!a?C^X{8c28swxu*Yqm$oYma*N6;d#i*uaSTmsAx({*`p;ktPz zSuA*lcPVmMr7H!@c(WDcC#49zBlhZzVCAL3DnfJc&^qC|(Z9mn>$pz+8Q0AV7o&S1 zIeL)`j_c6j%;8Hx8)Xdtw0C~OXQ6vWT09VwR1uUnvAClvIk_$*FZ4uc7Bi!gnP2M6 zIQfvG=M*a-DCmPu(EE6@i1Z+DM{@Bbd4%aYtU5Il;rbHXTT2lZc2E*~b8)7_65ne) zAw|&eOhiJBgERdiCMH3roQY-7;}RjbLl=ZF*Ue)U`g9YX>BBdi&IPme3g_hT4Otw$ z!7F2G&@C~P~*W5Ej|Apv9H$=f` z)TwYhjgmhD|5)$!+@U72J8&46;e81(Lqd0C$>2_QB?Cnc>s65m*x0L=QJ5nbsv6zl ztUz=kdINs$x69qhxgk4bkFv~kr2dv>~mFS!-+L`)KKnQn1Mu20c+yST+%;uhy- z;pG6IbASmSt}Ep6)i#C^B)|;8ugY)>&%Ei(#SzJY99G>%@sf>Au1c#~<=JEmosCV> zTX?8s<2fOwO|Htz4cgxMLu7y0hDI9A>Tg20rYk3+eo^`!{s{IftZiinbdT>aT9$CQ zwT0HgqRoEBjy!ZVEazs9O!`$ngx5(+aJzplhyQfa;aZ}_obS&ui4_HCqZI|?kv0~& zqOdu7iz9P`a0`b&HwYBtMi0EL%aO7;02Ntrz`YV$PZ9SdZ0rB)-(gEbfV$rY8$J~Q@hmKlm8E6K8p?j From 58ec00e6abb7cb3cd274c222a86fddff262dff0b Mon Sep 17 00:00:00 2001 From: gnumonik Date: Mon, 16 Dec 2024 22:44:06 -0500 Subject: [PATCH 2/4] Escalate incomplete cases from warning to error + remove unnecessary traces in PureScript.Make --- src/Language/PureScript/CST/Convert.hs | 6 ++--- src/Language/PureScript/CoreFn/Desugar.hs | 4 --- .../PureScript/CoreFn/Desugar/Utils.hs | 3 +-- src/Language/PureScript/Make.hs | 14 ++-------- src/Language/PureScript/TypeChecker/Types.hs | 7 ++++- src/Language/Purus/Make.hs | 26 +++++++++++++++++++ 6 files changed, 37 insertions(+), 23 deletions(-) diff --git a/src/Language/PureScript/CST/Convert.hs b/src/Language/PureScript/CST/Convert.hs index efbce13b..de448589 100644 --- a/src/Language/PureScript/CST/Convert.hs +++ b/src/Language/PureScript/CST/Convert.hs @@ -85,11 +85,9 @@ srcTokenRange = tokRange . tokAnn type signature in scope when we convert the declaration. -} -groupSignaturesAndDeclarations :: (Show a) => [Declaration a] -> [[Declaration a]] +groupSignaturesAndDeclarations :: [Declaration a] -> [[Declaration a]] groupSignaturesAndDeclarations [] = [] -groupSignaturesAndDeclarations decls = - trace ("DECLARATIONS (grouping): \n" <> concatMap ((<> "\n\n") . show) decls) $ - go kindSigs typeSigs decls' +groupSignaturesAndDeclarations decls = go kindSigs typeSigs decls' where ((kindSigs, typeSigs), decls') = foldr diff --git a/src/Language/PureScript/CoreFn/Desugar.hs b/src/Language/PureScript/CoreFn/Desugar.hs index d60a41d0..5c00e190 100644 --- a/src/Language/PureScript/CoreFn/Desugar.hs +++ b/src/Language/PureScript/CoreFn/Desugar.hs @@ -166,7 +166,6 @@ moduleToCoreFn (A.Module modSS coms mn _decls (Just exps)) = do decls' <- concat <$> traverse (declToCoreFn mn) nonDataDecls let dataDecls' = mkDataDecls mn dataDecls result = Module modSS coms mn (spanName modSS) imports exps' reExps externs decls' dataDecls' - traceM $ prettyStr dataDecls' pure $ result where setModuleName = modify $ \cs -> @@ -219,10 +218,8 @@ lookupType sp tn = do Nothing -> case M.lookup (mkQualified tn mn) (names env) of Nothing -> error $ "No type found for " <> show tn Just (ty, _, nv) -> do - traceM $ "lookupType: " <> showIdent' tn <> " :: " <> ppType 10 ty pure (ty, nv) Just (ty, _, nv) -> do - traceM $ "lookupType: " <> showIdent' tn <> " :: " <> ppType 10 ty pure (ty, nv) getInnerListTy :: Type a -> Maybe (Type a) @@ -238,7 +235,6 @@ getInnerObjectTy _ = Nothing objectToCoreFn :: forall m. (M m) => ModuleName -> SourceSpan -> SourceType -> SourceType -> [(PSString, A.Expr)] -> m (Expr Ann) objectToCoreFn mn ss recTy row objFields = do - traceM $ "ObjLitTy: " <> show row let (tyFields, _) = rowToList row tyMap = M.fromList $ (\x -> (runLabel (rowListLabel x), x)) <$> tyFields resolvedFields <- foldM (go tyMap) [] objFields diff --git a/src/Language/PureScript/CoreFn/Desugar/Utils.hs b/src/Language/PureScript/CoreFn/Desugar/Utils.hs index 957bb428..94d92d58 100644 --- a/src/Language/PureScript/CoreFn/Desugar/Utils.hs +++ b/src/Language/PureScript/CoreFn/Desugar/Utils.hs @@ -562,8 +562,7 @@ binderToCoreFn dict env mn _ss (A.LiteralBinder ss lit) = binderToCoreFn _ _ _ ss A.NullBinder = NullBinder (ss, [], Nothing) binderToCoreFn dict _ _ _ss vb@(A.VarBinder ss name) = - trace ("binderToCoreFn: " <> show vb) $ - VarBinder (ss, [], Nothing) name (dict M.! name) + VarBinder (ss, [], Nothing) name (dict M.! name) binderToCoreFn dict env mn _ss (A.ConstructorBinder ss dctor@(Qualified mn' _) bs) = let (_, tctor, _, _) = lookupConstructor env dctor args = binderToCoreFn dict env mn _ss <$> bs diff --git a/src/Language/PureScript/Make.hs b/src/Language/PureScript/Make.hs index 16d77ae1..b000d2d4 100644 --- a/src/Language/PureScript/Make.hs +++ b/src/Language/PureScript/Make.hs @@ -133,11 +133,10 @@ rebuildModuleWithIndex MakeActions {..} exEnv externs m@(Module _ _ moduleName _ regrouped <- createBindingGroups moduleName . collapseBindingGroups $ deguarded let mod' = Module ss coms moduleName regrouped exps - traceM $ "PURUS START HERE: " <> T.unpack (runModuleName moduleName) + --traceM $ "PURUS START HERE: " <> T.unpack (runModuleName moduleName) -- pTrace regrouped -- pTrace exps ((coreFn, chkSt'), nextVar'') <- runSupplyT nextVar' $ runStateT (CFT.moduleToCoreFn mod') chkSt -- (emptyCheckState env') - traceM . T.unpack $ CFT.prettyModuleTxt coreFn let corefn = coreFn (optimized, nextVar''') = runSupply nextVar'' $ CF.optimizeCoreFn corefn (renamedIdents, renamed) = renameInModule optimized @@ -162,16 +161,7 @@ rebuildModuleWithIndex MakeActions {..} exEnv externs m@(Module _ _ moduleName _ evalSupplyT nextVar''' $ codegen renamed docs exts return exts - where - prettyEnv :: Environment -> String - prettyEnv Environment {..} = M.foldlWithKey' goPretty "" names - where - goPretty acc ident (ty, _, _) = - acc - <> "\n" - <> T.unpack (showQualified showIdent ident) - <> " :: " - <> ppType 10 ty + {- | Compiles in "make" mode, compiling each module separately to a @.js@ file and an @externs.cbor@ file. diff --git a/src/Language/PureScript/TypeChecker/Types.hs b/src/Language/PureScript/TypeChecker/Types.hs index c76603ea..2aaa4863 100644 --- a/src/Language/PureScript/TypeChecker/Types.hs +++ b/src/Language/PureScript/TypeChecker/Types.hs @@ -80,6 +80,7 @@ import Language.PureScript.Types import Debug.Trace import Language.PureScript.Pretty.Values (renderValue) import Language.Purus.Pretty.Types (prettyTypeStr) +import Language.PureScript.Constants.Prim qualified as C moduleTraces :: Bool moduleTraces = False @@ -216,7 +217,7 @@ typesOf bindingGroupType moduleName vals = goTrace ("TYPESOF: " <> T.unpack (run finalState <- get let replaceTypes' = replaceTypes (checkSubstitution finalState) runTypeSearch' gen = runTypeSearch (guard gen $> foldMap snd inferred) finalState - raisePreviousWarnings gen = escalateWarningWhen isHoleError . tell . onErrorMessages (runTypeSearch' gen . replaceTypes') + raisePreviousWarnings gen = escalateWarningWhen (\er -> isHoleError er || isIncompleteCoverageError er) . tell . onErrorMessages (runTypeSearch' gen . replaceTypes') raisePreviousWarnings False wInfer forM_ tys $ \(shouldGeneralize, ((_, (_, _)), w)) -> @@ -259,6 +260,10 @@ typesOf bindingGroupType moduleName vals = goTrace ("TYPESOF: " <> T.unpack (run isHoleError (ErrorMessage _ HoleInferredType {}) = True isHoleError _ = False + isIncompleteCoverageError :: ErrorMessage -> Bool + isIncompleteCoverageError (ErrorMessage _ (NoInstanceFound (Constraint _ C.Partial _ _ (Just PartialConstraintData{})) _ _ )) = True + isIncompleteCoverageError _ = False + {- | A binding group contains multiple value definitions, some of which are typed and some which are not. diff --git a/src/Language/Purus/Make.hs b/src/Language/Purus/Make.hs index 07f43ff9..9877fd77 100644 --- a/src/Language/Purus/Make.hs +++ b/src/Language/Purus/Make.hs @@ -359,6 +359,32 @@ compileDirNoEvalTest path = do hClose h pure $ testGroup "PIR Compilation (No Eval)" testCases +-- Makes a TestTree. Should probably be in the test dir but don't feel like sorting out imports there +compileDirNoEvalTest' :: FilePath -> IO [(String,IO ())] +compileDirNoEvalTest' path = do + allDecls <- allValueDeclarations path + let allModuleNames = runModuleName . fst <$> allDecls + forM_ allModuleNames $ \mn -> do + let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" + outFileExists <- doesFileExist outFilePath + when outFileExists $ + removeFile outFilePath + forM allDecls $ \(runModuleName -> mn, declNm) -> do + let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" + testNm = path <> " - " <> T.unpack mn <> ":" <> T.unpack declNm + (testNm,) <$> do + withFile outFilePath AppendMode $ \h -> pure $ do + result <- make path mn declNm (Just syntheticPrim) + let nmStr = T.unpack declNm + pirStr = docString $ prettyPirReadable result + msg = "\n------ " <> nmStr <> " ------\n" + <> pirStr + <> "\n------------\n" + -- putStrLn msg + hPutStr h msg + hClose h + + compileDirEvalTest :: FilePath -> IO TestTree compileDirEvalTest path = do allDecls <- allValueDeclarations path From 4e63865aeeb06c2803eb45cda872ae3f715c1708 Mon Sep 17 00:00:00 2001 From: gnumonik Date: Wed, 18 Dec 2024 01:27:50 -0500 Subject: [PATCH 3/4] Added exception handler so tests don't all fail if one purs module fails to parse --- purescript.cabal | 1 + src/Language/Purus/Eval.hs | 71 +- src/Language/Purus/Types.hs | 3 + tests/TestPurus.hs | 146 +-- tests/purus/passing/CoreFn/Misc/Lib.purs | 7 - .../passing/CoreFn/Misc/output/Lib/Lib.cfn | 1 + .../CoreFn/Misc/output/Lib/Lib.cfn.pretty | 1057 +++++++++++++++++ .../CoreFn/Misc/output/Lib/externs.cbor | Bin 0 -> 74204 bytes .../passing/NonTerminating/TestInliner.purs | 0 .../ShouldFail/Misc/IncompleteCases.purs | 8 + 10 files changed, 1209 insertions(+), 85 deletions(-) create mode 100644 tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn create mode 100644 tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty create mode 100644 tests/purus/passing/CoreFn/Misc/output/Lib/externs.cbor create mode 100644 tests/purus/passing/NonTerminating/TestInliner.purs create mode 100644 tests/purus/passing/ShouldFail/Misc/IncompleteCases.purs diff --git a/purescript.cabal b/purescript.cabal index 46f3062d..0c3cf93f 100644 --- a/purescript.cabal +++ b/purescript.cabal @@ -526,6 +526,7 @@ test-suite tests plutus-core ==1.30.0.0, regex-base >=0.94.0.2 && <0.95, split >=0.2.3.4 && <0.3, + stm, typed-process >=0.2.10.1 && <0.3, tasty ==1.5, tasty-hunit diff --git a/src/Language/Purus/Eval.hs b/src/Language/Purus/Eval.hs index 0ccdb13f..8b0595ec 100644 --- a/src/Language/Purus/Eval.hs +++ b/src/Language/Purus/Eval.hs @@ -2,8 +2,11 @@ module Language.Purus.Eval ( compileToUPLC, compileToUPLCTerm, + convertToUPLCAndEvaluate, evaluateUPLCTerm, evaluateTerm, + evaluateTermU_, + evaluateTermU, parseData, (#), applyArgs, @@ -22,7 +25,7 @@ import Control.Monad (join, void) import Control.Monad.Reader (Reader, runReader) import Control.Monad.Trans.Except (ExceptT, runExceptT) -import Language.Purus.Types (PIRTerm, PLCTerm) +import Language.Purus.Types (PIRTerm, PLCTerm, UPLCTerm) import PlutusCore ( getDefTypeCheckConfig, @@ -36,7 +39,6 @@ import PlutusCore.Default ( ) import PlutusCore.Evaluation.Machine.Ck ( EvaluationResult (EvaluationFailure, EvaluationSuccess), - unsafeToEvaluationResult, evaluateCk ) import PlutusCore.Evaluation.Machine.ExBudgetingDefaults qualified as PLC @@ -45,10 +47,20 @@ import PlutusIR.Compiler (CompilationCtx, Compiling, compileProgram, compileToRe import PlutusIR.Compiler.Provenance (Provenance (Original)) import PlutusIR.Compiler.Types (coDoSimplifierRemoveDeadBindings) import PlutusIR.Error (Error) -import Control.Lens (over, set) -import System.IO (readFile) +import Control.Lens (set) import PlutusCore.Data qualified as PLC import PlutusCore.MkPlc (mkConstant) +import PlutusCore.Evaluation.Machine.ExBudget ( + ExBudget (ExBudget), + ExRestrictingBudget (ExRestrictingBudget), + minusExBudget, + ) +import PlutusCore.Compiler.Erase (eraseTerm) +import UntypedPlutusCore.DeBruijn ( deBruijnTerm ) +import PlutusCore.Evaluation.Machine.ExBudgetingDefaults (defaultCekParametersForTesting) +import PlutusCore.Evaluation.Machine.ExMemory (ExCPU (ExCPU), ExMemory (ExMemory)) +import UntypedPlutusCore.Evaluation.Machine.Cek qualified as Cek +import Language.Purus.Pretty.Common (prettyStr) type PLCProgram uni fun a = PLC.Program PLC.TyName PLC.Name uni fun (Provenance a) @@ -58,8 +70,8 @@ type PLCProgram uni fun a = PLC.Program PLC.TyName PLC.Name uni fun (Provenance {- Evaluates a UPLC Program -} runPLCProgram :: PLCProgram DefaultUni DefaultFun () -> (EvaluationResult PLCTerm, [Text]) -runPLCProgram (PLC.Program _ _ c) = case evaluateCk PLC.defaultBuiltinsRuntimeForTesting . void $ c of - (result, logs) -> case result of +runPLCProgram (PLC.Program _ _ c) = case evaluateCk PLC.defaultBuiltinsRuntimeForTesting . void $ c of + (result, logs) -> case result of Left _ -> (EvaluationFailure, logs) Right t -> (EvaluationSuccess t, logs) @@ -67,8 +79,7 @@ runPLCProgram (PLC.Program _ _ c) = case evaluateCk PLC.defaultBuiltinsRuntimeFo f # a = PLC.Apply () f a applyArgs :: PLCTerm -> [PLCTerm] -> PLCTerm -applyArgs f [] = f -applyArgs f (arg:args) = applyArgs (f # arg) args +applyArgs f args = foldl (#) f args -- Parse a file containing a "show'd" piece of Data into a PLC term. -- Mainly for testing but might have some other uses. @@ -85,6 +96,11 @@ dummyData = mkConstant () $ PLC.I 0 evaluateTerm :: PIRTerm -> IO (EvaluationResult (PLC.Term PLC.TyName Name DefaultUni DefaultFun ()), [Text]) evaluateTerm term = runPLCProgram <$> compileToUPLC term +convertToUPLCAndEvaluate :: PIRTerm -> IO () +convertToUPLCAndEvaluate t = evaluateTerm t >>= \case + (EvaluationSuccess plcTerm ,_) -> evaluateTermU_ reasonablySizedBudget plcTerm + (EvaluationFailure,logs) -> error (show logs) + {- Compile a PIR Term to a UPLC Program-} compileToUPLC :: PIRTerm -> IO (PLCProgram DefaultUni DefaultFun ()) compileToUPLC e = do @@ -98,7 +114,7 @@ compileToUPLCTerm e = compileToUPLC e >>= \case PLC.Program a b c -> pure (void c) evaluateUPLCTerm :: PLCTerm -> IO (EvaluationResult PLCTerm, [Text]) -evaluateUPLCTerm e = do +evaluateUPLCTerm e = do let input = PLC.Program (Original ()) latestVersion (Original <$> e) withErrors = either (throwIO . userError) pure pure $ runPLCProgram input @@ -127,3 +143,40 @@ runCompile x = -> CompilationCtx DefaultUni DefaultFun () disableDeadCodeElimination = set (ccOpts . coDoSimplifierRemoveDeadBindings ) False + +toDeBruijnUPLC :: PLCTerm -> Either String UPLCTerm +toDeBruijnUPLC t = first prettyStr x + where + x :: Either (Error DefaultUni DefaultFun ()) UPLCTerm + x = deBruijnTerm (eraseTerm t) + +reasonablySizedBudget :: ExBudget +reasonablySizedBudget = ExBudget (ExCPU 100000000) (ExMemory 100000) + + +-- stolen from plutarch + +evaluateTermU :: + ExBudget -> + PLCTerm -> + Either (String, Maybe ExBudget, [Text]) (UPLCTerm,ExBudget,[Text]) +evaluateTermU budget t = case toDeBruijnUPLC t of + Left err -> Left (err, Nothing, []) + Right uplc -> case Cek.runCekDeBruijn defaultCekParametersForTesting (Cek.restricting (ExRestrictingBudget budget)) Cek.logEmitter uplc of + (errOrRes, Cek.RestrictingSt (ExRestrictingBudget final), logs) -> case errOrRes of + Left err -> Left (show err, Just $ budget `minusExBudget` final, logs) + Right res -> Right (res, budget `minusExBudget` final, logs) + +-- for tests +evaluateTermU_ :: + ExBudget -> + PLCTerm -> + IO () +evaluateTermU_ budget t = case evaluateTermU budget t of + Left (msg,mBudg,logs) -> do + let prettyErr = "Failed to evaluate term\nError Message:\n" <> msg <> + (case mBudg of + Nothing -> "" + Just resBudg -> "\nCost: " <> prettyStr resBudg <> "\nLog: " <> prettyStr logs) + throwIO $ userError prettyErr + Right _ -> pure () diff --git a/src/Language/Purus/Types.hs b/src/Language/Purus/Types.hs index 214dcef5..699ea5ce 100644 --- a/src/Language/Purus/Types.hs +++ b/src/Language/Purus/Types.hs @@ -20,6 +20,7 @@ import PlutusCore qualified as PLC import PlutusIR qualified as PIR import Control.Lens.TH (makeLenses) +import UntypedPlutusCore qualified as UPLC type PIRDatatype = PIR.Datatype @@ -34,6 +35,8 @@ type PIRTerm = PIR.Term PIR.TyName PIR.Name PLC.DefaultUni PLC.DefaultFun () type PLCTerm = PLC.Term PLC.TyName PLC.Name PLC.DefaultUni PLC.DefaultFun () +type UPLCTerm = UPLC.Term UPLC.NamedDeBruijn PLC.DefaultUni PLC.DefaultFun () + data DatatypeDictionary = DatatypeDictionary { _pirDatatypes :: Map (Qualified (ProperName 'TypeName)) PIRDatatype -- ^ The datatype declarations & their corresponding PS type name diff --git a/tests/TestPurus.hs b/tests/TestPurus.hs index 99ba046f..546bdae7 100644 --- a/tests/TestPurus.hs +++ b/tests/TestPurus.hs @@ -1,5 +1,5 @@ {-# LANGUAGE TypeApplications #-} -module TestPurus where +module TestPurus (shouldPassTests) where import Prelude import Data.Text (Text) @@ -9,7 +9,6 @@ import Control.Monad (when,unless, void) import System.FilePath import Language.PureScript qualified as P import Data.Set qualified as S -import Data.Foldable (traverse_) import System.Directory import System.FilePath.Glob qualified as Glob import Data.Function (on) @@ -17,26 +16,24 @@ import Data.List (sortBy, stripPrefix, groupBy) import Language.Purus.Make import Language.Purus.Eval import Language.Purus.Types -import PlutusCore.Evaluation.Result -import PlutusIR.Core.Instance.Pretty.Readable (prettyPirReadable) import Test.Tasty import Test.Tasty.HUnit import Language.Purus.Make.Prim (syntheticPrim) import Language.PureScript (ModuleName, runModuleName) -import Control.Concurrent ( threadDelay ) -import Test.Tasty.Providers -import Control.Exception +import Control.Concurrent.STM +import Data.Map (Map) +import Data.Map qualified as M +import Unsafe.Coerce +import Control.Exception (SomeException, try, throwIO, Exception (displayException)) shouldPassTests :: IO () -shouldPassTests = defaultShouldPassTests >>= defaultMain -{- - do - cfn <- coreFnTests - pirNoEval <- pirTestsNoEval - pirEval <- pirTestsEval - let validatorTest = testCase "validator apply/eval" mkValidatorTest - policyTest = testCase "minting policy apply/eval" mkMintingPolicyTest - defaultMain $ sequentialTestGroup "Purus Tests" AllFinish [cfn,pirNoEval,pirEval,validatorTest,policyTest] +shouldPassTests = do + generatedTests <- mkShouldPassTests "tests/purus/passing/CoreFn" + let allTests = testGroup "Passing" [generatedTests,validatorTest,mintingPolicyTest] + defaultMain allTests + +{- The PureScript -> CoreFn part of the pipeline. Need to run this to output the CoreFn + files which the other tests depend upon. (The Purus pipeline starts by parsing those CoreFn files) -} runPurusCoreFn :: P.CodegenTarget -> FilePath -> IO () runPurusCoreFn target dir = do @@ -56,7 +53,7 @@ runPurusCoreFn target dir = do pscmInput = files, pscmExclude = [], pscmOutputDir = outputDir, - pscmOpts = purusOpts, + pscmOpts = unsafeCoerce purusOpts, -- IT IS THE RIGHT TYPE BUT HLS WILL NOT SHUT UP ABOUT IT pscmUsePrefix = False, pscmJSONErrors = False } @@ -68,93 +65,104 @@ runPurusCoreFn target dir = do optionsCodegenTargets = S.singleton target } -mkPIRTests :: FilePath -> IO [(ModuleName,Text)] -> (PIRTerm -> IO ()) -> IO [TestTree] -mkPIRTests path ioInput f = map mkCase <$> ioInput +{- Generated PIR non-evaluation tests (i.e. only checks that the *Purus* pipeline reaches the PIR stage, + does not typecheck/compile/evaluate PIR). + + The TVar should be passed in empty. The path should be the full path to the project directory. The + list of declarations is passed in primarily to make the types line up (can't write this without + returning an IO [TestTree] if we don't pass it in afaict) +-} +-- TODO? withResource? We can do it w/ the TVar arg I think +mkPIRNoEval :: TVar (Map (ModuleName,Text) PIRTerm) -> FilePath -> [(ModuleName,Text)] -> [TestTree] +mkPIRNoEval tv path ioInput = mkCase <$> ioInput where mkCase :: (ModuleName, Text) -> TestTree - mkCase (runModuleName -> mn,dn) = testCase testName $ do - f =<< make path mn dn (Just syntheticPrim) + mkCase (mn'@(runModuleName -> mn),dn) = testCase testName $ do + term <- make path mn dn (Just syntheticPrim) + atomically $ modifyTVar' tv (M.insert (mn',dn) term) where testName = T.unpack mn <> "." <> T.unpack dn -defaultShouldPassTests :: IO TestTree -defaultShouldPassTests = mkShouldPassTests "tests/purus/passing/CoreFn" +{- Generates automated evaluation tests. + The first argument is an evaluation function. We want this as parameter so we can use (e.g.) + variants that don't throw an error if the execution budget is exceeded. + Second argument is the name of the test tree being generated. + Third argument is a TVar which should be *full* (i.e. non-empty) + + Fourth argument is a list of declarations, which, as before, is mainly used to make the types line up. +-} +mkPIREvalMany :: (PIRTerm -> IO ()) + -> String + -> TVar (Map (ModuleName,Text) PIRTerm) + -> [(ModuleName,Text)] + -> TestTree +mkPIREvalMany f nm tv decls = withResource (readTVarIO tv) (\_ -> pure ()) $ \tvIO -> + testGroup nm $ mkPIREval1 tvIO <$> decls + where + mkPIREval1 :: IO (Map (ModuleName,Text) PIRTerm) -> (ModuleName,Text) -> TestTree + mkPIREval1 dict declNm@(runModuleName -> mn,dn) = do + let testName = T.unpack mn <> "." <> T.unpack dn + testCase testName $ do + dict' <- dict + case M.lookup declNm dict' of + Nothing -> error $ "failure: no PIRTerm compiled at " <> show testName + Just term -> void $ f term + +{- Full pipeline tests for things we expect will succeed at the CoreFn -> PIR -> PLC -> UPLC -> Evaluation + path. Reads from the modules in the `tests/purus/passing/CoreFn` directory. + + All functions tested here *should terminate*. +-} mkShouldPassTests :: FilePath -> IO TestTree mkShouldPassTests testDirPath = do allProjectDirectories <- listDirectory testDirPath - testGroup "Purus Passing" <$> traverse (go . (testDirPath )) allProjectDirectories + testGroup "Generated (Passing)" <$> traverse (go . (testDirPath )) allProjectDirectories where - go :: FilePath -> IO TestTree - go path = do --let coreFnTest = testCase ("CoreFn: " <> path) (void $ runPurusCoreFnDefault path) -- this is stupid but idk how to get it to show up in the output unless we do it twice - pirNoEval <- testGroup "No Eval" <$> mkPIRTests path initialize (void . pure) - pirEval <- testGroup "Eval" <$> mkPIRTests path initialize (void . evaluateTerm) - pure $ testGroup ("PIR: " <> show path) [pirNoEval,pirEval] - - + go path = try @SomeException initialize >>= \case + Left err -> pure . testCase ("PIR: " <> show path) $ assertFailure ("Failed during CoreFn compilation with reason: " <> displayException err) + Right decls -> do + declDict <- newTVarIO M.empty + let pirNoEval = testGroup "No Eval" $ mkPIRNoEval declDict path decls + pirEvalPlc = mkPIREvalMany (void . evaluateTerm) "Eval (PLC)" declDict decls + pirEvalUplc = mkPIREvalMany convertToUPLCAndEvaluate "Eval (UPLC)" declDict decls + pure $ sequentialTestGroup ("PIR: " <> show path) AllFinish [pirNoEval,pirEvalPlc,pirEvalUplc] where initialize :: IO [(ModuleName,Text)] initialize = do void $ runPurusCoreFnDefault path - threadDelay 5000 -- not sure if the write will complete before the previous line finishes evaluating allValueDeclarations path +{- Runs the PureScript -> CoreFn part of the compiler pipeline in default mode (i.e. not in Golden mode, i.e. + this actually writes output files in the project directories) +-} runPurusCoreFnDefault :: FilePath -> IO () runPurusCoreFnDefault path = runPurusCoreFn P.CoreFn path -runPurusGolden :: FilePath -> IO () -runPurusGolden path = runPurusCoreFn P.CheckCoreFn path - -runFullPipeline_ :: FilePath -> Text -> Text -> IO () -runFullPipeline_ targetDir mainModuleName mainFunctionName = do - runPurusCoreFnDefault targetDir - pir <- make targetDir mainModuleName mainFunctionName Nothing - result <- evaluateTerm pir - print $ prettyPirReadable result - -runFullPipeline :: FilePath -> Text -> Text -> IO (EvaluationResult PLCTerm, [Text]) -runFullPipeline targetDir mainModuleName mainFunctionName = do - runPurusCoreFnDefault targetDir - pir <- make targetDir mainModuleName mainFunctionName Nothing - evaluateTerm pir - -mkValidatorTest :: IO () -mkValidatorTest = do +{- Manual tests for scripts. These require us to apply arguments and parse an example script context. +-} +-- TODO: Change these so they run through the UPLC evaluator using the new machinery +validatorTest :: TestTree +validatorTest = testCase "Basic Validator Test" $ do scriptContext <- parseData "sampleContext" - -- Data -> Data -> Data -> wBoolean + -- Data -> Data -> Data -> Boolean validatorPIR <- make "tests/purus/passing/CoreFn/Validator" "Validator" "validate" (Just syntheticPrim) validatorPLC <- compileToUPLCTerm validatorPIR let validatorApplied = applyArgs validatorPLC [dummyData,dummyData,scriptContext] res <- evaluateUPLCTerm validatorApplied print res -mkMintingPolicyTest :: IO () -mkMintingPolicyTest = do +mintingPolicyTest :: TestTree +mintingPolicyTest = testCase "Basic Minting Policy Test" $ do scriptContext <- parseData "sampleContext" policyPIR <- make "tests/purus/passing/CoreFn/MintingPolicy" "MintingPolicy" "oneAtATime" (Just syntheticPrim) policyPLC <- compileToUPLCTerm policyPIR let policyApplied = applyArgs policyPLC [dummyData,dummyData,scriptContext] res <- evaluateUPLCTerm policyApplied print res -{- These assumes that name of the main module is "Main" and the - name of the main function is "Main". - - For now this recompiles everything from scratch --} - -runDefaultCheckEvalSuccess :: String -> FilePath -> Assertion -runDefaultCheckEvalSuccess nm targetDir - = (fst <$> runFullPipeline targetDir "Main" "main") >>= assertBool nm . isEvaluationSuccess - -runDefaultEvalTest :: String -> FilePath -> PLCTerm -> Assertion -runDefaultEvalTest nm targetDir expected - = (fst <$> runFullPipeline targetDir "Main" "main") >>= \case - EvaluationSuccess resTerm -> assertEqual nm expected resTerm - EvaluationFailure -> assertFailure nm - getTestFiles :: FilePath -> IO [[FilePath]] getTestFiles testDir = do diff --git a/tests/purus/passing/CoreFn/Misc/Lib.purs b/tests/purus/passing/CoreFn/Misc/Lib.purs index f4ef92c3..99415087 100644 --- a/tests/purus/passing/CoreFn/Misc/Lib.purs +++ b/tests/purus/passing/CoreFn/Misc/Lib.purs @@ -509,10 +509,3 @@ testNestedSmaller = case _ of Nothing -> 0 Just Nothing -> 1 Just (Just x) -> x - -testIncompleteCases :: Int -> Int -testIncompleteCases = case _ of - 0 -> 0 - 1 -> 1 - 2 -> 2 - 3 -> 3 diff --git a/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn b/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn new file mode 100644 index 00000000..4441725b --- /dev/null +++ b/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn @@ -0,0 +1 @@ +{"builtWith":"0.0.1","comments":[],"dataTypes":{"_ctorDict":[[[["Lib"],{"Ident":"ADataRec"}],[["Lib"],"ADataRec"]],[[["Lib"],{"Ident":"ANewTypeRec"}],[["Lib"],"ANewtypeRec"]],[[["Lib"],{"Ident":"C"}],[["Lib"],"C"]],[[["Lib"],{"Ident":"ConChar"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConConstrained"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConInt"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConNested"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConObject"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConObjectQuantified"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConQuantified"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"ConString"}],[["Lib"],"TestBinderSum"]],[[["Lib"],{"Ident":"Constr1"}],[["Lib"],"ASum"]],[[["Lib"],{"Ident":"Constr2"}],[["Lib"],"ASum"]],[[["Lib"],{"Ident":"Identitee"}],[["Lib"],"Identitee"]],[[["Lib"],{"Ident":"Nada"}],[["Lib"],"Option"]],[[["Lib"],{"Ident":"Some"}],[["Lib"],"Option"]]],"_tyDict":[[[["Lib"],"ADataRec"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["hello",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["world",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ADataRec"}]}],"_dDataTyName":[["Lib"],"ADataRec"],"_dDeclType":"data"}],[[["Lib"],"ANewtypeRec"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ANewTypeRec"}]}],"_dDataTyName":[["Lib"],"ANewtypeRec"],"_dDeclType":"newtype"}],[[["Lib"],"ASum"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"Constr1"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"Constr2"}]}],"_dDataTyName":[["Lib"],"ASum"],"_dDeclType":"data"}],[[["Lib"],"C"],{"_dDataArgs":[["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],["b",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],["c",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}]],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],[{"Ident":"value1"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],[{"Ident":"value2"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}]],"_cdCtorName":[["Lib"],{"Ident":"C"}]}],"_dDataTyName":[["Lib"],"C"],"_dDeclType":"data"}],[[["Lib"],"Identitee"],{"_dDataArgs":[["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}]],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}]],"_cdCtorName":[["Lib"],{"Ident":"Identitee"}]}],"_dDataTyName":[["Lib"],"Identitee"],"_dDeclType":"data"}],[[["Lib"],"Option"],{"_dDataArgs":[["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}]],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}]],"_cdCtorName":[["Lib"],{"Ident":"Some"}]},{"_cdCtorFields":[],"_cdCtorName":[["Lib"],{"Ident":"Nada"}]}],"_dDataTyName":[["Lib"],"Option"],"_dDeclType":"data"}],[[["Lib"],"TestBinderSum"],{"_dDataArgs":[],"_dDataCtors":[{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConInt"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConString"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Char"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConChar"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}]],"_cdCtorName":[["Lib"],{"Ident":"ConNested"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}]],"_cdCtorName":[["Lib"],{"Ident":"ConQuantified"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}]],"_cdCtorName":[["Lib"],{"Ident":"ConConstrained"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objField",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ConObject"}]},{"_cdCtorFields":[[{"Ident":"value0"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objFieldQ",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}]],"_cdCtorName":[["Lib"],{"Ident":"ConObjectQuantified"}]}],"_dDataTyName":[["Lib"],"TestBinderSum"],"_dDeclType":"data"}]]},"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["testMethod",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}}]]}},"identifier":"testClassInt"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["eq",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}}]]}},"identifier":"eqInt"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["Eq",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}}],["compare",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":42}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}}]]}},"identifier":"ordInt"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["eq2",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}}]]}},"identifier":"eq2IntBoolean"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[46,29],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[46,26]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Identitee","moduleName":["Lib"]},"typeName":{"identifier":"Identitee","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[48,13]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"unIdentitee"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[138,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[138,21]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Constr1","moduleName":["Lib"]},"typeName":{"identifier":"ASum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"z","type":{"annotation":[{"end":[138,42],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[138,35]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Constr2","moduleName":["Lib"]},"typeName":{"identifier":"ASum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"ASum"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[151,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"ASum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testasum"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"datum","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"redeemer","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"context","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":7,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":6,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"c","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":5,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"testValidator"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":7,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":6,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"c","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":5,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"c"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"testValidator","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"datum"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"redeemer"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"context"}},"kind":"App"},"identifier":"testValidatorApplied"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x1","type":{"annotation":[{"end":[490,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[490,21]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[491,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testRedundantLit"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x1","type":{"annotation":[{"end":[476,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[476,29]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"x","sourcePos":[477,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testRedundantCtors"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[507,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[507,35]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[511,14]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testNestedSmaller"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[500,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[500,35]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[505,20]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testNested"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[11,3]}},"fieldName":"testMethod","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":11,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"testMethod"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":11,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"testMethod","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["testMethod",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"testClassInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"identifier":"testTestClass"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"DCert"],"tag":"TypeConstructor"},"value":{"identifier":"DCertMir","moduleName":["Prim"]}},"identifier":"testLedgerTypes"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"unIdentitee","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":12,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"Identitee","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":101}},"kind":"App"},"kind":"App"},"identifier":"testIdentitee"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[331,1]}},"identifier":"q"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"y","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"c","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"d","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"d","sourcePos":[343,5]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[345,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"c","sourcePos":[343,5]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"d","sourcePos":[343,5]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"j"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"z","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":16,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"i"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":16,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"i","sourcePos":[339,9]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"q","sourcePos":[333,5]}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"j","sourcePos":[342,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"a","sourcePos":[337,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[337,5]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[345,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"},"value":{"identifier":"a","sourcePos":[337,5]}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"h"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},3,14],"tag":"Skolem"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[336,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[331,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":13,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"testForLiftPoly"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":13,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"testForLiftPoly","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"identifier":"testForLiftPolyApplied"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":17,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"testCons"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"addInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"testBuiltin"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"constructorName":{"identifier":"Identitee","moduleName":["Lib"]},"typeName":{"identifier":"Identitee","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[485,36],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[485,33]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Identitee","moduleName":["Lib"]},"typeName":{"identifier":"Identitee","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Identitee"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testBrokenCollapse"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"a","type":{"annotation":[{"end":[65,15],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[65,12]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConInt","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[78,10]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"constructorName":{"identifier":"ConChar","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"conNest","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConNested","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"n","type":{"annotation":[{"end":[65,15],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[65,12]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConInt","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[81,12]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"},"value":{"identifier":"conNest","sourcePos":[80,13]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"f","type":{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,20]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[71,37],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,33]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,40]},[]],"contents":[{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,40]},[]],"contents":[{"annotation":[{"end":[71,44],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,42]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[71,41],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,40]},[]],"contents":{"kind":{"annotation":[{"end":[71,37],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,33]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[71,48],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[71,45]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}}],"constructorName":{"identifier":"ConQuantified","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"f","sourcePos":[83,17]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"g","type":{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,21]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,9]},[]],"contents":[{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,9]},[]],"contents":[{"annotation":[{"end":[20,13],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,11]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[72,45],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,44]},[]],"contents":{"kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,14]},[]],"contents":[{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,14]},[]],"contents":[{"annotation":[{"end":[20,18],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,16]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[72,45],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,44]},[]],"contents":{"kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[20,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[20,19]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,49]},[]],"contents":[{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,49]},[]],"contents":[{"annotation":[{"end":[72,53],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,51]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[72,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,49]},[]],"contents":{"kind":{"annotation":[{"end":[72,38],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,34]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[72,57],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[72,54]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}}],"constructorName":{"identifier":"ConConstrained","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"g","sourcePos":[84,18]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"other","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"ConNested","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":7}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"obj","type":{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[{"annotation":[{"end":[73,16],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,16]},[]],"contents":["objField",{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"contents":[{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"tag":"REmpty"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"}}],"constructorName":{"identifier":"ConObject","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objField",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"obj","sourcePos":[86,13]}},"fieldName":"objField","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"objQ","type":{"annotation":[{"end":[74,68],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,25]},[]],"contents":[{"annotation":[{"end":[74,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,25]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,26]},[]],"contents":["objFieldQ",{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,39]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[74,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,52]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,59]},[]],"contents":[{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,59]},[]],"contents":[{"annotation":[{"end":[74,63],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,61]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[74,60],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,59]},[]],"contents":{"kind":{"annotation":[{"end":[74,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,52]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,64]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[74,68],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,67]},[]],"contents":[{"annotation":[{"end":[74,68],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,67]},[]],"tag":"REmpty"},{"annotation":[{"end":[74,67],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[74,39]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"}}],"constructorName":{"identifier":"ConObjectQuantified","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objFieldQ",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"objQ","sourcePos":[87,23]}},"fieldName":"objFieldQ","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"world"}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"objs","type":{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[{"annotation":[{"end":[73,16],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,15]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,16]},[]],"contents":["objField",{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"contents":[{"annotation":[{"end":[73,32],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,31]},[]],"tag":"REmpty"},{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"}}],"constructorName":{"identifier":"ConObject","moduleName":["Lib"]},"typeName":{"identifier":"TestBinderSum","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"ObjectLiteral","value":[["objField",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"f","type":{"annotation":[{"end":[73,31],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[73,28]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}]]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"f","sourcePos":[89,16]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["objField",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"objs","sourcePos":[88,13]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"other","type":{"annotation":[{"end":[76,29],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[76,16]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[77,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testBinders"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"testBinders","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"TestBinderSum"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"ConInt","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"identifier":"testBindersCase"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"iData","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"identifier":"someData"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"mkCons","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"},"value":{"identifier":"someData","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"mkNilData","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"identifier":"someDataList"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"deserializeInt","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"},"value":{"identifier":"someData","moduleName":["Lib"]}},"kind":"App"},"identifier":"testPrelude1"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":25,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"go"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["bar",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["baz",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["baz",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":100}}],["bar",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":25,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"go","sourcePos":[254,5]}}]]}},"kind":"Let"},"identifier":"polyInObj"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"ObjectLiteral","value":[["bar",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"f","type":{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,22]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[251,39],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,35]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,42]},[]],"contents":[{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,42]},[]],"contents":[{"annotation":[{"end":[251,46],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,44]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[251,43],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,42]},[]],"contents":{"kind":{"annotation":[{"end":[251,39],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,35]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[251,50],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,47]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}}],["baz",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}]]}}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"f","sourcePos":[259,9]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["bar",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["baz",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"polyInObj","moduleName":["Lib"]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"identifier":"polyInObjMatch"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"addInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[210,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[210,1]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"plus"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[468,46],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,43]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[470,35]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[468,33],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,30]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[471,27]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[468,33],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,30]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[468,46],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[468,43]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[472,27]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[472,36]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"testMultiCaseSimple"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"identifier":"testPlus"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b2","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b2","sourcePos":[351,1]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b1","sourcePos":[351,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"or"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i","type":{"annotation":[{"end":[36,22],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[36,19]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Some","moduleName":["Lib"]},"typeName":{"identifier":"Option","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i","sourcePos":[38,8]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nada","moduleName":["Lib"]},"typeName":{"identifier":"Option","moduleName":["Lib"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"opt2Int"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"opt2Int","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":27,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"Option"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"Some","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"kind":"App"},"identifier":"testOpt2Int"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[356,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"not"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":29,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"g"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"f"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":29,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"g","sourcePos":[125,8]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"identifier":"i"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"f","sourcePos":[122,8]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i","sourcePos":[128,16]}},"kind":"App"},"identifier":"j"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"f","sourcePos":[122,8]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"j","sourcePos":[129,16]}},"kind":"App"},"kind":"Let"},"identifier":"h"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"h","sourcePos":[128,8]}},"kind":"Let"},"identifier":"nestedBinds"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[236,5]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"i"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":2}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"v","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"h"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[237,5]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"f"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"i","sourcePos":[236,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"f","sourcePos":[237,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[238,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[239,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"kind":"Let"},"identifier":"nestedApplications"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":42}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"minus"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"r","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"var":"r"},"tag":"TypeVar"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"r","sourcePos":[206,5]}},"fieldName":"a","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"r","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"skolem":31,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"var":"r"},"tag":"TypeVar"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"aFunction4"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"r","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"skolem":31,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Row"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"var":"r"},"tag":"TypeVar"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"aFunction4","sourcePos":[205,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["a",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["b",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["b",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}}],["a",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":101}}]]}},"kind":"App"},"kind":"Let"},"identifier":"main"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"n","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":0}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":2}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":3}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":4}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[395,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"litPattern"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"litPattern","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"App"},"identifier":"litPatternApplied"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"nullList","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinList"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Builtin"],"BuiltinData"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"someDataList","moduleName":["Lib"]}},"kind":"App"},"identifier":"isNullSomeDataList"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"n","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"irrPattern"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[427,1]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":33,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"identitea"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"p","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"q","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"p","sourcePos":[436,5]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":37,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":35,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"const"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":33,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"identitea","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":37,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":35,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"const","sourcePos":[435,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"kind":"Let"},"identifier":"testIdConst"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[277,1]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"id"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":42,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":41,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["getIdA",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["getIdB",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"literalType":"ObjectLiteral","value":[["getIdB",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}}],["getIdA",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}}]]}},"identifier":"objForall"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"testId"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"fakeLT"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"c","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"d","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"c","sourcePos":[323,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[324,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"d","sourcePos":[323,5]}},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"j"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"fakeLT","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[324,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[322,5]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"j","sourcePos":[323,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"b","sourcePos":[322,5]}},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"h"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"j","sourcePos":[323,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"multiplyInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[322,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[324,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[322,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[320,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testForLift"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"fakeLT","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"g","sourcePos":[442,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[441,5]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"h"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"plus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"multiplyInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[441,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"a","sourcePos":[442,5]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"g"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"h","sourcePos":[441,5]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[439,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"testForLift'"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"False","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"False","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v","sourcePos":[0,0]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"eqBool"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[53,3]}},"fieldName":"eq2","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":46,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":45,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"eq2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":46,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"b","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":45,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq2","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq2",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"b"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"eq2IntBoolean","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":101}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"kind":"App"},"identifier":"testEq2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[20,3]}},"fieldName":"eq","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"eq"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$36","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$36"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"v"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"LiteralBinder","literal":{"literalType":"ObjectLiteral","value":[["bar",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],["baz",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"x","type":{"annotation":[{"end":[251,62],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[251,59]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}]]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[289,17]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"identifier":"v1"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[289,17]}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$36","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$36"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$36","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$36"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["bar",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":23,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["baz",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"polyInObj","moduleName":["Lib"]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"identifier":"guardedCase2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dictOrd","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"a","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"b","body":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dictOrd","sourcePos":[0,0]}},"fieldName":"Eq","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"a","sourcePos":[307,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"b","sourcePos":[307,1]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":48,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"testEqViaOrd"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":48,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"testEqViaOrd","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"ordInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"testSuperClass"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"xs","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"},"value":{"identifier":"x","sourcePos":[265,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":50,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"cons"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":50,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"cons","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"consEmptyList1"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":50,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"cons","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"hello"}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"consEmptyList2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"dict","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"dict","sourcePos":[301,3]}},"fieldName":"compare","kind":"Accessor","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":52,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["compare",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["Eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"}},"identifier":"compare"},{"bindType":"Rec","binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"n","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"brokenEven","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"minus","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[29,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"n","sourcePos":[29,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"brokenEven"}]},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"t","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":39,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"t"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"id","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":53,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"identifier":"arrForall"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":33,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"identitea","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"apIdentitea"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"p","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"q","body":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"or","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"p","sourcePos":[359,1]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"q","sourcePos":[359,1]}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"and"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i1","type":{"annotation":[{"end":[460,17],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,14]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s1","type":{"annotation":[{"end":[460,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,18]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"b1","type":{"annotation":[{"end":[460,39],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,32]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i2","type":{"annotation":[{"end":[460,49],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,46]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s2","type":{"annotation":[{"end":[460,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,50]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"b2","type":{"annotation":[{"end":[460,71],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,64]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}}],"constructorName":{"identifier":"Just","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i1","sourcePos":[461,12]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i2","sourcePos":[461,32]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsString","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s1","sourcePos":[461,15]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s2","sourcePos":[461,35]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"eqBool","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b1","sourcePos":[461,24]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"b2","sourcePos":[461,44]}},"kind":"App"},"kind":"App"},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i1","type":{"annotation":[{"end":[460,17],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,14]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s1","type":{"annotation":[{"end":[460,24],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,18]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"i2","type":{"annotation":[{"end":[460,49],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,46]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"s2","type":{"annotation":[{"end":[460,56],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[460,50]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"Nothing","moduleName":["Prim"]},"typeName":{"identifier":"Maybe","moduleName":["Prim"]}}],"constructorName":{"identifier":"C","moduleName":["Lib"]},"typeName":{"identifier":"C","moduleName":["Lib"]}}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsInteger","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i1","sourcePos":[465,12]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"i2","sourcePos":[465,30]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"equalsString","moduleName":["Builtin"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s1","sourcePos":[465,15]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"identifier":"s2","sourcePos":[465,33]}},"kind":"App"},"kind":"App"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"False","moduleName":["Prim"]}},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[0,0]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Lib"],"C"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Maybe"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"equalsC"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"p","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"q","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"or","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"p","sourcePos":[364,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"q","sourcePos":[364,1]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"value":{"identifier":"and","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"p","sourcePos":[364,1]}},"kind":"App"},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"not","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"q","sourcePos":[364,1]}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"iff"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"literalType":"ObjectLiteral","value":[["foo",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}}]]}},"identifier":"anObj"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"anObj","moduleName":["Lib"]}},"identifier":"v"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"copy":[],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"v","sourcePos":[249,1]}},"kind":"ObjectUpdate","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["foo",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"}],"tag":"KindApp"}],"tag":"RCons"}],"tag":"TypeApp"},"updates":[["foo",{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}}]]},"kind":"Let"},"identifier":"objUpdate"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"identifier":"anIntLit"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"identifier":"aVal"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"String"],"tag":"TypeConstructor"},"value":{"literalType":"StringLiteral","value":"woop"}},"identifier":"aStringLit"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"aPred"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"w","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"v1","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"v"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"y","type":{"annotation":[{"end":[225,19],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[225,16]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"VarBinder","identifier":"z","type":{"annotation":[{"end":[225,26],"name":"tests/purus/passing/CoreFn/Misc/Lib.purs","start":[225,23]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[227,3]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"identifier":"v1"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"aPred","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[227,3]}},"kind":"App"},"identifier":"v2"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"z","sourcePos":[227,6]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":0}},"kind":"App"},"identifier":"v3"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"y","sourcePos":[227,3]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"nestedBinds","moduleName":["Lib"]}},"kind":"App"},"identifier":"v4"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v4","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v3","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v2","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"$39","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"$39"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"v","sourcePos":[0,0]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"kind":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"v1","sourcePos":[0,0]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"w","sourcePos":[226,1]}},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[226,1]}}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Let"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"guardedCase"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":55,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":56,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"identifier":"aList2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":3}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":5}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"App"},"kind":"App"},"identifier":"aList"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"ConstructorBinder","binders":[],"constructorName":{"identifier":"True","moduleName":["Prim"]},"typeName":{"identifier":"Boolean","moduleName":["Prim"]}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":4}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"binderType":"NullBinder"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"isGuarded":false}],"caseExpressions":[{"abstraction":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":47,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarVisible"},"tag":"ForAll"},"value":{"identifier":"eq","moduleName":["Lib"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Record"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":["eq",{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"tag":"REmpty"}],"tag":"RCons"}],"tag":"TypeApp"},"value":{"identifier":"eqInt","moduleName":["Lib"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[173,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":2}},"kind":"App"}],"kind":"Case","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"identifier":"aFunction3"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"x","body":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"identifier":"x","sourcePos":[170,1]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":null,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"Cons","moduleName":["Prim"]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Literal","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"},"value":{"literalType":"IntLiteral","value":1}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"Nil","moduleName":["Prim"]}},"kind":"App"},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"List"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"}},"identifier":"aFunction2"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"any","body":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":"f","body":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":58,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"f","sourcePos":[167,1]}},"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"},"value":{"identifier":"any","sourcePos":[167,1]}},"kind":"App"},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":58,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}},"kind":"Abs","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"x","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":59,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"x"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"identifier":"y","kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":58,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":{"kind":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"y"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}],"tag":"TypeApp"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Int"],"tag":"TypeConstructor"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"}},"identifier":"aFunction"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Boolean"],"tag":"TypeConstructor"},"value":{"identifier":"True","moduleName":["Prim"]}},"identifier":"aBool"}],"exports":["compare","eq","eq2","testMethod","testCons","testTestClass","minus","brokenEven","Some","Nada","opt2Int","testOpt2Int","Identitee","unIdentitee","testIdentitee","testEq2","ConInt","ConString","ConChar","ConNested","ConQuantified","ConConstrained","ConObject","ConObjectQuantified","testBinders","testBindersCase","nestedBinds","ADataRec","ANewTypeRec","Constr1","Constr2","anIntLit","aStringLit","aVal","testasum","aBool","aList","aList2","aFunction","aFunction2","aFunction3","testBuiltin","main","plus","fakeLT","testPlus","guardedCase","nestedApplications","anObj","objUpdate","polyInObj","polyInObjMatch","aPred","cons","consEmptyList1","consEmptyList2","id","testId","objForall","arrForall","guardedCase2","testEqViaOrd","testSuperClass","testValidator","testValidatorApplied","testForLift","testForLiftPoly","testForLiftPolyApplied","or","not","and","iff","testLedgerTypes","litPattern","litPatternApplied","irrPattern","someData","testPrelude1","someDataList","isNullSomeDataList","identitea","apIdentitea","testIdConst","testForLift'","C","eqBool","equalsC","testMultiCaseSimple","testRedundantCtors","testBrokenCollapse","testRedundantLit","testNested","testNestedSmaller","testClassInt","eqInt","eq2IntBoolean","ordInt"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[511,21],"start":[1,1]}},"moduleName":["Builtin"]},{"annotation":{"meta":null,"sourceSpan":{"end":[511,21],"start":[1,1]}},"moduleName":["Lib"]},{"annotation":{"meta":null,"sourceSpan":{"end":[511,21],"start":[1,1]}},"moduleName":["Prim"]}],"moduleName":["Lib"],"modulePath":"tests/purus/passing/CoreFn/Misc/Lib.purs","reExports":{},"sourceSpan":{"end":[511,21],"start":[1,1]}} \ No newline at end of file diff --git a/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty b/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty new file mode 100644 index 00000000..d91a4a99 --- /dev/null +++ b/tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn.pretty @@ -0,0 +1,1057 @@ +Lib (tests/purus/passing/CoreFn/Misc/Lib.purs) + +Imported Modules: +------------------------------ + Builtin, + Lib, + Prim + +Exports: +------------------------------ + compare, + eq, + eq2, + testMethod, + testCons, + testTestClass, + minus, + brokenEven, + Some, + Nada, + opt2Int, + testOpt2Int, + Identitee, + unIdentitee, + testIdentitee, + testEq2, + ConInt, + ConString, + ConChar, + ConNested, + ConQuantified, + ConConstrained, + ConObject, + ConObjectQuantified, + testBinders, + testBindersCase, + nestedBinds, + ADataRec, + ANewTypeRec, + Constr1, + Constr2, + anIntLit, + aStringLit, + aVal, + testasum, + aBool, + aList, + aList2, + aFunction, + aFunction2, + aFunction3, + testBuiltin, + main, + plus, + fakeLT, + testPlus, + guardedCase, + nestedApplications, + anObj, + objUpdate, + polyInObj, + polyInObjMatch, + aPred, + cons, + consEmptyList1, + consEmptyList2, + id, + testId, + objForall, + arrForall, + guardedCase2, + testEqViaOrd, + testSuperClass, + testValidator, + testValidatorApplied, + testForLift, + testForLiftPoly, + testForLiftPolyApplied, + or, + not, + and, + iff, + testLedgerTypes, + litPattern, + litPatternApplied, + irrPattern, + someData, + testPrelude1, + someDataList, + isNullSomeDataList, + identitea, + apIdentitea, + testIdConst, + testForLift', + C, + eqBool, + equalsC, + testMultiCaseSimple, + testRedundantCtors, + testBrokenCollapse, + testRedundantLit, + testNested, + testNestedSmaller, + testClassInt, + eqInt, + eq2IntBoolean, + ordInt + +Re-Exports: +------------------------------ + + +Foreign: +------------------------------ + + +Datatypes: +------------------------------ +data ADataRec = + ADataRec ({ hello :: Prim.Int, world :: Prim.Boolean }) + +newtype ANewtypeRec = + ANewTypeRec ({ foo :: Prim.Int }) + +data ASum = + Constr1 (Prim.Int) + | Constr2 (Prim.Boolean) + +data C (a :: Prim.Type) (b :: Prim.Type) (c :: Prim.Type) = + C ((a :: Prim.Type)) ((b :: Prim.Type)) ((c :: Prim.Type)) + +data Identitee (a :: Prim.Type) = + Identitee ((a :: Prim.Type)) + +data Option (a :: Prim.Type) = + Some ((a :: Prim.Type)) + | Nada + +data TestBinderSum = + ConInt (Prim.Int) + | ConString (Prim.String) + | ConChar (Prim.Char) + | ConNested (Lib.TestBinderSum) + | ConQuantified (forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int))) + | ConConstrained (forall (x :: Prim.Type). ({ eq :: ((x :: Prim.Type) -> (((x :: Prim.Type) -> (Prim.Boolean)))) } -> (((x :: Prim.Type) -> (Prim.Int))))) + | ConObject ({ objField :: Prim.Int }) + | ConObjectQuantified ({ objFieldQ :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)) }) + + +Declarations: +------------------------------ +testClassInt :: { testMethod :: (Prim.Int -> (Prim.Boolean)) } +testClassInt = + ({ + testMethod: \(x: Prim.Int) -> + (True: Prim.Boolean) + }: { testMethod :: (Prim.Int -> (Prim.Boolean)) }) + +eqInt :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } +eqInt = + ({ + eq: \(v: Prim.Int) -> + \(v1: Prim.Int) -> + (True: Prim.Boolean) + }: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) + +ordInt :: { compare :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))), Eq :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } } +ordInt = + ({ + Eq: (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }), + compare: \(v: Prim.Int) -> + \(v1: Prim.Int) -> + (42: Prim.Int) + }: { + compare :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))), + Eq :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } + }) + +eq2IntBoolean :: { eq2 :: (Prim.Int -> ((Prim.Boolean -> (Prim.Boolean)))) } +eq2IntBoolean = + ({ + eq2: \(v: Prim.Int) -> + \(v1: Prim.Boolean) -> + (True: Prim.Boolean) + }: { eq2 :: (Prim.Int -> ((Prim.Boolean -> (Prim.Boolean)))) }) + +unIdentitee :: ((Lib.Identitee (Prim.Int)) -> (Prim.Int)) +unIdentitee = + \(v: (Lib.Identitee (Prim.Int))) -> + case (v: (Lib.Identitee (Prim.Int))) of + Identitee x -> (x: Prim.Int) + +testasum :: (Lib.ASum -> (Prim.Int)) +testasum = + \(x: Lib.ASum) -> + case (x: Lib.ASum) of + Constr1 y -> (1: Prim.Int) + Constr2 z -> (2: Prim.Int) + +testValidator :: forall (a :: Prim.Type) (b :: Prim.Type) (c :: Prim.Type). ((a :: Prim.Type) -> (((b :: Prim.Type) -> (((c :: Prim.Type) -> (Prim.Boolean)))))) +testValidator = + \(datum: (a :: Prim.Type)) -> + \(redeemer: (b :: Prim.Type)) -> + \(context: (c :: Prim.Type)) -> + (True: Prim.Boolean) + +testValidatorApplied :: Prim.Boolean +testValidatorApplied = + (testValidator: forall (a :: Prim.Type) + (b :: Prim.Type) + (c :: Prim.Type). ((a :: Prim.Type) -> + (((b :: Prim.Type) -> (((c :: Prim.Type) -> (Prim.Boolean))))))) + ("datum": Prim.String) + ("redeemer": Prim.String) + ("context": Prim.String) + +testRedundantLit :: (Prim.Int -> (Prim.Int)) +testRedundantLit = + \(x: Prim.Int) -> + case (x: Prim.Int) of + 1 -> (1: Prim.Int) + 1 -> (2: Prim.Int) + 1 -> (3: Prim.Int) + _ -> (4: Prim.Int) + x1 -> (5: Prim.Int) + +testRedundantCtors :: ((Prim.Maybe (Prim.Int)) -> (Prim.Unit)) +testRedundantCtors = + \(x: (Prim.Maybe (Prim.Int))) -> + case (x: (Prim.Maybe (Prim.Int))) of + Just 1 -> (unit: Prim.Unit) + Just x1 -> (unit: Prim.Unit) + Nothing -> (unit: Prim.Unit) + +testNestedSmaller :: ((Prim.Maybe ((Prim.Maybe (Prim.Int)))) -> (Prim.Int)) +testNestedSmaller = + \(v: (Prim.Maybe ((Prim.Maybe (Prim.Int))))) -> + case (v: (Prim.Maybe ((Prim.Maybe (Prim.Int))))) of + Nothing -> (0: Prim.Int) + Just Nothing -> (1: Prim.Int) + Just Just x -> (x: Prim.Int) + +testNested :: ((Prim.Maybe ((Prim.Maybe ((Prim.Maybe (Prim.Int)))))) -> (Prim.Int)) +testNested = + \(v: (Prim.Maybe ((Prim.Maybe ((Prim.Maybe (Prim.Int))))))) -> + case (v: (Prim.Maybe ((Prim.Maybe ((Prim.Maybe (Prim.Int))))))) of + Nothing -> (0: Prim.Int) + Just Nothing -> (1: Prim.Int) + Just Just Nothing -> (2: Prim.Int) + Just Just Just x -> (x: Prim.Int) + +testMethod :: forall (@a :: Prim.Type). ({ testMethod :: ((a :: Prim.Type) -> (Prim.Boolean)) } -> (((a :: Prim.Type) -> (Prim.Boolean)))) +testMethod = + \(dict: { testMethod :: ((a :: Prim.Type) -> (Prim.Boolean)) }) -> + (dict: { testMethod :: ((a :: Prim.Type) -> (Prim.Boolean)) }) + .testMethod + +testTestClass :: Prim.Boolean +testTestClass = + (testMethod: forall (@a :: Prim.Type). ({ + testMethod :: ((a :: Prim.Type) -> + (Prim.Boolean)) + } -> + (((a :: Prim.Type) -> (Prim.Boolean))))) + (testClassInt: { testMethod :: (Prim.Int -> (Prim.Boolean)) }) + (3: Prim.Int) + +testLedgerTypes :: Prim.DCert +testLedgerTypes = (DCertMir: Prim.DCert) + +testIdentitee :: Prim.Int +testIdentitee = + (unIdentitee: ((Lib.Identitee (Prim.Int)) -> (Prim.Int))) + ((Identitee: forall (@a :: Prim.Type). ((a :: Prim.Type) -> + ((Lib.Identitee ((a :: Prim.Type)))))) + (101: Prim.Int)) + +testForLiftPoly :: forall (a :: Prim.Type). ((a :: Prim.Type) -> (Prim.Boolean)) +testForLiftPoly = + \(x: (a :: Prim.Type)) -> + let + q :: (a :: Prim.Type) + q = (x: (a :: Prim.Type)) + g :: (a*3 -> (Prim.Boolean)) + g = \(y: a*3) -> (True: Prim.Boolean) + j :: (a*3 -> ((Prim.Boolean -> (Prim.Boolean)))) + j = + \(c: a*3) -> + \(d: Prim.Boolean) -> + case (d: Prim.Boolean) of + True -> (d: Prim.Boolean) + _ -> (g: (a*3 -> (Prim.Boolean))) (c: a*3) + h :: (a*3 -> ((Prim.Boolean -> (Prim.Boolean)))) + h = + \(a: a*3) -> + \(b: Prim.Boolean) -> + let + i :: forall (b :: Prim.Type). ((b :: Prim.Type) -> (Prim.Boolean)) + i = \(z: (b :: Prim.Type)) -> (False: Prim.Boolean) + in case ((g: (a*3 -> (Prim.Boolean))) (a: a*3)) of + True -> + (i: forall (b :: Prim.Type). ((b :: Prim.Type) -> + (Prim.Boolean))) + (q: a*3) + _ -> + (j: (a*3 -> ((Prim.Boolean -> (Prim.Boolean))))) + (a: a*3) + (b: Prim.Boolean) + in (h: (a*3 -> ((Prim.Boolean -> (Prim.Boolean))))) + (x: (a :: Prim.Type)) + (True: Prim.Boolean) + +testForLiftPolyApplied :: Prim.Boolean +testForLiftPolyApplied = + (testForLiftPoly: forall (a :: Prim.Type). ((a :: Prim.Type) -> + (Prim.Boolean))) + ("hello": Prim.String) + +testCons :: List (Prim.Int) +testCons = + (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (1: Prim.Int) + (Nil: List (Prim.Int)) + +testBuiltin :: Prim.Int +testBuiltin = + (addInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (1: Prim.Int) + (2: Prim.Int) + +testBrokenCollapse :: ((Lib.Identitee (Prim.Int)) -> (Prim.Unit)) +testBrokenCollapse = + \(v: (Lib.Identitee (Prim.Int))) -> + case (v: (Lib.Identitee (Prim.Int))) of + Identitee 1 -> (unit: Prim.Unit) + Identitee x -> (unit: Prim.Unit) + +testBinders :: (Lib.TestBinderSum -> (Prim.Int)) +testBinders = + \(x: Lib.TestBinderSum) -> + case (x: Lib.TestBinderSum) of + ConInt a -> (a: Prim.Int) + ConChar _ -> (5: Prim.Int) + ConNested conNest -> + case (conNest: Lib.TestBinderSum) of + ConInt n -> (n: Prim.Int) + _ -> (2: Prim.Int) + ConQuantified f -> + (f: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int))) + ("hello": Prim.String) + ConConstrained g -> + (g: forall (x :: Prim.Type). ({ + eq :: ((x :: Prim.Type) -> + (((x :: Prim.Type) -> (Prim.Boolean)))) + } -> + (((x :: Prim.Type) -> (Prim.Int))))) + (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) + (2: Prim.Int) + ConNested other -> (7: Prim.Int) + ConObject obj -> (obj: { objField :: Prim.Int }).objField + ConObjectQuantified objQ -> + ((objQ: { + objFieldQ :: forall (x :: Prim.Type). ((x :: Prim.Type) -> + (Prim.Int)) + }) + .objFieldQ) + ("world": Prim.String) + ConObject objs -> + case (objs: { objField :: Prim.Int }) of + { objField: f } -> (f: Prim.Int) + other -> (0: Prim.Int) + +testBindersCase :: Prim.Int +testBindersCase = + (testBinders: (Lib.TestBinderSum -> (Prim.Int))) + ((ConInt: (Prim.Int -> (Lib.TestBinderSum))) (2: Prim.Int)) + +someData :: Builtin.BuiltinData +someData = (iData: (Prim.Int -> (Builtin.BuiltinData))) (1: Prim.Int) + +someDataList :: (Builtin.BuiltinList (Builtin.BuiltinData)) +someDataList = + (mkCons: forall (a :: Prim.Type). ((a :: Prim.Type) -> + (((Builtin.BuiltinList ((a :: Prim.Type))) -> + ((Builtin.BuiltinList ((a :: Prim.Type)))))))) + (someData: Builtin.BuiltinData) + ((mkNilData: (Prim.Unit -> ((Builtin.BuiltinList (Builtin.BuiltinData))))) + (unit: Prim.Unit)) + +testPrelude1 :: Prim.Int +testPrelude1 = + (deserializeInt: (Builtin.BuiltinData -> (Prim.Int))) + (someData: Builtin.BuiltinData) + +polyInObj :: { bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), baz :: Prim.Int } +polyInObj = + let + go :: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int)) + go = \(v: (y :: Prim.Type)) -> (5: Prim.Int) + in ({ + baz: (100: Prim.Int), + bar: (go: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int))) + }: { + bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), + baz :: Prim.Int + }) + +polyInObjMatch :: Prim.Int +polyInObjMatch = + case (polyInObj: { bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), baz :: Prim.Int }) of + { bar: f, baz: _ } -> + (f: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int))) + ("hello": Prim.String) + +plus :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) +plus = + \(a: Prim.Int) -> + \(b: Prim.Int) -> + (addInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (a: Prim.Int) + (b: Prim.Int) + +testMultiCaseSimple :: ((Prim.Maybe (Prim.Int)) -> (((Prim.Maybe (Prim.Int)) -> (Prim.Int)))) +testMultiCaseSimple = + \(v: (Prim.Maybe (Prim.Int))) -> + \(v1: (Prim.Maybe (Prim.Int))) -> + case (v: (Prim.Maybe (Prim.Int))) (v1: (Prim.Maybe (Prim.Int))) of + Nothing Nothing -> (0: Prim.Int) + Nothing Just y -> (y: Prim.Int) + Just x Nothing -> (x: Prim.Int) + Just x Just y -> + (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (x: Prim.Int) + (y: Prim.Int) + +testPlus :: Prim.Int +testPlus = + (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) (1: Prim.Int) (1: Prim.Int) + +or :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) +or = + \(b1: Prim.Boolean) -> + \(b2: Prim.Boolean) -> + case (b1: Prim.Boolean) of + True -> (True: Prim.Boolean) + _ -> (b2: Prim.Boolean) + +opt2Int :: ((Lib.Option (Prim.Int)) -> (Prim.Int)) +opt2Int = + \(v: (Lib.Option (Prim.Int))) -> + case (v: (Lib.Option (Prim.Int))) of + Some i -> (i: Prim.Int) + Nada -> (0: Prim.Int) + +testOpt2Int :: Prim.Int +testOpt2Int = + (opt2Int: ((Lib.Option (Prim.Int)) -> (Prim.Int))) + ((Some: forall (@a :: Prim.Type). ((a :: Prim.Type) -> + ((Lib.Option ((a :: Prim.Type)))))) + (3: Prim.Int)) + +not :: (Prim.Boolean -> (Prim.Boolean)) +not = + \(b: Prim.Boolean) -> + case (b: Prim.Boolean) of + True -> (False: Prim.Boolean) + _ -> (True: Prim.Boolean) + +nestedBinds :: Prim.Int +nestedBinds = + let + g :: forall (a :: Prim.Type). ((a :: Prim.Type) -> (Prim.Int)) + g = \(v: (a :: Prim.Type)) -> (5: Prim.Int) + f :: (Prim.Int -> (Prim.Int)) + f = \(v: Prim.Int) -> (4: Prim.Int) + h :: Prim.Int + h = + let + i :: Prim.Int + i = + (g: forall (a :: Prim.Type). ((a :: Prim.Type) -> (Prim.Int))) + ("hello": Prim.String) + j :: Prim.Int + j = (f: (Prim.Int -> (Prim.Int))) (i: Prim.Int) + in (f: (Prim.Int -> (Prim.Int))) (j: Prim.Int) + in (h: Prim.Int) + +nestedApplications :: Prim.Int +nestedApplications = + let + i :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) + i = \(x: Prim.Int) -> \(v: Prim.Int) -> (x: Prim.Int) + h :: (Prim.Int -> (Prim.Int)) + h = + \(v: Prim.Int) -> + case (v: Prim.Int) of + 2 -> (3: Prim.Int) + _ -> (5: Prim.Int) + g :: (Prim.Int -> (Prim.Int)) + g = \(v: Prim.Int) -> (5: Prim.Int) + f :: (Prim.Int -> (Prim.Int)) + f = \(x: Prim.Int) -> (x: Prim.Int) + in (i: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + ((f: (Prim.Int -> (Prim.Int))) + ((g: (Prim.Int -> (Prim.Int))) + ((h: (Prim.Int -> (Prim.Int))) (2: Prim.Int)))) + (4: Prim.Int) + +minus :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) +minus = \(v: Prim.Int) -> \(v1: Prim.Int) -> (42: Prim.Int) + +main :: Prim.Int +main = + let + aFunction4 :: forall (r :: (Prim.Row (Prim.Type))). ({ a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) } -> (Prim.Int)) + aFunction4 = + \(r: { a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) }) -> + (r: { a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) }) + .a + in (aFunction4: forall (r :: (Prim.Row + (Prim.Type))). ({ a :: Prim.Int | (r :: (Prim.Row (Prim.Type))) } -> + (Prim.Int))) + ({ b: ("hello": Prim.String), a: (101: Prim.Int) }: { + a :: Prim.Int, + b :: Prim.String + }) + +litPattern :: (Prim.Int -> (Prim.Boolean)) +litPattern = + \(n: Prim.Int) -> + case (n: Prim.Int) of + 0 -> (False: Prim.Boolean) + 1 -> (True: Prim.Boolean) + 2 -> (True: Prim.Boolean) + 3 -> (True: Prim.Boolean) + 4 -> (True: Prim.Boolean) + _ -> (False: Prim.Boolean) + +litPatternApplied :: Prim.Boolean +litPatternApplied = (litPattern: (Prim.Int -> (Prim.Boolean))) (5: Prim.Int) + +isNullSomeDataList :: Prim.Boolean +isNullSomeDataList = + (nullList: forall (a :: Prim.Type). ((Builtin.BuiltinList + ((a :: Prim.Type))) -> + (Prim.Boolean))) + (someDataList: (Builtin.BuiltinList (Builtin.BuiltinData))) + +irrPattern :: (Prim.Int -> (Prim.Int)) +irrPattern = \(n: Prim.Int) -> (2: Prim.Int) + +identitea :: forall (x :: Prim.Type). ((x :: Prim.Type) -> ((x :: Prim.Type))) +identitea = \(x: (x :: Prim.Type)) -> (x: (x :: Prim.Type)) + +testIdConst :: Prim.Int +testIdConst = + let + const :: forall (a :: Prim.Type) (b :: Prim.Type). ((a :: Prim.Type) -> (((b :: Prim.Type) -> ((a :: Prim.Type))))) + const = + \(p: (a :: Prim.Type)) -> \(q: (b :: Prim.Type)) -> (p: (a :: Prim.Type)) + in (identitea: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((x :: Prim.Type)))) + ((const: forall (a :: Prim.Type) + (b :: Prim.Type). ((a :: Prim.Type) -> + (((b :: Prim.Type) -> ((a :: Prim.Type)))))) + (5: Prim.Int) + (2: Prim.Int)) + +id :: forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type))) +id = \(x: (t :: Prim.Type)) -> (x: (t :: Prim.Type)) + +objForall :: forall (a :: Prim.Type) (b :: Prim.Type). { getIdA :: ((a :: Prim.Type) -> ((a :: Prim.Type))), getIdB :: ((b :: Prim.Type) -> ((b :: Prim.Type))) } +objForall = + ({ + getIdB: (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> + ((t :: Prim.Type)))), + getIdA: (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> + ((t :: Prim.Type)))) + }: forall (a :: Prim.Type) + (b :: Prim.Type). { + getIdA :: ((a :: Prim.Type) -> ((a :: Prim.Type))), + getIdB :: ((b :: Prim.Type) -> ((b :: Prim.Type))) + }) + +testId :: Prim.Int +testId = + (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type)))) + (2: Prim.Int) + +fakeLT :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) +fakeLT = \(v: Prim.Int) -> \(v1: Prim.Int) -> (True: Prim.Boolean) + +testForLift :: (Prim.Int -> (Prim.Boolean)) +testForLift = + \(x: Prim.Int) -> + let + j :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) + j = + \(c: Prim.Int) -> + \(d: Prim.Int) -> + (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (c: Prim.Int) + ((g: (Prim.Int -> (Prim.Int))) (d: Prim.Int)) + h :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) + h = + \(a: Prim.Int) -> + \(b: Prim.Int) -> + (fakeLT: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) + ((g: (Prim.Int -> (Prim.Int))) (a: Prim.Int)) + ((j: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (4: Prim.Int) + (b: Prim.Int)) + g :: (Prim.Int -> (Prim.Int)) + g = + \(a: Prim.Int) -> + case ((h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) (a: Prim.Int) (x: Prim.Int)) of + True -> + (j: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (x: Prim.Int) + (1: Prim.Int) + _ -> + (multiplyInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (x: Prim.Int) + (x: Prim.Int) + in (h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) + (x: Prim.Int) + (3: Prim.Int) + +testForLift' :: (Prim.Int -> (Prim.Boolean)) +testForLift' = + \(x: Prim.Int) -> + let + h :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) + h = + \(a: Prim.Int) -> + \(b: Prim.Int) -> + (fakeLT: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) + ((g: (Prim.Int -> (Prim.Int))) (a: Prim.Int)) + (4: Prim.Int) + g :: (Prim.Int -> (Prim.Int)) + g = + \(a: Prim.Int) -> + case ((h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) (a: Prim.Int) (x: Prim.Int)) of + True -> + (plus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (x: Prim.Int) + (x: Prim.Int) + _ -> + (multiplyInteger: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (x: Prim.Int) + (x: Prim.Int) + in (h: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) + (x: Prim.Int) + (3: Prim.Int) + +eqBool :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) +eqBool = + \(v: Prim.Boolean) -> + \(v1: Prim.Boolean) -> + case (v: Prim.Boolean) (v1: Prim.Boolean) of + True True -> (True: Prim.Boolean) + False False -> (True: Prim.Boolean) + _ _ -> (False: Prim.Boolean) + +eq2 :: forall (@a :: Prim.Type) (@b :: Prim.Type). ({ eq2 :: ((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))))) +eq2 = + \(dict: { + eq2 :: ((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))) + }) -> + (dict: { + eq2 :: ((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean)))) + }) + .eq2 + +testEq2 :: Prim.Boolean +testEq2 = + (eq2: forall (@a :: Prim.Type) + (@b :: Prim.Type). ({ + eq2 :: ((a :: Prim.Type) -> + (((b :: Prim.Type) -> (Prim.Boolean)))) + } -> + (((a :: Prim.Type) -> (((b :: Prim.Type) -> (Prim.Boolean))))))) + (eq2IntBoolean: ({ + eq2 :: (Prim.Int -> (((b :: Prim.Type) -> (Prim.Boolean)))) + } (Prim.Boolean))) + (101: Prim.Int) + (False: Prim.Boolean) + +eq :: forall (@a :: Prim.Type). ({ eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))))) +eq = + \(dict: { + eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) + }) -> + (dict: { + eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) + }) + .eq + +guardedCase2 :: Prim.Int +guardedCase2 = + let + v :: forall ($36 :: Prim.Type). (($36 :: Prim.Type) -> (Prim.Int)) + v = \(v1: ($36 :: Prim.Type)) -> (0: Prim.Int) + in case (polyInObj: { bar :: forall (x :: Prim.Type). ((x :: Prim.Type) -> (Prim.Int)), baz :: Prim.Int }) of + { bar: _, baz: x } -> + let + v1 :: Prim.Boolean + v1 = + (eq: forall (@a :: Prim.Type). ({ + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean)))) + } -> + (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) + (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) + (x: Prim.Int) + (4: Prim.Int) + in case (v1: Prim.Boolean) of + True -> (x: Prim.Int) + _ -> + (v: forall ($36 :: Prim.Type). (($36 :: Prim.Type) -> + (Prim.Int))) + (True: Prim.Boolean) + _ -> + (v: forall ($36 :: Prim.Type). (($36 :: Prim.Type) -> (Prim.Int))) + (True: Prim.Boolean) + +testEqViaOrd :: forall (a :: Prim.Type). ({ compare :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))), Eq :: { eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))))) +testEqViaOrd = + \(dictOrd: { + compare :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Int)))), + Eq :: { + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Boolean)))) + } + }) -> + \(a: (a :: Prim.Type)) -> + \(b: (a :: Prim.Type)) -> + (eq: forall (@a :: Prim.Type). ({ + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean)))) + } -> + (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) + ((dictOrd: { + compare :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Int)))), + Eq :: { + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Boolean)))) + } + }) + .Eq) + (a: (a :: Prim.Type)) + (b: (a :: Prim.Type)) + +testSuperClass :: Prim.Boolean +testSuperClass = + (testEqViaOrd: forall (a :: Prim.Type). ({ + compare :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Int)))), + Eq :: { + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean)))) + } + } -> + (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) + (ordInt: { + compare :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))), + Eq :: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) } + }) + (1: Prim.Int) + (2: Prim.Int) + +cons :: forall (a :: Prim.Type). ((a :: Prim.Type) -> ((List ((a :: Prim.Type)) -> (List ((a :: Prim.Type)))))) +cons = + \(x: (a :: Prim.Type)) -> + \(xs: List ((a :: Prim.Type))) -> + (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (x: (a :: Prim.Type)) + (Nil: List ((a :: Prim.Type))) + +consEmptyList1 :: List (Prim.Int) +consEmptyList1 = + (cons: forall (a :: Prim.Type). ((a :: Prim.Type) -> + ((List ((a :: Prim.Type)) -> (List ((a :: Prim.Type))))))) + (1: Prim.Int) + (Nil: List (Prim.Int)) + +consEmptyList2 :: List (Prim.String) +consEmptyList2 = + (cons: forall (a :: Prim.Type). ((a :: Prim.Type) -> + ((List ((a :: Prim.Type)) -> (List ((a :: Prim.Type))))))) + ("hello": Prim.String) + (Nil: List (Prim.String)) + +compare :: forall (@a :: Prim.Type). ({ compare :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))), Eq :: { eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))))) +compare = + \(dict: { + compare :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Int)))), + Eq :: { + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Boolean)))) + } + }) -> + (dict: { + compare :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Int)))), + Eq :: { + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Boolean)))) + } + }) + .compare + +brokenEven :: (Prim.Int -> (Prim.Int)) +brokenEven = + \(n: Prim.Int) -> + case ((eq: forall (@a :: Prim.Type). ({ eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) (n: Prim.Int) (0: Prim.Int)) of + True -> (1: Prim.Int) + _ -> + (brokenEven: (Prim.Int -> (Prim.Int))) + ((minus: (Prim.Int -> ((Prim.Int -> (Prim.Int))))) + (n: Prim.Int) + (2: Prim.Int)) + +arrForall :: List (forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type)))) +arrForall = + (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (id: forall (t :: Prim.Type). ((t :: Prim.Type) -> ((t :: Prim.Type)))) + (Nil: List (forall (a :: Prim.Type). ((a :: Prim.Type) -> + ((a :: Prim.Type))))) + +apIdentitea :: Prim.Int +apIdentitea = + (identitea: forall (x :: Prim.Type). ((x :: Prim.Type) -> ((x :: Prim.Type)))) + (2: Prim.Int) + +and :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) +and = + \(p: Prim.Boolean) -> + \(q: Prim.Boolean) -> + (not: (Prim.Boolean -> (Prim.Boolean))) + ((or: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + ((not: (Prim.Boolean -> (Prim.Boolean))) (p: Prim.Boolean)) + ((not: (Prim.Boolean -> (Prim.Boolean))) (q: Prim.Boolean))) + +equalsC :: ((((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean)))) -> (((((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean)))) -> (Prim.Boolean)))) +equalsC = + \(v: (((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) -> + \(v1: (((Lib.C + (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) -> + case (v: (((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) (v1: (((Lib.C (Prim.Int)) (Prim.String)) ((Prim.Maybe (Prim.Boolean))))) of + C i1 s1 Just b1 C i2 s2 Just b2 -> + (and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + ((equalsInteger: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) + (i1: Prim.Int) + (i2: Prim.Int)) + ((and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + ((equalsString: (Prim.String -> ((Prim.String -> (Prim.Boolean))))) + (s1: Prim.String) + (s2: Prim.String)) + ((eqBool: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + (b1: Prim.Boolean) + (b2: Prim.Boolean))) + C i1 s1 Nothing C i2 s2 Nothing -> + (and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + ((equalsInteger: (Prim.Int -> ((Prim.Int -> (Prim.Boolean))))) + (i1: Prim.Int) + (i2: Prim.Int)) + ((equalsString: (Prim.String -> ((Prim.String -> (Prim.Boolean))))) + (s1: Prim.String) + (s2: Prim.String)) + _ _ -> (False: Prim.Boolean) + +iff :: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean)))) +iff = + \(p: Prim.Boolean) -> + \(q: Prim.Boolean) -> + (or: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + ((and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + (p: Prim.Boolean) + (q: Prim.Boolean)) + ((and: (Prim.Boolean -> ((Prim.Boolean -> (Prim.Boolean))))) + ((not: (Prim.Boolean -> (Prim.Boolean))) (p: Prim.Boolean)) + ((not: (Prim.Boolean -> (Prim.Boolean))) (q: Prim.Boolean))) + +anObj :: { foo :: Prim.Int } +anObj = ({ foo: (3: Prim.Int) }: { foo :: Prim.Int }) + +objUpdate :: { foo :: Prim.Int } +objUpdate = + let + v :: { foo :: Prim.Int } + v = (anObj: { foo :: Prim.Int }) + in (v: { foo :: Prim.Int }) { foo = (4: Prim.Int) } + +anIntLit :: Prim.Int +anIntLit = (1: Prim.Int) + +aVal :: Prim.Int +aVal = (1: Prim.Int) + +aStringLit :: Prim.String +aStringLit = ("woop": Prim.String) + +aPred :: (Prim.Int -> (Prim.Boolean)) +aPred = \(v: Prim.Int) -> (True: Prim.Boolean) + +guardedCase :: (Prim.Int -> ((Prim.Int -> (Prim.Int)))) +guardedCase = + \(w: Prim.Int) -> + \(x: Prim.Int) -> + let + v :: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> (Prim.Int)) + v = \(v1: ($39 :: Prim.Type)) -> (0: Prim.Int) + in case (w: Prim.Int) (x: Prim.Int) of + y z -> + let + v1 :: Prim.Boolean + v1 = + (eq: forall (@a :: Prim.Type). ({ + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean)))) + } -> + (((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Boolean))))))) + (eqInt: { + eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) + }) + (y: Prim.Int) + (2: Prim.Int) + in case (v1: Prim.Boolean) of + True -> + let + v2 :: Prim.Boolean + v2 = (aPred: (Prim.Int -> (Prim.Boolean))) (y: Prim.Int) + in case (v2: Prim.Boolean) of + True -> + let + v3 :: Prim.Boolean + v3 = + (eq: forall (@a :: Prim.Type). ({ + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean)))) + } -> + (((a :: Prim.Type) -> + (((a :: Prim.Type) -> (Prim.Boolean))))))) + (eqInt: { + eq :: (Prim.Int -> + ((Prim.Int -> (Prim.Boolean)))) + }) + (z: Prim.Int) + (0: Prim.Int) + in case (v3: Prim.Boolean) of + True -> + let + v4 :: Prim.Boolean + v4 = + (eq: forall (@a :: Prim.Type). ({ + eq :: ((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean)))) + } -> + (((a :: Prim.Type) -> + (((a :: Prim.Type) -> + (Prim.Boolean))))))) + (eqInt: { + eq :: (Prim.Int -> + ((Prim.Int -> + (Prim.Boolean)))) + }) + (y: Prim.Int) + (nestedBinds: Prim.Int) + in case (v4: Prim.Boolean) of + True -> (2: Prim.Int) + _ -> + (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> + (Prim.Int))) + (True: Prim.Boolean) + _ -> + (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> + (Prim.Int))) + (True: Prim.Boolean) + _ -> + (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> + (Prim.Int))) + (True: Prim.Boolean) + _ -> + (v: forall ($39 :: Prim.Type). (($39 :: Prim.Type) -> + (Prim.Int))) + (True: Prim.Boolean) + +aList2 :: List (Prim.Int) +aList2 = + (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (1: Prim.Int) + ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (2: Prim.Int) + (Nil: List (Prim.Int))) + +aList :: List (Prim.Int) +aList = + (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (1: Prim.Int) + ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (2: Prim.Int) + ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (3: Prim.Int) + ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (4: Prim.Int) + ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (5: Prim.Int) + (Nil: List (Prim.Int)))))) + +aFunction3 :: (Prim.Int -> (Prim.Int)) +aFunction3 = + \(x: Prim.Int) -> + case ((eq: forall (@a :: Prim.Type). ({ eq :: ((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean)))) } -> (((a :: Prim.Type) -> (((a :: Prim.Type) -> (Prim.Boolean))))))) (eqInt: { eq :: (Prim.Int -> ((Prim.Int -> (Prim.Boolean)))) }) (x: Prim.Int) (2: Prim.Int)) of + True -> (4: Prim.Int) + _ -> (1: Prim.Int) + +aFunction2 :: (Prim.Int -> (List (Prim.Int))) +aFunction2 = + \(x: Prim.Int) -> + (Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (x: Prim.Int) + ((Cons: forall (x :: Prim.Type). ((x :: Prim.Type) -> + ((List ((x :: Prim.Type)) -> (List ((x :: Prim.Type))))))) + (1: Prim.Int) + (Nil: List (Prim.Int))) + +aFunction :: forall (x :: Prim.Type). ((x :: Prim.Type) -> ((forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int)) -> (Prim.Int)))) +aFunction = + \(any: (x :: Prim.Type)) -> + \(f: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int))) -> + (f: forall (y :: Prim.Type). ((y :: Prim.Type) -> (Prim.Int))) + (any: (x :: Prim.Type)) + +aBool :: Prim.Boolean +aBool = (True: Prim.Boolean) \ No newline at end of file diff --git a/tests/purus/passing/CoreFn/Misc/output/Lib/externs.cbor b/tests/purus/passing/CoreFn/Misc/output/Lib/externs.cbor new file mode 100644 index 0000000000000000000000000000000000000000..067aab035d14614177e86273c81adbf871f512d6 GIT binary patch literal 74204 zcmeG_&u?7S)iboAl#oKfggdQUD5OBZjuR7q`O(lcaU5dT2`QnhD#Y{58~fSgnep=s zC7-$&|7hS#RjCqE7Oh$rRf*{$~s6$Uidrb+;`u*cV?dL zd+tk!gcor4+xUtjF77;uLIwg14Qxq z#I#=obo24|35bgtk#$M9gZtGqEW_TsLr|Zol2DMMdA>TPj-But-Wz@qH4%SU<0G6o zcEx87_z2#N- zv4Q4CZ@xLpN8x+NYc&TFd~ZCMcMxNl;2jc;z&qKj7I9YM3t>9O;Xp`&lm>`Q#I%VlrIAAgfS_{5P{`Ji?H*Fy(kR8X2Db8iKn6PhZbIoGWFVHWFVNN@u1|60hm)dmt2m5eDzg_%z-Rv+%HY~A+DDkX6xxn&^YUXyMzwe-&}&k*%GINFmxtpY91<0 zxLW0_mm(uf+?8g@cbGIQiW0XqPZ-RfX;vy&Kts0NkOe_hxN;EBj8|6`CKoIi$3{!E zPIpvQ6b)bCmm|DkENpng4n=~pKj*eKp7iIMUS)omFAS)DK^46Tt3g~7oC{{_6^BGR zL~L*PrDnARrL6YT;?-ShT6Kdmr;-Y7Jjl8sU+!~Ak3@2A7LrRp zT;8^vn>jM+SN#wcGo_y|<#IXvx0s{YLYWejlos;of9U&j8~nvAY`MUnpw+>`Ydu`$ zT38}vYb(pS(%CSWUC1ra|I4|_sD1!HQQyXY(^^~keQqJY4P4{prQBj3x2P6@30m^2 z-@JssQK0zS+ANx29amuuAEv434{^P$;fU7X>X(p5XupJ<1b^}1Vr~NFY3&y{>BDax z0Fr1L)qe$(@>*+U>08NO*!$mIT+Y3tgx^}odEU}C_>s*HTOr>k3b@JECw|mIQb=wf z1Dt)AA2tTKkTX6egkz@OT3OB;zs{PNwbt@?teNZo9`e>Ne&`0w5NrQqH1gxRP^VON zjzndrrihbATUpDMBh@Edq#6Trr1~U{{8VOAmBjR9E>#Y1LMX9nj#$LVwwM$9(eq&s zI}4|O0&Me%9$ki3?haeGS$KO26%0S``R-D#NBqFv#}%NpwtBY1h&yx%@_n0#c$i~> zDH62y=pKlYJo!a{_VNP@?8zuL67{UOm?A%WZXk-F{4}?nRCx=y?f|+jc93M@yJG+M zmmnHEsSifp+lhR_nh~*I{0Om&pLC$#bS?lJ<5@(9R6g6&j7+&?1RpW@c1V{azt|xv7iU`@x2}0?LvQ5{-(4%}wDo}Q($V!q#$YU)pQ@dnv)f34w zB`Eb{Qn3dklh&Qq8AI$>6c0bOlzSMwK^xa9yGWYUvIrw-)G!=P6O@#LB?34o3EJK?nx1%l6#xWMntcCpGj-}j#AS>GiFu{G_ zuvV%;TH|?Kj-M={F>_yrf5jw6qjSrQ?|ML6x`7_S-&^hLSL?p@{`=t;F>za$Se&nyyZc z%<=NnCm?HN6+#uDJ;Tw6UytHAi|coF+{ zHh0c?Jx$u=P0H`>1Mb#FBA$2eN#97kHvwZ~*ORLq6-L@OHS!Y1}k&K|Y`wB}_eg#4Y4 z>8sB;0kFq~)En(MwE1Fdo;zWOk0*o((4KJUXWQAmo6Q~<5@B?8p%CoRU>h1rL0gg% zBHSw0?#-|juIR;`@m?r6SQ}>oYR!%41(y-M-8WGg*oX(Cafu~l(F=Q_B#bsGW922f zSj1jT&q6UlJS$#gNH_+ymq`Me?0xcGSv-phd)Dv?TFVe&T^A0jijiY&wxtdj)iLO9 z7unowlL~_#o*`}ggtOH3L{!Mg4F zE(vjC%4L?T9MQR!pDI#JbIb2~m8QQ}>Jx7e`kM6FMS=HB3@xl@tLu;K1K%!ehTFyI z%@HxEec;;#olY>SQ9(~^-FkkMl6Vy64*)Q6J8pePTCb_KZR8nMptsiN{97K!~y5Gv4m+YN#CY^Nc|*#)l+ zY%}_{kDG8`d)cL(_-Gru?c?1cCG~tr`f%-A^ifag6bO^IOE320OwBuS5rZ<+phnfq zF7{0ZIw;q4JI6z6v|4G#JUM_e=+9Uj49ijre_oeu>cN$T{8F~3H=;}^w)o6iBE+D5 zQ$%v;$lhGyqfYkbvUOfbzt}oC>co&F299skd8Lf^K1CN>q);N41+klAzeM~YlSM(= zOx}q+)6-*ZnL*n}vcL_N9GH1(e}ZY1_AyzxZqSjj6|d|!$Wx~&M)+2TBppDv;uUqc ziJ^7QSKh05)#k`;AG`RqT*t*REraEFT10C{ooPI4ncX3{EMv8Yq`KB(w)r3Ro8Sci z48PktT%OS?Y3p!#+SLw>kiJgvQ;jI~e2hjBOOuuZ+Oi+3O}G=AJl4R#dje{B)6tAJdye9Ux7V_SE_9}Rds&cQ1pXy4GtAFd7 z=xem4fV9|0;{=w&!%HNCKAnfSeq>+NSG4SIWh+q*XZ?|O+gzlDw$t`J3B!0!L6ej? zB@Qu-=ahJs;Gfq8FO3K9x3jY2Q(|{S3tfiCg6$_dq^m(=Yjn$nC8|Cmqo1Ywbb&B# z#Q??Zi$r4YPYJBO)twTr(6~doS{?jJ(K48^OgWtWPbAT9{*=7#Bg=?ZhBJzD&ZvO> zCF`9L32HQK>Z^S_GH`coR6O01cMsIWgqRj5MF4jXRN&qL263V{!q_GaPJnA_Nxc$Ax~*1JHx{S39W z4u&egH*X!xv){Ir^L=5!TWj&QC#qrnyR{boCa%SKKAo)I?}9tquQaym0UJF*k7Wv2 zDqzjTeyNbalC@aY61tQ$XsN)nylxeQ`@#lQU16&x;h(Gyv`;VTD`WY}0`HwUPLJE$U*jysu{1mmJAL-%9fR7- zV4Q;dxcTluTs33hlU&FrmAaKj7$|8Q3ninKj?}RSdNwhVIlY){UEcod5WoH_~aj4N=#VIGCOrSA*khai#*;)SU6Jw@9d6;Wesd|VK_B3x}&L6~iVMY!HL`1Omw%b*@TDdm1M@*#R56-n(`_QKh zbj!GhYhkxEYRkAgGRt)1?h=mW92T3nR^7)yK6C7h|Jw$<7`Uleo~MQ^g27h?0frII zKM>D>TYn%17~x#O?$VR|nb^VoVneB6NjIam$W%IZt~uKUuxomW zyLj`Ba37=R@*?)AT@<3-cd-L5LOaMoOHuBkcuB{r@+f&+NfC`H2yyG|NcMi8#(fvT z%ZY>t)l`Lh-%3nhDjdW zUw`V>aEt_(ytllHJ+U9cm6+ngM|AsC#L{C<-h6Y`KA*jWBDe(Z@Rq(PH|a`GkfMPQ!(Q*^m1x+QOaj;J(sD(g|xW9+Uw{tW$>4U(IFmt zzI|)H;^R41&s??=#o8`cq6(HH(UUapDcve!i873o4sBe9zEwCta-Kua5Yc1Qqu5q@ zgm9f;S*e2M@bGgQ_ZMAd%CS;O%d4$yCCcIKSR_#`hG5KIfHz7HbMTE4zHwbr3g6Fg zew&U1CSx-A7$=yI#g7^Kk3sF3`WSEK``F0dVuxa2BOW>?N&C3_F<$?M!eG!KL5+TL z=G^!(%|b**=j@m$`xSfsK0!f!!n(CM2DKN>C#dXCvQoArq(j*ZvQT3vj5a?-m!dlz zk2ix#BdFSA{x>E!|L&UHlxE>EQhSX5p+@-s2qRpoM6gt^G#Q(dpW$NXGq_#R-i~5W zdrm&X#n5L)3hChal8}xC8-pWM8B-VvlpzegCh(XOkpTchA=2ox@BI(>0r^fBq^PN&)TGK(dDNo5Y433 zgdNHrlwm1 z%O@RoAiu=u1X$YSZ-2b*ORQLeQ0#Y(6r{a!yAV$ce9TRQ+Qjs)>m{$jh*@7@ee5eV z8f%M|phn`x*6>$2D}M#4w`|VgZZdy`^BJOX)-fQ71Y@t|1ePJxE*vC^uGcE(M|qyS zii%#vgR|C(mY~@vdKDGDDh4A(PY6$hjI+?IC?-V1yK!ZeHo{h+M@=&nX2EQgPJAIP z_Te>wWoU&?=B%0x74cMOUoca&yv!==rc0E=*+8USO*=SMLc#1Q`_8{rI`_URey-Wv z|1z2pSLw_<;%Otxeg**~kvG~$mjsp}S>-kw2XS<%#?j@p*C%FGL`hz4$TljJZgM}uaF_#teX$FYr!J=VW< zfYrG9G3U`NfX`O6aBq}@Xk%!WXm`u8U)DouB3j#9&ybCXo)_)&8x7jnBBf$IOUWbnE2JX_5v@qVg0l-xI$DOo6Tnbe&?2XLU8|SeVVjnAL z+$DjL_}_`|IML#^nj%f&?YHhwwD+9&=u$@%{zOn>%s4&YL8It_Fblc7eLoq1LIDgB z7#&318K(yeNRk|e@o3NtZ|jk>U60vql7vNksL$qL39=D!)7#2gv>aldQKHS578`jo>hEFl@Nn8g2%M$5lRIFHtV6YnK)Y>naK1w3#i z@wq`W0z?5#_lo0ew68->*6>=Qz)D zeyQ-WEGLF$S`~0$=2S-du3jMx@OG| z>rjJEF@#Q0(HZ~-89I2H>T*vThb(Y;NAD}X9?JUXJMkirY$W+e18N_WX1`dA44V3I zE31(2GdIP_!qW$Af7Wn~ZZrT6c#j&w@bI8sA>S{4XunOO19SL~N7mNd_gtVdqU08M zulb?+Qnjca;8WU>=Z!Tx!W}>DV`5f%TAloX+=DH`LEl+X#|=8+bMl>jS|%|yo&Ym6 z-Vcp9U~5K8XsmEXUK$beC@=1;qdCSL(NB9UT&c#u9I4V&+izT=;v`i`Oi$)g5p&Wbl3&oE+DC9Qc`R;nWKPCR`x&o~HjMhVXD%Vyu}p}iO~~XU zM}A#Ajv`+4=%5Ns^yr}aK_Uz;t#9OB$pH4V?WQ5N0_i610E3V$r-ZFQiqq3p zAYBn#fplJfI2WuUEs$;;ilR$wRCJ|0CkcL8$JVw-3Sm^%BZccGw)C>#WU)3|_d@&L z#yH&Y)*M?IXxF=@K&o*P>6E^5vW#zJ2D-Ll{Tdf|7451*>WJyAj10WjxB%7N%0ky# zYppv}b-``Bk-4`555fqe2slVpmqFO#VQ$C`Vsm~WKPa9hc^TK|*uJ8MXnrcO9c?i* z7emWiais2wAQ;9|YDfzeBnRP+9o7u6j$|0msUbbIIf%MqL=O#`5k3aRUa6NsUCS;@ z*q9z>NpcR7b95}BiXrT z-4BN=-n{)Go>cBU&DWb1;ScA!vSQM$3b;GxDH# zPS-Up_c`Q<=QVmb?F$Fx#>YXtEitKW^644W=#iKA+I8I=6bBH)LGiN=dKi9rh$c5w zmlH6<<`0o69x_f$xkSr|lgD}fypGjz1Vg=qT&c#u9I47u;~~?-o#ZOXd5X6YzmE5C zjh8G>mzI zj+XkeGtMrW9g!PPN74^t)7==*N-!Rj?N7cJ@<*xUag=l8j1J5Y=uzq%J!+g+iOq$B zPjX^3Hc)e~?U6g+3l8(bSG;*9nbMT1QN460ekAm>a4e89^Ntbw@B{}p5g5aV%M1B2 z^VWX3(`nzsKZdtpA-4UTnNEXdXl@J-@!{ARy_D4(7ej_-Q~aPYCe|Ad$C{{xjOpcVDr>wgc5zH30cJ?>ZR&V>JEMz33i*f_zB~c^h+aKZxrEWTBXW#m+)6eq3Mnr@;dC*6G{$1J#+kW_4!n!aIRotV2)s9id;6k%Us-F@zULR>{F?-EbgLk(yTEkml;BzA#0rB zSz`js5c&*R<4k7O7!i||HO`PhaRn0ta|9!;aV9%!RJ>$mjWg03Q8+2qNSXb(Uz+qo zd_aU#M0}qz`}fU@Q2Z0ae%Qe2Zn_dQ&U&yw466*Yzet(TMG&zQFhjc+$uur@FGz9l zNlpwmVy@RNQVj-$lA_hQMCSao`a>G!!}L+6gD~W4_7chC5||A`vk5Rm6PHM{mon3A zL`)W%y+krcp=g>VD*;cMny=0J_{6mxcVFqq@pubh#*8H5z?KXkm;BuFBx@ zj7qcQ?_-SfS1KU?wWB8;BSA&c&$zGF0$S$~*trS>Qy}7^X%`^vDnc^}h)9zq+EP2pH9+USQbW zrxc|=1s8AvW^nZ>bu4|_z15S0Pjb>3%k7s%pUQnGl!`X7sYO2?_wj}q;<`$wZLW$T zj;s@4hHNz8q+}k42M$7ty;qGSf*Uv!;+$m4;UZRure-Ix$b#QhbH>{eO#Z6uWVmX+ zXGVe{y}c8k`_nWb<(6B>tt@$*Eb?lakuKzySVy6+rmGiGa<)O&5lnP;%^O}}%->gK zL)TTYkGIE?DmxY})HZTeyu#atUq|dLYW8EUgkd;qjmZ-|-Y`C7=M7Uzn;16p3{R>e zI?;0)gw~O5=KvWSIEDK}Ky4q><3b#vS=!$#wV%0P;I8gHXXfrX*4M($UGvN~+gkr) z7t52a#*p>l+9lC)w$oBO@{Ikt9eu{$+-l*um-4$_rRncg-|SQ046flCtL)F=tA!+f zyH=ZP+tF>W@fOz!Fe6F4M)kLAnbqGSVvN)|URv099J+gFh?-5Tz}2%eu{%L z2V+D|_e!z-I_{cm!a?C^X{8c28swxu*Yqm$oYma*N6;d#i*uaSTmsAx({*`p;ktPz zSuA*lcPVmMr7H!@c(WDcC#49zBlhZzVCAL3DnfJc&^qC|(Z9mn>$pz+8Q0AV7o&S1 zIeL)`j_c6j%;8Hx8)Xdtw0C~OXQ6vWT09VwR1uUnvAClvIk_$*FZ4uc7Bi!gnP2M6 zIQfvG=M*a-DCmPu(EE6@i1Z+DM{@Bbd4%aYtU5Il;rbHXTT2lZc2E*~b8)7_65ne) zAw|&eOhiJBgERdiCMH3roQY-7;}RjbLl=ZF*Ue)U`g9YX>BBdi&IPme3g_hT4Otw$ z!7F2G&@C~P~*W5Ej|Apv9H$=f` z)TwYhjgmhD|5)$!+@U72J8&46;e81(Lqd0C$>2_QB?Cnc>s65m*x0L=QJ5nbsv6zl ztUz=kdINs$x69qhxgk4bkFv~kr2dv>~mFS!-+L`)KKnQn1Mu20c+yST+%;uhy- z;pG6IbASmSt}Ep6)i#C^B)|;8ugY)>&%Ei(#SzJY99G>%@sf>Au1c#~<=JEmosCV> zTX?8s<2fOwO|Htz4cgxMLu7y0hDI9A>Tg20rYk3+eo^`!{s{IftZiinbdT>aT9$CQ zwT0HgqRoEBjy!ZVEazs9O!`$ngx5(+aJzplhyQfa;aZ}_obS&ui4_HCqZI|?kv0~& zqOdu7iz9P`a0`b&HwYBtMi0EL%aO7;02Ntrz`YV$PZ9SdZ0rB)-(gEbfV$rY8$J~Q@hmKlm8E6K8p?j literal 0 HcmV?d00001 diff --git a/tests/purus/passing/NonTerminating/TestInliner.purs b/tests/purus/passing/NonTerminating/TestInliner.purs new file mode 100644 index 00000000..e69de29b diff --git a/tests/purus/passing/ShouldFail/Misc/IncompleteCases.purs b/tests/purus/passing/ShouldFail/Misc/IncompleteCases.purs new file mode 100644 index 00000000..56c138f3 --- /dev/null +++ b/tests/purus/passing/ShouldFail/Misc/IncompleteCases.purs @@ -0,0 +1,8 @@ +module IncompleteCses where + +testIncompleteCases :: Int -> Int +testIncompleteCases = case _ of + 0 -> 0 + 1 -> 1 + 2 -> 2 + 3 -> 3 From 401c9ae6e14a57a79bf46488e78806063bc11e5d Mon Sep 17 00:00:00 2001 From: gnumonik Date: Wed, 18 Dec 2024 20:12:56 -0500 Subject: [PATCH 4/4] Addressed Koz's review comments --- purescript.cabal | 2 +- src/Language/Purus/Make.hs | 225 ++----------------------------------- tests/TestPurus.hs | 31 ++++- 3 files changed, 35 insertions(+), 223 deletions(-) diff --git a/purescript.cabal b/purescript.cabal index 0c3cf93f..e5ae0ead 100644 --- a/purescript.cabal +++ b/purescript.cabal @@ -526,7 +526,7 @@ test-suite tests plutus-core ==1.30.0.0, regex-base >=0.94.0.2 && <0.95, split >=0.2.3.4 && <0.3, - stm, + stm >=2.5.0.2 && <2.6, typed-process >=0.2.10.1 && <0.3, tasty ==1.5, tasty-hunit diff --git a/src/Language/Purus/Make.hs b/src/Language/Purus/Make.hs index 9877fd77..f8b121aa 100644 --- a/src/Language/Purus/Make.hs +++ b/src/Language/Purus/Make.hs @@ -1,35 +1,30 @@ {-# LANGUAGE TypeApplications #-} -module Language.Purus.Make where +module Language.Purus.Make (compile, make, allValueDeclarations) where import Prelude -import Control.Exception (throwIO) import Data.Text (Text) import Data.Text qualified as T -import Data.Text.Lazy qualified as LT import Data.Map qualified as M import Data.Set qualified as S import Data.Function (on) -import Control.Exception -import Control.Monad (forM) -import Data.Foldable (foldrM, forM_) -import Data.List (delete, foldl', groupBy, sortBy, stripPrefix, find) +import Control.Exception ( throwIO ) +import Data.Foldable (foldrM) +import Data.List (delete, foldl', groupBy, sortBy, stripPrefix) import System.FilePath ( makeRelative, - takeBaseName, takeDirectory, takeExtensions, (), ) -import System.IO import Language.PureScript.CoreFn.Ann (Ann) -import Language.PureScript.CoreFn.Expr (Bind (..), PurusType, cfnBindIdents) +import Language.PureScript.CoreFn.Expr (Bind (..), PurusType) import Language.PureScript.CoreFn.Module (Module (..)) import Language.PureScript.Names ( Ident (Ident), @@ -38,8 +33,7 @@ import Language.PureScript.Names ( runModuleName, ) -import Language.Purus.Eval -import Language.Purus.IR.Utils (IR_Decl, foldBinds, stripSkolemsFromExpr) +import Language.Purus.IR.Utils (IR_Decl, foldBinds) import Language.Purus.Pipeline.CompileToPIR (compileToPIR) import Language.Purus.Pipeline.DesugarCore (desugarCoreModule) import Language.Purus.Pipeline.DesugarObjects ( @@ -63,13 +57,12 @@ import Language.Purus.Pipeline.Monad ( runPlutusContext, ) import Language.Purus.Pretty.Common (prettyStr, docString) -import Language.Purus.Prim.Data (primDataPS, primData) -import Language.Purus.Types (PIRTerm, PLCTerm, initDatatypeDict) +import Language.Purus.Prim.Data (primDataPS) +import Language.Purus.Types (PIRTerm, initDatatypeDict) import Language.Purus.Utils ( decodeModuleIO, - findDeclBodyWithIndex, findMain, + findDeclBodyWithIndex, ) -import Language.Purus.Make.Prim (syntheticPrim) import Language.Purus.Pipeline.EliminateCases.EliminateNested (eliminateNestedCases) import Control.Monad.Except (MonadError (throwError), when) @@ -84,22 +77,8 @@ import Algebra.Graph.AdjacencyMap.Algorithm (topSort) import System.FilePath.Glob qualified as Glob -import PlutusCore.Evaluation.Result (EvaluationResult(..)) import PlutusIR.Core.Instance.Pretty.Readable (prettyPirReadable) - -import Language.Purus.Pipeline.Lift.Types -import System.Directory - - -import Debug.Trace (traceM) -import Language.Purus.IR (expTy) - --- TODO: Move the stuff that needs this to the tests -import Test.Tasty -import Test.Tasty.HUnit --- import PlutusIR.Core.Instance.Pretty.Readable (prettyPirReadable) - {- Compiles a main function to PIR, given its module name, dependencies, and a Prim module that will be compiled before anything else. (This is kind of a hack-ey shim to let us write e.g. serialization functions and provide them by default without a @@ -243,30 +222,6 @@ make path mainModule mainFunction primModule = do (Nothing, m : ms) -> either (throwIO . userError) pure $ compile m ms (ModuleName mainModule) (Ident mainFunction) _ -> throwIO . userError $ "Error: No modules found for compilation" --- for exploration/repl testing, this hardcodes `tests/purus/passing/Lib` as the target directory and --- we only select the name of the main function -makeForTest :: Text -> IO PIRTerm -makeForTest main = make "tests/purus/passing/CoreFn/Misc" "Lib" main (Just syntheticPrim) - - - -{- Takes a path to a Purus project directory, the name of - a target module, and a list of expression names and - compiles them to PIR. - - Assumes that the directory already contains an "output" directory with serialized - CoreFn files --} -evalForTest_ :: Text -> IO () -evalForTest_ main = (fst <$> evalForTest main) >>= \case - EvaluationSuccess res -> pure () -- print $ prettyPirReadable res - _ -> error $ "failed to evaluate " <> T.unpack main - -evalForTest :: Text -> IO (EvaluationResult PLCTerm, [Text]) -evalForTest main = do - pir <- makeForTest main - -- traceM . docString $ prettyPirReadable pir - evaluateTerm pir -- TODO put this somewhere else note :: (MonadError String m) => String -> Maybe a -> m a @@ -274,33 +229,6 @@ note msg = \case Nothing -> throwError msg Just x -> pure x -makeTestModule :: FilePath -> IO [(Text,PIRTerm)] -makeTestModule path = do - mdl@Module{..} <- decodeModuleIO path - let toTest :: [Ident] - toTest = concatMap cfnBindIdents moduleDecls - nm = runModuleName moduleName - goCompile = pure . compile syntheticPrim [mdl] moduleName - forM toTest $ \x -> goCompile x >>= \case - Left err -> error $ "Error while compiling " <> T.unpack (runIdent x) <> "\nReason: " <> err - Right res -> pure (runIdent x,res) - -evalTestModule :: FilePath -> IO () -evalTestModule path = do - made <- makeTestModule path - putStrLn $ "Starting evaluation of: " <> prettyStr (fst <$> made) - evaluated <- flip traverse made $ \(x,e) -> do - res <- fst <$> evaluateTerm e - pure (x,res) - forM_ evaluated $ \(eNm,eRes) -> case eRes of - EvaluationFailure -> putStrLn $ "\n\n> FAIL: Failed to evaluate " <> T.unpack eNm - EvaluationSuccess res -> do - putStrLn $ "\n\n> SUCCESS: Evaluated " <> T.unpack eNm - print $ prettyPirReadable res - -sanityCheck :: IO () -sanityCheck = evalTestModule "tests/purus/passing/CoreFn/Misc/output/Lib/Lib.cfn" - -- takes a path to a project dir, returns (ModuleName,Decl Identifier) allValueDeclarations :: FilePath -> IO [(ModuleName,Text)] allValueDeclarations path = do @@ -310,138 +238,3 @@ allValueDeclarations path = do NonRec _ ident _ -> [(mn,runIdent ident)] Rec xs -> map (\((_,ident),_) -> (mn,runIdent ident)) xs pure $ concatMap (\(mdl,dcls) -> concatMap (go mdl) dcls) allDecls - -compileDirNoEval :: FilePath -> IO () -compileDirNoEval path = do - allDecls <- allValueDeclarations path - let allModuleNames = runModuleName . fst <$> allDecls - forM_ allModuleNames $ \mn -> do - let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" - outFileExists <- doesFileExist outFilePath - when outFileExists $ - removeFile outFilePath - forM_ allDecls $ \(runModuleName -> mn, declNm) -> do - let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" - withFile outFilePath AppendMode $ \h -> do - result <- make path mn declNm (Just syntheticPrim) - let nmStr = T.unpack declNm - pirStr = docString $ prettyPirReadable result - msg = "\n------ " <> nmStr <> " ------\n" - <> pirStr - <> "\n------------\n" - -- putStrLn msg - hPutStr h msg - hClose h - --- Makes a TestTree. Should probably be in the test dir but don't feel like sorting out imports there -compileDirNoEvalTest :: FilePath -> IO TestTree -compileDirNoEvalTest path = do - allDecls <- allValueDeclarations path - let allModuleNames = runModuleName . fst <$> allDecls - forM_ allModuleNames $ \mn -> do - let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" - outFileExists <- doesFileExist outFilePath - when outFileExists $ - removeFile outFilePath - testCases <- forM allDecls $ \(runModuleName -> mn, declNm) -> do - let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" - testNm = path <> " - " <> T.unpack mn <> ":" <> T.unpack declNm - pure $ testCase testNm $ do - withFile outFilePath AppendMode $ \h -> do - result <- make path mn declNm (Just syntheticPrim) - let nmStr = T.unpack declNm - pirStr = docString $ prettyPirReadable result - msg = "\n------ " <> nmStr <> " ------\n" - <> pirStr - <> "\n------------\n" - -- putStrLn msg - hPutStr h msg - hClose h - pure $ testGroup "PIR Compilation (No Eval)" testCases - --- Makes a TestTree. Should probably be in the test dir but don't feel like sorting out imports there -compileDirNoEvalTest' :: FilePath -> IO [(String,IO ())] -compileDirNoEvalTest' path = do - allDecls <- allValueDeclarations path - let allModuleNames = runModuleName . fst <$> allDecls - forM_ allModuleNames $ \mn -> do - let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" - outFileExists <- doesFileExist outFilePath - when outFileExists $ - removeFile outFilePath - forM allDecls $ \(runModuleName -> mn, declNm) -> do - let outFilePath = path T.unpack mn <> "_pir_no_eval.txt" - testNm = path <> " - " <> T.unpack mn <> ":" <> T.unpack declNm - (testNm,) <$> do - withFile outFilePath AppendMode $ \h -> pure $ do - result <- make path mn declNm (Just syntheticPrim) - let nmStr = T.unpack declNm - pirStr = docString $ prettyPirReadable result - msg = "\n------ " <> nmStr <> " ------\n" - <> pirStr - <> "\n------------\n" - -- putStrLn msg - hPutStr h msg - hClose h - - -compileDirEvalTest :: FilePath -> IO TestTree -compileDirEvalTest path = do - allDecls <- allValueDeclarations path - let allModuleNames = runModuleName . fst <$> allDecls - forM_ allModuleNames $ \mn -> do - let outFilePath = path T.unpack mn <> "_pir_eval.txt" - outFileExists <- doesFileExist outFilePath - when outFileExists $ - removeFile outFilePath - testCases <- forM allDecls $ \(runModuleName -> mn, declNm) -> do - let outFilePath = path T.unpack mn <> "_pir_eval.txt" - testNm = path <> " - " <> T.unpack mn <> ":" <> T.unpack declNm - pure $ testCase testNm $ do - withFile outFilePath AppendMode $ \h -> do - result <- snd <$> (evaluateTerm =<< make path mn declNm (Just syntheticPrim)) - let nmStr = T.unpack declNm - pirStr = prettyStr result - msg = "\n------ " <> nmStr <> " ------\n" - <> pirStr - <> "\n------------\n" - hPutStr h msg - hClose h - pure $ testGroup "PIR Evaluation" testCases - -compileModuleNoEval :: FilePath -> IO () -compileModuleNoEval path = do - let baseName = takeBaseName path - pathDir = takeDirectory path - outFilePath = pathDir baseName "_pir_decls_no_eval.txt" - mdl <- decodeModuleIO path - removeFile outFilePath - withFile outFilePath AppendMode $ \h -> do - made <- makeTestModule path - forM_ made $ \(nm,pirterm) -> do - let nmStr = T.unpack nm - pirStr = docString $ prettyPirReadable pirterm - origStr = unsafeFindDeclStr mdl nm - msg = "\n\n------ " <> nmStr <> " ------\n\n" - <> "Original coreFn declaration:\n" <> origStr - <> "\n\nCompiled PIR expression:\n" <> pirStr - <> "\n------------\n" - putStrLn msg - hPutStr h msg - hClose h - where - findDecl :: Ident -> [Bind Ann] -> Maybe (Bind Ann) - findDecl _ [] = Nothing - findDecl i (bnd@(NonRec _ i' _):bs) - | i == i' = Just bnd - | otherwise = findDecl i bs - findDecl i (Rec xs:bs) = case find (\x -> snd (fst x) == i) xs of - Nothing -> findDecl i bs - Just ((a,_),body) -> Just $ NonRec a i body - - unsafeFindDeclStr :: Module (Bind Ann) PurusType PurusType Ann - -> Text - -> String - unsafeFindDeclStr mdl nm = case findDecl (Ident nm) (moduleDecls mdl) of - Nothing -> "error: couldn't find a declaration for " <> prettyStr nm - Just bnd -> prettyStr bnd diff --git a/tests/TestPurus.hs b/tests/TestPurus.hs index 546bdae7..c3c4a4d2 100644 --- a/tests/TestPurus.hs +++ b/tests/TestPurus.hs @@ -7,24 +7,43 @@ import Data.Text qualified as T import Command.Compile ( compileForTests, PSCMakeOptions(..) ) import Control.Monad (when,unless, void) import System.FilePath + ( makeRelative, (), takeDirectory, takeExtensions ) import Language.PureScript qualified as P import Data.Set qualified as S import System.Directory + ( createDirectory, + doesDirectoryExist, + listDirectory, + removeDirectoryRecursive ) import System.FilePath.Glob qualified as Glob import Data.Function (on) import Data.List (sortBy, stripPrefix, groupBy) -import Language.Purus.Make +import Language.Purus.Make ( allValueDeclarations, make ) import Language.Purus.Eval -import Language.Purus.Types + ( applyArgs, + parseData, + dummyData, + evaluateTerm, + convertToUPLCAndEvaluate, + compileToUPLCTerm, + evaluateUPLCTerm ) +import Language.Purus.Types ( PIRTerm ) import Test.Tasty -import Test.Tasty.HUnit + ( TestTree, + defaultMain, + withResource, + sequentialTestGroup, + testGroup, + DependencyType(AllFinish) ) +import Test.Tasty.HUnit ( testCase, assertFailure ) import Language.Purus.Make.Prim (syntheticPrim) import Language.PureScript (ModuleName, runModuleName) -import Control.Concurrent.STM +import Control.Concurrent.STM + ( atomically, TVar, newTVarIO, readTVarIO, modifyTVar' ) import Data.Map (Map) import Data.Map qualified as M -import Unsafe.Coerce -import Control.Exception (SomeException, try, throwIO, Exception (displayException)) +import Unsafe.Coerce ( unsafeCoerce ) +import Control.Exception (SomeException, try, Exception (displayException)) shouldPassTests :: IO () shouldPassTests = do