From 6d34d1eb9aa02e14886280d7132ec6505548bc5e Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Thu, 18 Jul 2024 11:18:48 +0100 Subject: [PATCH 01/23] WIP --- wasm-calc11/src/Calc/ExprUtils.hs | 1 + wasm-calc11/src/Calc/Linearity/Decorate.hs | 6 ++++++ wasm-calc11/src/Calc/Types/Pattern.hs | 4 ++++ wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 2 ++ wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs | 2 ++ wasm-calc11/test/Test/Helpers.hs | 5 +++++ wasm-calc11/test/Test/Parser/ParserSpec.hs | 3 ++- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 4 ++++ 8 files changed, 26 insertions(+), 1 deletion(-) diff --git a/wasm-calc11/src/Calc/ExprUtils.hs b/wasm-calc11/src/Calc/ExprUtils.hs index 56395624..82ccfd36 100644 --- a/wasm-calc11/src/Calc/ExprUtils.hs +++ b/wasm-calc11/src/Calc/ExprUtils.hs @@ -90,3 +90,4 @@ getOuterPatternAnnotation (PVar ann _) = ann getOuterPatternAnnotation (PTuple ann _ _) = ann getOuterPatternAnnotation (PLiteral ann _) = ann getOuterPatternAnnotation (PBox ann _) = ann +getOuterPatternAnnotation (PConstructor ann _ _) = ann diff --git a/wasm-calc11/src/Calc/Linearity/Decorate.hs b/wasm-calc11/src/Calc/Linearity/Decorate.hs index 56f489d8..23c2a049 100644 --- a/wasm-calc11/src/Calc/Linearity/Decorate.hs +++ b/wasm-calc11/src/Calc/Linearity/Decorate.hs @@ -94,6 +94,12 @@ decoratePattern (PLiteral ty prim) = decoratePattern (PBox ty pat) = do (decoratedPat, innerIdents) <- decoratePattern pat pure (PBox (ty, dropForType ty) decoratedPat, innerIdents) +decoratePattern (PConstructor ty constructor pats) = do + decoratedPatsAndIdents <- traverse decoratePattern pats + + let allIdents = foldMap snd decoratedPatsAndIdents + + pure (PConstructor (ty, dropForType ty) constructor (fst <$> decoratedPatsAndIdents), allIdents) decoratePattern (PTuple ty p ps) = do (decoratedPat, innerIdents) <- decoratePattern p decoratedPatsAndIdents <- traverse decoratePattern ps diff --git a/wasm-calc11/src/Calc/Types/Pattern.hs b/wasm-calc11/src/Calc/Types/Pattern.hs index e5948819..1071eb10 100644 --- a/wasm-calc11/src/Calc/Types/Pattern.hs +++ b/wasm-calc11/src/Calc/Types/Pattern.hs @@ -8,6 +8,7 @@ import Calc.Types.Identifier import Calc.Types.Prim import qualified Data.List.NonEmpty as NE import qualified Prettyprinter as PP +import Calc.Types.Constructor data Pattern ann = PVar ann Identifier @@ -15,6 +16,7 @@ data Pattern ann | PTuple ann (Pattern ann) (NE.NonEmpty (Pattern ann)) | PLiteral ann Prim | PBox ann (Pattern ann) + | PConstructor ann Constructor [Pattern ann] deriving stock (Eq, Ord, Show, Functor, Foldable, Traversable) instance PP.Pretty (Pattern ann) where @@ -27,3 +29,5 @@ instance PP.Pretty (Pattern ann) where where tupleItems :: a -> NE.NonEmpty a -> [a] tupleItems b bs = b : NE.toList bs + pretty (PConstructor _ constructor as) = + PP.pretty constructor <> "(" <> PP.cat (PP.punctuate "," (PP.pretty <$> as)) <> ")" diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index 82c67380..02db110f 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -59,6 +59,7 @@ patternToDropPaths (PTuple (ty, drops) a as) addPath = <$> zip [1 ..] (NE.toList as) ) <> dropContainer +patternToDropPaths (PConstructor {}) _ = error "patternToDropPaths: PConstructor" patternToPaths :: Pattern (Type ann) -> @@ -80,6 +81,7 @@ patternToPaths (PTuple ty p ps) addPath = ) <$> zip [1 ..] (NE.toList ps) ) +patternToPaths (PConstructor {}) _ = error "patternToPaths: PConstructor" -- | given a path, create AST for fetching it fromPath :: (MonadError FromWasmError m) => Natural -> Path ann -> m WasmExpr diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index 08e01678..3ef6e8b2 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -36,6 +36,8 @@ predicatesFromPattern (PTuple ty p ps) path = (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) ) allPs +predicatesFromPattern (PConstructor _ constructor _) _ = + error $ "predicatesFromPattern for " <> show constructor -- | turn a single `Predicate` into a `WasmExpr` for that predicate, that -- should return a boolean diff --git a/wasm-calc11/test/Test/Helpers.hs b/wasm-calc11/test/Test/Helpers.hs index 17846ffc..60b5b0f4 100644 --- a/wasm-calc11/test/Test/Helpers.hs +++ b/wasm-calc11/test/Test/Helpers.hs @@ -19,6 +19,7 @@ module Test.Helpers tyVar, patTuple, patInt, + patBool, patVar, ) where @@ -84,6 +85,10 @@ patTuple = \case (a : rest) -> PTuple mempty a (NE.fromList rest) _ -> error "not enough items for patTuple" +patBool :: (Monoid ann) => Bool -> Pattern ann +patBool = PLiteral mempty . PBool + + patInt :: (Monoid ann) => Word64 -> Pattern ann patInt = PLiteral mempty . PIntLit diff --git a/wasm-calc11/test/Test/Parser/ParserSpec.hs b/wasm-calc11/test/Test/Parser/ParserSpec.hs index 2bd3125a..7f0cb187 100644 --- a/wasm-calc11/test/Test/Parser/ParserSpec.hs +++ b/wasm-calc11/test/Test/Parser/ParserSpec.hs @@ -392,7 +392,8 @@ spec = do [ ("_", PWildcard ()), ("a", PVar () "a"), ("Box(_)", PBox () (PWildcard ())), - ("1", patInt 1) + ("1", patInt 1), + ("Just(True)", PConstructor () "Just" [patBool True]) ] traverse_ ( \(str, pat) -> it (T.unpack str) $ do diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index b9f7f9fe..d7ddf8dd 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -370,6 +370,10 @@ spec = do "}" ], Wasm.VI64 202 + ), + ( joinLines ["type Maybe = Just(a) | Nothing", + asTest "case Just((100: Int64)) { Just(a) -> a + 1, Nothing -> 0 }"], + Wasm.VI64 101 ) {-, -- absolutely baffled why `allocated` is not dropped here when we From 4dc13dce2f4332d1971120d6e6019a4f4f604fc9 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Fri, 19 Jul 2024 23:20:25 +0100 Subject: [PATCH 02/23] Typecheck those constructor patterns --- wasm-calc11/src/Calc/Parser/Pattern.hs | 22 ++++++++++ wasm-calc11/src/Calc/Typecheck/Helpers.hs | 41 +++++++++++++++++- wasm-calc11/src/Calc/Typecheck/Infer.hs | 43 ++++++++----------- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 17 +++++++- wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 2 +- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 2 +- 6 files changed, 98 insertions(+), 29 deletions(-) diff --git a/wasm-calc11/src/Calc/Parser/Pattern.hs b/wasm-calc11/src/Calc/Parser/Pattern.hs index b8fd0f34..a77075e7 100644 --- a/wasm-calc11/src/Calc/Parser/Pattern.hs +++ b/wasm-calc11/src/Calc/Parser/Pattern.hs @@ -23,6 +23,7 @@ patternParser = <|> try patWildcardParser <|> try patVariableParser <|> patBoxParser + <|> patConstructorParser <|> patPrimParser ) ) @@ -71,3 +72,24 @@ patBoxParser = label "box" $ patPrimParser :: Parser ParserPattern patPrimParser = myLexeme $ withLocation PLiteral primParser + +---- + +argsParser :: Parser [ParserPattern] +argsParser = try someP <|> pure [] + where + someP = some patternParser + +patConstructorParser :: Parser ParserPattern +patConstructorParser = + let parser = do + cons <- myLexeme constructorParserInternal + args <- argsParser + pure (cons, args) + in withLocation + ( \loc (cons, args) -> + PConstructor loc cons args + ) + parser + + diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index c763491e..d83f4032 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE NamedFieldPuns #-} - + {-# LANGUAGE LambdaCase #-} module Calc.Typecheck.Helpers ( runTypecheckM, lookupVar, @@ -12,6 +12,8 @@ module Calc.Typecheck.Helpers lookupGlobal, arrangeDataTypes, calculateMonomorphisedTypes, + lookupConstructor, + matchConstructorTypesToArgs ) where @@ -138,6 +140,14 @@ identifiersFromPattern pat@(PTuple _ p ps) ty@(TContainer _ tyItems) = do (throwError $ PatternMismatch ty pat) allIdents <- zipWithM identifiersFromPattern (p : NE.toList ps) (NE.toList tyItems) pure $ mconcat allIdents +identifiersFromPattern (PConstructor ann constructor ps) (TConstructor _ _ tyArgs) = do + (_dataTypeName, dataTypeVars, dataTypeArgs) <- + lookupConstructor ann constructor + + let filtered = matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs + + allIdents <- zipWithM identifiersFromPattern ps filtered + pure $ mconcat allIdents identifiersFromPattern pat ty = throwError $ PatternMismatch ty pat @@ -203,3 +213,32 @@ calculateMonomorphisedTypes typeVars fnArgTys argTys fallbacks = do flipMap :: (Hashable v) => HM.HashMap k v -> HM.HashMap v k flipMap = HM.fromList . fmap (\(k, v) -> (v, k)) . HM.toList + + +lookupConstructor :: + ann -> + Constructor -> + TypecheckM ann (DataName, [TypeVar], [Type ann]) +lookupConstructor ann constructor = do + result <- asks (M.lookup constructor . tceDataTypes) + case result of + (Just (TCDataType dataType vars args)) -> + pure (dataType, vars, args) + Nothing -> + throwError $ ConstructorNotFound ann constructor + + + +matchConstructorTypesToArgs :: [TypeVar] -> [Type ann] -> [Type ann] -> [Type ann] +matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs = + let pairs = M.fromList (zip dataTypeVars tyArgs) + filteredTyArgs = + ( \case + TVar _ var -> case M.lookup var pairs of + Just ty -> ty + Nothing -> error "cannot find" + otherTy -> otherTy + ) + <$> dataTypeArgs + in filteredTyArgs + diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index d4e6094e..a70a8631 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -345,6 +345,24 @@ checkPattern ty@(TContainer _ tyItems) pat@(PTuple _ p ps) = do pHead <- checkPattern (NE.head tyItems) p pTail <- zipWithM checkPattern (NE.tail tyItems) (NE.toList ps) pure (PTuple ty pHead (NE.fromList pTail)) +checkPattern (TConstructor _ tyDataName tyArgs) (PConstructor ann constructor patArgs) = do + (dataTypeName, dataTypeVars, dataTypeArgs) <- + lookupConstructor ann constructor + + unless (tyDataName == dataTypeName) $ + error "wrong" + + let filtered = matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs + + typedArgs <- zipWithM checkPattern filtered patArgs + + let fallbackTypes = M.fromList (zip dataTypeVars tyArgs) + + monomorphisedArgs <- + calculateMonomorphisedTypes dataTypeVars dataTypeArgs (getOuterPatternAnnotation <$> typedArgs) fallbackTypes + + let ty = TConstructor ann dataTypeName (snd <$> monomorphisedArgs) + pure (PConstructor ty constructor typedArgs) checkPattern ty pat = throwError $ PatternMismatch ty pat checkTuple :: @@ -378,19 +396,6 @@ checkTuple Nothing ann fstExpr restExpr = do ) pure $ ETuple typ typedFst typedRest -matchConstructorTypesToArgs :: [TypeVar] -> [Type ann] -> [Type ann] -> [Type ann] -matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs = - let pairs = M.fromList (zip dataTypeVars tyArgs) - filteredTyArgs = - ( \case - TVar _ var -> case M.lookup var pairs of - Just ty -> ty - Nothing -> error "cannot find" - otherTy -> otherTy - ) - <$> dataTypeArgs - in filteredTyArgs - checkConstructor :: Maybe (DataName, [Type ann]) -> ann -> Constructor -> [Expr ann] -> TypecheckM ann (Expr (Type ann)) checkConstructor maybeTy ann constructor args = do (dataTypeName, dataTypeVars, dataTypeArgs) <- @@ -435,18 +440,6 @@ checkLet maybeReturnTy ann pat expr rest = do Left patternMatchError -> throwError (PatternMatchError patternMatchError) pure $ ELet (getOuterAnnotation typedRest $> ann) typedPat typedExpr typedRest -lookupConstructor :: - ann -> - Constructor -> - TypecheckM ann (DataName, [TypeVar], [Type ann]) -lookupConstructor ann constructor = do - result <- asks (M.lookup constructor . tceDataTypes) - case result of - (Just (TCDataType dataType vars args)) -> - pure (dataType, vars, args) - Nothing -> - throwError $ ConstructorNotFound ann constructor - checkMatch :: Maybe (Type ann) -> ann -> Expr ann -> NE.NonEmpty (Pattern ann, Expr ann) -> TypecheckM ann (Expr (Type ann)) checkMatch maybeTy ann matchExpr pats = do elabExpr <- infer matchExpr diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index 4d41e476..f8fa4ca6 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -190,7 +190,22 @@ fromExpr (EPrim (ty, _) prim) = WPrim <$> fromPrim ty prim fromExpr (EMatch _ expr pats) = fromMatch expr pats -fromExpr (EConstructor {}) = error "fromExpr EConstructor" +fromExpr (EConstructor (ty,_) _constructor args) = do + -- TODO: add the constructor number in + wasmType <- liftEither $ scalarFromType ty + index <- addLocal Nothing wasmType + let allItems = zip [0..] args + tupleLength = memorySizeForType ty + allocate = WAllocate (fromIntegral tupleLength) + offsetList = getOffsetList ty + WSet index allocate + <$> traverse + ( \(i, item) -> + (,,) (offsetList !! i) + <$> liftEither (scalarFromType (fst $ getOuterAnnotation item)) + <*> fromExpr item + ) + allItems fromExpr (EBlock (_, Just _) _) = do error "found drops on block" fromExpr (EBlock _ expr) = do diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index 6f85f18e..4f460c7e 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -209,7 +209,7 @@ scalarFromType (TVar _ _) = pure Pointer -- all polymorphic variables are Pointer scalarFromType (TUnificationVar {}) = pure Pointer -scalarFromType (TConstructor {}) = error "scalarFromType" +scalarFromType (TConstructor {}) = pure Pointer -- maybe enums will become I8 in future, but for now, it's all pointers genericArgName :: TypeVar -> Identifier genericArgName generic = diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index d7ddf8dd..529092c0 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -390,7 +390,7 @@ spec = do )-} ] - describe "From expressions" $ do + fdescribe "From expressions" $ do traverse_ testWithInterpreter testVals describe "Deallocations for expressions" $ do From d80865a21b891cd7372ab969987e0da073202a3c Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Mon, 22 Jul 2024 23:49:48 +0100 Subject: [PATCH 03/23] Add data type map and start doing lookup 'n' shit --- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 4 ++- wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs | 22 ++++++++++---- .../Calc/Wasm/FromExpr/Patterns/Predicates.hs | 30 ++++++++++++------- wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs | 3 +- 4 files changed, 41 insertions(+), 18 deletions(-) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index f8fa4ca6..8afbc158 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -133,6 +133,8 @@ fromMatch expr pats = do -- return type of exprs wasmReturnType <- liftEither $ scalarFromType $ fst $ getOuterAnnotation headExpr + dataTypes <- gets fesDataTypes + -- fold through patterns wasmPatExpr <- foldr @@ -140,7 +142,7 @@ fromMatch expr pats = do predExprs <- traverse (predicateToWasm (WVar index)) - (predicatesFromPattern (fst <$> pat) mempty) + (predicatesFromPattern dataTypes (fst <$> pat) mempty) wasmPatExpr <- patternBindings pat patExpr index case NE.nonEmpty predExprs of Nothing -> pure wasmPatExpr diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs index 82926a41..3cbc4287 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs @@ -63,7 +63,8 @@ fromTest funcMap globalMap (Test {tesName = Identifier testName, tesExpr}) = do fesGlobals = globalMap, fesImports = mempty, fesFunctions = funcMap, - fesGenerated = mempty + fesGenerated = mempty, + fesDataTypes = mempty } ) @@ -81,10 +82,11 @@ fromFunction :: M.Map FunctionName FromExprFunc -> M.Map FunctionName FromExprImport -> M.Map Identifier FromExprGlobal -> + M.Map DataName [Constructor] -> [WasmFunction] -> Function (Type ann) -> Either FromWasmError ([WasmFunction], WasmFunction) -fromFunction functionAbilities funcMap importMap globalMap generatedFns fn@Function {fnPublic, fnBody, fnArgs, fnFunctionName, fnGenerics} = do +fromFunction functionAbilities funcMap importMap globalMap dataTypeMap generatedFns fn@Function {fnPublic, fnBody, fnArgs, fnFunctionName, fnGenerics} = do args <- traverse ( \(FunctionArg {faName = ArgumentName ident, faType}) -> do @@ -113,7 +115,8 @@ fromFunction functionAbilities funcMap importMap globalMap generatedFns fn@Funct fesGlobals = globalMap, fesImports = importMap, fesFunctions = funcMap, - fesGenerated = generatedFns + fesGenerated = generatedFns, + fesDataTypes = dataTypeMap } ) @@ -162,7 +165,8 @@ fromGlobal (Global {glbExpr, glbMutability}) = do fesGlobals = mempty, fesImports = mempty, fesFunctions = mempty, - fesGenerated = mempty + fesGenerated = mempty, + fesDataTypes = mempty } ) @@ -173,15 +177,21 @@ fromGlobal (Global {glbExpr, glbMutability}) = do wgType <- scalarFromType (getOuterAnnotation glbExpr) pure $ WasmGlobal {wgExpr, wgType, wgMutable} +getDataTypeMap :: [Data ann] -> M.Map DataName [Constructor] +getDataTypeMap = + foldMap (\(Data {dtName,dtConstructors}) -> + M.singleton dtName (M.keys dtConstructors)) + fromModule :: (Show ann, Ord ann) => Module (Type ann) -> Either FromWasmError WasmModule -fromModule wholeMod@(Module {mdMemory, mdTests, mdGlobals, mdImports, mdFunctions}) = do +fromModule wholeMod@(Module {mdDataTypes,mdMemory, mdTests, mdGlobals, mdImports, mdFunctions}) = do let moduleAbilities = getAbilitiesForModule wholeMod importMap <- getImportMap mdImports funcMap <- getFunctionMap mdFunctions globalMap <- getGlobalMap mdGlobals + let dataTypeMap = getDataTypeMap mdDataTypes wasmGlobals <- traverse fromGlobal mdGlobals @@ -189,7 +199,7 @@ fromModule wholeMod@(Module {mdMemory, mdTests, mdGlobals, mdImports, mdFunction foldM ( \(generatedFns, fns) input -> do (generated, newFn) <- - fromFunction (maFunctions moduleAbilities) funcMap importMap globalMap generatedFns input + fromFunction (maFunctions moduleAbilities) funcMap importMap globalMap dataTypeMap generatedFns input pure (generated, [newFn] <> fns) ) ([], []) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index 3ef6e8b2..dcffa0ef 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -3,6 +3,10 @@ module Calc.Wasm.FromExpr.Patterns.Predicates where +import Calc.TypeUtils +import Calc.Types.Constructor +import qualified Data.Map.Strict as M +import Calc.Types.DataName import Calc.ExprUtils import Calc.Types.Op import Calc.Types.Pattern @@ -20,24 +24,30 @@ data Predicate ann = Equals [(Type ann, Natural)] (Type ann) Prim deriving stock (Eq, Ord, Show) -- | Return a list of things that would need to be true for a pattern to match -predicatesFromPattern :: Pattern (Type ann) -> [(Type ann, Natural)] -> [Predicate ann] -predicatesFromPattern (PWildcard {}) _ = mempty -predicatesFromPattern (PLiteral ty prim) path = [Equals path ty prim] -predicatesFromPattern (PVar {}) _ = mempty -predicatesFromPattern (PBox _ inner) path = - predicatesFromPattern inner (path <> [(getOuterPatternAnnotation inner, 0)]) -predicatesFromPattern (PTuple ty p ps) path = +predicatesFromPattern :: M.Map DataName [Constructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> [Predicate ann] +predicatesFromPattern _ (PWildcard {}) _ = mempty +predicatesFromPattern _ (PLiteral ty prim) path = [Equals path ty prim] +predicatesFromPattern _ (PVar {}) _ = mempty +predicatesFromPattern dataTypes (PBox _ inner) path = + predicatesFromPattern dataTypes inner (path <> [(getOuterPatternAnnotation inner, 0)]) +predicatesFromPattern dataTypes (PTuple ty p ps) path = let allPs = zip (p : NE.toList ps) [0 ..] offsetList = getOffsetList ty in foldMap ( \(pat, index) -> - predicatesFromPattern + predicatesFromPattern dataTypes pat (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) ) allPs -predicatesFromPattern (PConstructor _ constructor _) _ = - error $ "predicatesFromPattern for " <> show constructor +predicatesFromPattern _dataTypes (PConstructor ty _constructor _) path = + -- what + let _typeName = case ty of + TConstructor _ tn _ -> tn + _ -> error "should be type" + -- wrong but yolo + constructorValue = 1 + in [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] -- | turn a single `Predicate` into a `WasmExpr` for that predicate, that -- should return a boolean diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs index 766000d6..0a7c6e98 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs @@ -23,7 +23,8 @@ data FromExprState = FromExprState fesGlobals :: M.Map Identifier FromExprGlobal, fesVars :: [(Maybe Identifier, WasmType)], fesArgs :: [(Identifier, WasmType)], - fesGenerated :: [WasmFunction] + fesGenerated :: [WasmFunction], + fesDataTypes :: M.Map DataName [Constructor] } deriving stock (Eq, Ord, Show) From bbaa91382ef270bf0afb1c4b71071ec7a52285cd Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Thu, 25 Jul 2024 18:04:23 +0100 Subject: [PATCH 04/23] Move helpers to FromExpr, start keeping data type map --- wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs | 3 +- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 1 - wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 83 ++++++++++++++++++- wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs | 8 +- .../src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 1 - .../Calc/Wasm/FromExpr/Patterns/Predicates.hs | 4 +- wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs | 10 ++- wasm-calc11/src/Calc/Wasm/ToWasm/Helpers.hs | 83 ------------------- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 19 ++++- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 2 +- 10 files changed, 116 insertions(+), 98 deletions(-) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs index d1db3225..c4f3c82b 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs @@ -16,14 +16,13 @@ import Calc.Linearity (Drops (..)) import Calc.TypeUtils (monoidType) import Calc.Types import Calc.Wasm.FromExpr.Helpers - ( addGeneratedFunction, + ( getOffsetList,addGeneratedFunction, genericArgName, lookupIdent, scalarFromType, ) import Calc.Wasm.FromExpr.Patterns (Path (..)) import Calc.Wasm.FromExpr.Types -import Calc.Wasm.ToWasm.Helpers import Calc.Wasm.ToWasm.Types import Control.Monad (foldM) import Control.Monad.Except diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index 8afbc158..566777f0 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -13,7 +13,6 @@ import Calc.Wasm.FromExpr.Drops import Calc.Wasm.FromExpr.Helpers import Calc.Wasm.FromExpr.Patterns import Calc.Wasm.FromExpr.Types -import Calc.Wasm.ToWasm.Helpers import Calc.Wasm.ToWasm.Types import Control.Monad (void) import Control.Monad.Except diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index 4f460c7e..fa8896a2 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -15,10 +15,12 @@ module Calc.Wasm.FromExpr.Helpers lookupFunction, genericArgName, monomorphiseTypes, - fromPrim, + fromPrim,getOffsetList, boxed,memorySizeForType ) where +import Data.Monoid +import qualified Data.List.NonEmpty as NE import Calc.ExprUtils import Calc.Typecheck ( TypecheckEnv (..), @@ -252,3 +254,82 @@ fromPrim (TPrim _ TInt64) (PIntLit i) = pure (WPInt64 (fromIntegral i)) fromPrim ty prim = throwError $ PrimWithNonNumberType prim (void ty) + +getOffsetList :: Type ann -> [Natural] +getOffsetList (TContainer _ items) = + scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) +getOffsetList _ = [] + + +-- 1 item is a byte, so i8, so i32 is 4 bytes +memorySize :: WasmType -> Natural +memorySize I8 = 1 +memorySize I16 = 2 +memorySize I32 = 4 +memorySize I64 = 8 +memorySize F32 = 4 +memorySize F64 = 8 +memorySize Pointer = memorySize I32 +memorySize Void = 0 + +-- | wrap a `WasmExpr` in a single item struct +boxed :: Natural -> WasmType -> WasmExpr -> WasmExpr +boxed index ty wExpr = + let allocate = WAllocate (memorySize ty) + in WSet index allocate [(0, ty, wExpr)] + +-- | size of the primitive in memory (ie, struct is size of its pointer) +offsetForType :: Type ann -> Natural +offsetForType (TPrim _ TInt8) = + memorySize I8 +offsetForType (TPrim _ TInt16) = + memorySize I16 +offsetForType (TPrim _ TInt32) = + memorySize I32 +offsetForType (TPrim _ TInt64) = + memorySize I64 +offsetForType (TPrim _ TFloat32) = + memorySize F32 +offsetForType (TPrim _ TFloat64) = + memorySize F64 +offsetForType (TPrim _ TBool) = + memorySize I32 +offsetForType (TConstructor {}) = error "offsetForType TConstructor" +offsetForType (TPrim _ TVoid) = + error "offsetForType TVoid" +offsetForType (TContainer _ _) = + memorySize Pointer +offsetForType (TFunction {}) = + memorySize Pointer +offsetForType (TVar _ _) = + memorySize Pointer +offsetForType (TUnificationVar _ _) = + error "offsetForType TUnificationVar" + +-- | the actual size of the item in memory +memorySizeForType :: Type ann -> Natural +memorySizeForType (TPrim _ TInt8) = memorySize I8 +memorySizeForType (TPrim _ TInt16) = + memorySize I16 +memorySizeForType (TPrim _ TInt32) = + memorySize I32 +memorySizeForType (TPrim _ TInt64) = + memorySize I64 +memorySizeForType (TPrim _ TFloat32) = + memorySize F32 +memorySizeForType (TPrim _ TFloat64) = + memorySize F64 +memorySizeForType (TPrim _ TBool) = + memorySize I32 +memorySizeForType (TPrim _ TVoid) = + error "memorySizeForType TVoid" +memorySizeForType (TConstructor {}) = error "memorySizeForType TConstructor" +memorySizeForType (TContainer _ as) = + getSum (foldMap (Sum . memorySizeForType) as) +memorySizeForType (TFunction {}) = + memorySize Pointer +memorySizeForType (TVar _ _) = + memorySize Pointer +memorySizeForType (TUnificationVar _ _) = + error "memorySizeForType TUnificationVar" + diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs index 3cbc4287..d16f381d 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs @@ -82,7 +82,7 @@ fromFunction :: M.Map FunctionName FromExprFunc -> M.Map FunctionName FromExprImport -> M.Map Identifier FromExprGlobal -> - M.Map DataName [Constructor] -> + M.Map DataName [FromExprConstructor] -> [WasmFunction] -> Function (Type ann) -> Either FromWasmError ([WasmFunction], WasmFunction) @@ -177,10 +177,12 @@ fromGlobal (Global {glbExpr, glbMutability}) = do wgType <- scalarFromType (getOuterAnnotation glbExpr) pure $ WasmGlobal {wgExpr, wgType, wgMutable} -getDataTypeMap :: [Data ann] -> M.Map DataName [Constructor] +getDataTypeMap :: [Data ann] -> M.Map DataName [FromExprConstructor] getDataTypeMap = foldMap (\(Data {dtName,dtConstructors}) -> - M.singleton dtName (M.keys dtConstructors)) + let withConstructor (dtCon,dtConTypes) = + FromExprConstructor { fecConstructor = dtCon, fecTypes = dtConTypes } + in M.singleton dtName (withConstructor <$> M.toList dtConstructors)) fromModule :: (Show ann, Ord ann) => diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index 02db110f..939b0cde 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -16,7 +16,6 @@ import Calc.Linearity (Drops (..)) import Calc.Types import Calc.Wasm.FromExpr.Helpers import Calc.Wasm.FromExpr.Types -import Calc.Wasm.ToWasm.Helpers import Calc.Wasm.ToWasm.Types import Control.Monad.Except import qualified Data.List.NonEmpty as NE diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index dcffa0ef..aff7f375 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -4,7 +4,6 @@ module Calc.Wasm.FromExpr.Patterns.Predicates where import Calc.TypeUtils -import Calc.Types.Constructor import qualified Data.Map.Strict as M import Calc.Types.DataName import Calc.ExprUtils @@ -14,7 +13,6 @@ import Calc.Types.Prim import Calc.Types.Type import Calc.Wasm.FromExpr.Helpers import Calc.Wasm.FromExpr.Types -import Calc.Wasm.ToWasm.Helpers import Calc.Wasm.ToWasm.Types import Control.Monad.Except import qualified Data.List.NonEmpty as NE @@ -24,7 +22,7 @@ data Predicate ann = Equals [(Type ann, Natural)] (Type ann) Prim deriving stock (Eq, Ord, Show) -- | Return a list of things that would need to be true for a pattern to match -predicatesFromPattern :: M.Map DataName [Constructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> [Predicate ann] +predicatesFromPattern :: M.Map DataName [FromExprConstructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> [Predicate ann] predicatesFromPattern _ (PWildcard {}) _ = mempty predicatesFromPattern _ (PLiteral ty prim) path = [Equals path ty prim] predicatesFromPattern _ (PVar {}) _ = mempty diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs index 0a7c6e98..f00cec6d 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs @@ -7,7 +7,7 @@ module Calc.Wasm.FromExpr.Types FromExprFunc (..), FromExprImport (..), FromWasmError (..), - ) + FromExprConstructor(..)) where import Calc.Types @@ -24,10 +24,16 @@ data FromExprState = FromExprState fesVars :: [(Maybe Identifier, WasmType)], fesArgs :: [(Identifier, WasmType)], fesGenerated :: [WasmFunction], - fesDataTypes :: M.Map DataName [Constructor] + fesDataTypes :: M.Map DataName [FromExprConstructor] } deriving stock (Eq, Ord, Show) +data FromExprConstructor = FromExprConstructor { + fecConstructor :: Constructor, + fecTypes :: [WasmType] + } + deriving stock (Eq, Ord, Show) + newtype FromExprGlobal = FromExprGlobal {fegIndex :: Natural} deriving stock (Eq, Ord, Show) diff --git a/wasm-calc11/src/Calc/Wasm/ToWasm/Helpers.hs b/wasm-calc11/src/Calc/Wasm/ToWasm/Helpers.hs index 9c338b18..de1261e9 100644 --- a/wasm-calc11/src/Calc/Wasm/ToWasm/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/ToWasm/Helpers.hs @@ -6,12 +6,7 @@ module Calc.Wasm.ToWasm.Helpers ( UsesAllocator (..), moduleUsesAllocator, - getOffsetList, allocCountIndex, - boxed, - memorySize, - memorySizeForType, - offsetForType, testName, allocIndex, dropIndex, @@ -25,7 +20,6 @@ import Calc.Types import Calc.Wasm.ToWasm.Types import Control.Monad.Reader import Data.Bool (bool) -import qualified Data.List.NonEmpty as NE import Data.Monoid import qualified Data.Set as S import qualified Data.Text as T @@ -67,80 +61,3 @@ globalOffset = asks tweGlobalOffset -- what do we call tests in Wasm exports testName :: WasmTest -> T.Text testName (WasmTest {wtName}) = "_test_" <> wtName - --- 1 item is a byte, so i8, so i32 is 4 bytes -memorySize :: WasmType -> Natural -memorySize I8 = 1 -memorySize I16 = 2 -memorySize I32 = 4 -memorySize I64 = 8 -memorySize F32 = 4 -memorySize F64 = 8 -memorySize Pointer = memorySize I32 -memorySize Void = 0 - --- | wrap a `WasmExpr` in a single item struct -boxed :: Natural -> WasmType -> WasmExpr -> WasmExpr -boxed index ty wExpr = - let allocate = WAllocate (memorySize ty) - in WSet index allocate [(0, ty, wExpr)] - -getOffsetList :: Type ann -> [Natural] -getOffsetList (TContainer _ items) = - scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) -getOffsetList _ = [] - --- | size of the primitive in memory (ie, struct is size of its pointer) -offsetForType :: Type ann -> Natural -offsetForType (TPrim _ TInt8) = - memorySize I8 -offsetForType (TPrim _ TInt16) = - memorySize I16 -offsetForType (TPrim _ TInt32) = - memorySize I32 -offsetForType (TPrim _ TInt64) = - memorySize I64 -offsetForType (TPrim _ TFloat32) = - memorySize F32 -offsetForType (TPrim _ TFloat64) = - memorySize F64 -offsetForType (TPrim _ TBool) = - memorySize I32 -offsetForType (TConstructor {}) = error "offsetForType TConstructor" -offsetForType (TPrim _ TVoid) = - error "offsetForType TVoid" -offsetForType (TContainer _ _) = - memorySize Pointer -offsetForType (TFunction {}) = - memorySize Pointer -offsetForType (TVar _ _) = - memorySize Pointer -offsetForType (TUnificationVar _ _) = - error "offsetForType TUnificationVar" - --- | the actual size of the item in memory -memorySizeForType :: Type ann -> Natural -memorySizeForType (TPrim _ TInt8) = memorySize I8 -memorySizeForType (TPrim _ TInt16) = - memorySize I16 -memorySizeForType (TPrim _ TInt32) = - memorySize I32 -memorySizeForType (TPrim _ TInt64) = - memorySize I64 -memorySizeForType (TPrim _ TFloat32) = - memorySize F32 -memorySizeForType (TPrim _ TFloat64) = - memorySize F64 -memorySizeForType (TPrim _ TBool) = - memorySize I32 -memorySizeForType (TPrim _ TVoid) = - error "memorySizeForType TVoid" -memorySizeForType (TConstructor {}) = error "memorySizeForType TConstructor" -memorySizeForType (TContainer _ as) = - getSum (foldMap (Sum . memorySizeForType) as) -memorySizeForType (TFunction {}) = - memorySize Pointer -memorySizeForType (TVar _ _) = - memorySize Pointer -memorySizeForType (TUnificationVar _ _) = - error "memorySizeForType TUnificationVar" diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index 448bae17..fd3d007e 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -10,7 +10,7 @@ import Calc.Wasm.FromExpr.Drops createDropFunction, typeToDropPaths, ) -import Calc.Wasm.FromExpr.Helpers (monomorphiseTypes) +import Calc.Wasm.FromExpr.Helpers (monomorphiseTypes,getOffsetList) import Calc.Wasm.FromExpr.Patterns.Predicates import Calc.Wasm.ToWasm.Types import Control.Monad (void) @@ -28,6 +28,23 @@ unsafeTy tyString = spec :: Spec spec = do describe "FromWasmSpec" $ do + describe "getOffsetList" $ do + it "Tuple of ints" $ do + getOffsetList (unsafeTy "(Int32,Int32,Int64)") + `shouldBe` [0,4,8,16] + + it "Tuple of smaller ints" $ do + getOffsetList (unsafeTy "(Int8,Int8,Int64)") + `shouldBe` [0,1,2,10] + + it "Construct with single item" $ do + getOffsetList (unsafeTy "Maybe(Int8)") + `shouldBe` [1,2] + + it "Construct with two items" $ do + getOffsetList (unsafeTy "These(Int8,Int64)") + `shouldBe` [1,2,10] + describe "calculateMonomorphisedTypes" $ do it "Ints" $ do monomorphiseTypes @() ["a", "b"] [tyVar "a", tyVar "b"] [tyInt32, tyInt64] diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 529092c0..d7ddf8dd 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -390,7 +390,7 @@ spec = do )-} ] - fdescribe "From expressions" $ do + describe "From expressions" $ do traverse_ testWithInterpreter testVals describe "Deallocations for expressions" $ do From 088d5d94d9cac6a31da23a40dc7288aaac2f871f Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 31 Jul 2024 23:18:11 +0100 Subject: [PATCH 05/23] Smash smash smash --- wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs | 30 ++++----- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 22 ++++--- wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 13 ++-- wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs | 14 +++-- .../src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 61 +++++++++++-------- .../Calc/Wasm/FromExpr/Patterns/Predicates.hs | 23 ++++--- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 30 +++++---- 7 files changed, 112 insertions(+), 81 deletions(-) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs index c4f3c82b..de5b235b 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs @@ -111,25 +111,26 @@ addDropsToWasmExpr drops wasmExpr = Nothing -> pure wasmExpr typeToDropPaths :: - Type ann -> + (MonadState FromExprState m, MonadError FromWasmError m) => Type ann -> (DropPath ann -> DropPath ann) -> - [DropPath ann] -typeToDropPaths ty@(TContainer _ tyItems) addPath = - let offsetList = getOffsetList ty - in mconcat - ( ( \(index, innerTy) -> + m [DropPath ann] +typeToDropPaths ty@(TContainer _ tyItems) addPath = do + offsetList <- getOffsetList ty + innerPaths <- traverse + ( \(index, innerTy) -> typeToDropPaths innerTy ( DropPathSelect innerTy (offsetList !! index) . addPath ) ) - <$> zip [0 ..] (NE.toList tyItems) - ) - <> [addPath (DropPathFetch Nothing)] + (zip [0 ..] (NE.toList tyItems)) + + pure (mconcat innerPaths + <> [addPath (DropPathFetch Nothing)]) typeToDropPaths (TVar _ tyVar) addPath = - [addPath (DropPathFetch (Just tyVar))] -typeToDropPaths _ _ = mempty + pure [addPath (DropPathFetch (Just tyVar))] +typeToDropPaths _ _ = pure mempty typeVars :: Type ann -> S.Set TypeVar typeVars (TVar _ tv) = S.singleton tv @@ -153,10 +154,11 @@ dropFunctionForType ty = dropFunc <- createDropFunction 1 ty WFunctionPointer <$> addGeneratedFunction dropFunc -createDropFunction :: (MonadError FromWasmError m) => Natural -> Type ann -> m WasmFunction +createDropFunction :: (MonadError FromWasmError m, + MonadState FromExprState m) => Natural -> Type ann -> m WasmFunction createDropFunction natIndex ty = do - let dropPaths = typeToDropPaths ty id - typeVarList = S.toList (typeVars ty) + dropPaths <- typeToDropPaths ty id + let typeVarList = S.toList (typeVars ty) allTypeVars = M.fromList $ zip typeVarList [0 ..] wasmTy <- liftEither (scalarFromType ty) let arg = 0 diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index 566777f0..3d7a60e0 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -28,7 +28,7 @@ patternBindings :: Natural -> m WasmExpr patternBindings pat patExpr index = do - let paths = patternToPaths (fst <$> pat) id + paths <- patternToPaths (fst <$> pat) id -- turn patterns into indexes and expressions indexes <- @@ -49,12 +49,14 @@ patternBindings pat patExpr index = do -- convert the continuation expr wasmPatExpr <- fromExprWithDrops patExpr + dropPaths <- patternToDropPaths pat id + -- drop items in the match expr we will no longer need - dropPaths <- - traverse (addDropsFromPath index) (patternToDropPaths pat id) + dropPathExprs <- + traverse (addDropsFromPath index) dropPaths -- take care of stuff we've pattern matched into oblivion - let wasmPatExprWithDrops = foldr (WSequence Void) wasmPatExpr dropPaths + let wasmPatExprWithDrops = foldr (WSequence Void) wasmPatExpr dropPathExprs pure $ foldr @@ -75,7 +77,7 @@ fromLet :: Expr (Type ann, Maybe (Drops ann)) -> m WasmExpr fromLet pat expr rest = do - let paths = patternToPaths (fst <$> pat) id + paths <- patternToPaths (fst <$> pat) id if null paths then do wasmTy <- liftEither $ scalarFromType $ fst $ getOuterPatternAnnotation pat @@ -138,10 +140,10 @@ fromMatch expr pats = do wasmPatExpr <- foldr ( \(pat, patExpr) wholeExpr -> do + preds <- + predicatesFromPattern dataTypes (fst <$> pat) mempty predExprs <- - traverse - (predicateToWasm (WVar index)) - (predicatesFromPattern dataTypes (fst <$> pat) mempty) + traverse (predicateToWasm (WVar index)) preds wasmPatExpr <- patternBindings pat patExpr index case NE.nonEmpty predExprs of Nothing -> pure wasmPatExpr @@ -198,7 +200,7 @@ fromExpr (EConstructor (ty,_) _constructor args) = do let allItems = zip [0..] args tupleLength = memorySizeForType ty allocate = WAllocate (fromIntegral tupleLength) - offsetList = getOffsetList ty + offsetList <- getOffsetList ty WSet index allocate <$> traverse ( \(i, item) -> @@ -247,7 +249,7 @@ fromExpr (ETuple (ty, _) a as) = do let allItems = zip [0 ..] (a : NE.toList as) tupleLength = memorySizeForType ty allocate = WAllocate (fromIntegral tupleLength) - offsetList = getOffsetList ty + offsetList <- getOffsetList ty WSet index allocate <$> traverse ( \(i, item) -> diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index fa8896a2..8966583a 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -255,11 +255,16 @@ fromPrim (TPrim _ TInt64) (PIntLit i) = fromPrim ty prim = throwError $ PrimWithNonNumberType prim (void ty) -getOffsetList :: Type ann -> [Natural] +getOffsetList :: (MonadError FromWasmError m, MonadState FromExprState m) => Type ann -> m [Natural] getOffsetList (TContainer _ items) = - scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) -getOffsetList _ = [] - + pure $ scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) +getOffsetList (TConstructor _ constructor _items) = do + maybeDataType <- gets (M.lookup constructor . fesDataTypes) + dt <- case maybeDataType of + Just dt -> pure dt + Nothing -> error "oh fuck" + error (show dt) +getOffsetList _ = pure [] -- 1 item is a byte, so i8, so i32 is 4 bytes memorySize :: WasmType -> Natural diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs index d16f381d..c1fd4347 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs @@ -177,12 +177,14 @@ fromGlobal (Global {glbExpr, glbMutability}) = do wgType <- scalarFromType (getOuterAnnotation glbExpr) pure $ WasmGlobal {wgExpr, wgType, wgMutable} -getDataTypeMap :: [Data ann] -> M.Map DataName [FromExprConstructor] +getDataTypeMap :: [Data ann] -> Either FromWasmError (M.Map DataName [FromExprConstructor]) getDataTypeMap = - foldMap (\(Data {dtName,dtConstructors}) -> - let withConstructor (dtCon,dtConTypes) = - FromExprConstructor { fecConstructor = dtCon, fecTypes = dtConTypes } - in M.singleton dtName (withConstructor <$> M.toList dtConstructors)) + fmap mconcat . traverse (\(Data {dtName,dtConstructors}) -> + let withConstructor (dtCon,dtConTypes) = do + wasmTypes <- traverse scalarFromType dtConTypes + pure $ FromExprConstructor { fecConstructor = dtCon, + fecTypes = wasmTypes } + in M.singleton dtName <$> (traverse withConstructor $ M.toList dtConstructors)) fromModule :: (Show ann, Ord ann) => @@ -193,7 +195,7 @@ fromModule wholeMod@(Module {mdDataTypes,mdMemory, mdTests, mdGlobals, mdImports importMap <- getImportMap mdImports funcMap <- getFunctionMap mdFunctions globalMap <- getGlobalMap mdGlobals - let dataTypeMap = getDataTypeMap mdDataTypes + dataTypeMap <- getDataTypeMap mdDataTypes wasmGlobals <- traverse fromGlobal mdGlobals diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index 939b0cde..729a28ba 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -11,6 +11,7 @@ module Calc.Wasm.FromExpr.Patterns.Paths ) where +import Control.Monad.State import Calc.ExprUtils import Calc.Linearity (Drops (..)) import Calc.Types @@ -32,54 +33,62 @@ data Path ann -- | return a path to every item in Expr marked with `DropMe`. patternToDropPaths :: - (Eq ann) => + (Eq ann, MonadState FromExprState m, + MonadError FromWasmError m) => Pattern (Type ann, Maybe (Drops ann)) -> (Path ann -> Path ann) -> - [Path ann] + m [Path ann] patternToDropPaths (PWildcard (ty, drops)) addPath = - [addPath (PathFetch ty) | drops == Just DropMe] + pure [addPath (PathFetch ty) | drops == Just DropMe] patternToDropPaths (PVar (ty, drops) _) addPath = - [addPath (PathFetch ty) | drops == Just DropMe] -patternToDropPaths (PBox (ty, drops) a) addPath = + pure [addPath (PathFetch ty) | drops == Just DropMe] +patternToDropPaths (PBox (ty, drops) a) addPath = do let dropContainer = ([addPath (PathFetch ty) | drops == Just DropMe]) - in patternToDropPaths a (PathSelect (fst $ getOuterPatternAnnotation a) 0 . addPath) <> dropContainer -patternToDropPaths (PLiteral {}) _ = mempty -patternToDropPaths (PTuple (ty, drops) a as) addPath = - let offsetList = getOffsetList ty - dropContainer = + paths <- patternToDropPaths a (PathSelect (fst $ getOuterPatternAnnotation a) 0 . addPath) + pure (paths <> dropContainer) +patternToDropPaths (PLiteral {}) _ = + pure mempty +patternToDropPaths (PTuple (ty, drops) a as) addPath = do + offsetList <- getOffsetList ty + let dropContainer = ([addPath (PathFetch ty) | drops == Just DropMe]) - in patternToDropPaths a (PathSelect (fst $ getOuterPatternAnnotation a) (head offsetList) . addPath) - <> mconcat - ( ( \(index, innerPat) -> + pathsHead <- + patternToDropPaths a (PathSelect (fst $ getOuterPatternAnnotation a) (head offsetList) . addPath) + pathsTail <- + traverse ( \(index, innerPat) -> let innerTy = fst (getOuterPatternAnnotation innerPat) in patternToDropPaths innerPat (PathSelect innerTy (offsetList !! index) . addPath) ) - <$> zip [1 ..] (NE.toList as) + (zip [1 ..] (NE.toList as) ) - <> dropContainer + pure (pathsHead <> mconcat pathsTail <> dropContainer) patternToDropPaths (PConstructor {}) _ = error "patternToDropPaths: PConstructor" patternToPaths :: + (MonadError FromWasmError m, MonadState FromExprState m) => Pattern (Type ann) -> (Path ann -> Path ann) -> - M.Map Identifier (Path ann) -patternToPaths (PWildcard _) _ = mempty -patternToPaths (PLiteral {}) _ = mempty + m (M.Map Identifier (Path ann)) +patternToPaths (PWildcard _) _ = pure mempty +patternToPaths (PLiteral {}) _ = pure mempty patternToPaths (PVar ty ident) addPath = - M.singleton ident (addPath (PathFetch ty)) + pure $ M.singleton ident (addPath (PathFetch ty)) patternToPaths (PBox _ pat) addPath = patternToPaths pat (PathSelect (getOuterPatternAnnotation pat) 0 . addPath) -patternToPaths (PTuple ty p ps) addPath = - let offsetList = getOffsetList ty - in patternToPaths p (PathSelect (getOuterPatternAnnotation p) (head offsetList) . addPath) - <> mconcat - ( ( \(index, pat) -> +patternToPaths (PTuple ty p ps) addPath = do + offsetList <- getOffsetList ty + + pathsHead <- patternToPaths p (PathSelect (getOuterPatternAnnotation p) (head offsetList) . addPath) + + pathsTail <- traverse + ( \(index, pat) -> let innerTy = getOuterPatternAnnotation pat in patternToPaths pat (PathSelect innerTy (offsetList !! index) . addPath) ) - <$> zip [1 ..] (NE.toList ps) - ) + (zip [1 ..] (NE.toList ps)) + + pure (pathsHead <> mconcat pathsTail) patternToPaths (PConstructor {}) _ = error "patternToPaths: PConstructor" -- | given a path, create AST for fetching it diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index aff7f375..4a7314bb 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -3,6 +3,7 @@ module Calc.Wasm.FromExpr.Patterns.Predicates where +import Control.Monad.State import Calc.TypeUtils import qualified Data.Map.Strict as M import Calc.Types.DataName @@ -22,17 +23,18 @@ data Predicate ann = Equals [(Type ann, Natural)] (Type ann) Prim deriving stock (Eq, Ord, Show) -- | Return a list of things that would need to be true for a pattern to match -predicatesFromPattern :: M.Map DataName [FromExprConstructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> [Predicate ann] -predicatesFromPattern _ (PWildcard {}) _ = mempty -predicatesFromPattern _ (PLiteral ty prim) path = [Equals path ty prim] -predicatesFromPattern _ (PVar {}) _ = mempty +predicatesFromPattern :: (MonadState FromExprState m, + MonadError FromWasmError m) => + M.Map DataName [FromExprConstructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> m [Predicate ann] +predicatesFromPattern _ (PWildcard {}) _ = pure mempty +predicatesFromPattern _ (PLiteral ty prim) path = pure [Equals path ty prim] +predicatesFromPattern _ (PVar {}) _ = pure mempty predicatesFromPattern dataTypes (PBox _ inner) path = predicatesFromPattern dataTypes inner (path <> [(getOuterPatternAnnotation inner, 0)]) -predicatesFromPattern dataTypes (PTuple ty p ps) path = +predicatesFromPattern dataTypes (PTuple ty p ps) path = do let allPs = zip (p : NE.toList ps) [0 ..] - offsetList = getOffsetList ty - in foldMap - ( \(pat, index) -> + offsetList <- getOffsetList ty + mconcat <$> traverse ( \(pat, index) -> predicatesFromPattern dataTypes pat (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) @@ -45,11 +47,12 @@ predicatesFromPattern _dataTypes (PConstructor ty _constructor _) path = _ -> error "should be type" -- wrong but yolo constructorValue = 1 - in [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] + in pure $ [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] -- | turn a single `Predicate` into a `WasmExpr` for that predicate, that -- should return a boolean -predicateToWasm :: (MonadError FromWasmError m) => WasmExpr -> Predicate ann -> m WasmExpr +predicateToWasm :: (MonadState FromExprState m, + MonadError FromWasmError m) => WasmExpr -> Predicate ann -> m WasmExpr predicateToWasm wasmValue (Equals path tyPrim primValue) = do wasmPrim <- fromPrim tyPrim primValue wasmType <- liftEither $ scalarFromType tyPrim diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index fd3d007e..77a50378 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -3,6 +3,7 @@ module Test.Wasm.FromWasmSpec (spec) where +import Control.Monad.State import Calc.Parser import Calc.Types import Calc.Wasm.FromExpr.Drops @@ -10,6 +11,7 @@ import Calc.Wasm.FromExpr.Drops createDropFunction, typeToDropPaths, ) +import Calc.Wasm.FromExpr.Types import Calc.Wasm.FromExpr.Helpers (monomorphiseTypes,getOffsetList) import Calc.Wasm.FromExpr.Patterns.Predicates import Calc.Wasm.ToWasm.Types @@ -25,25 +27,28 @@ unsafeTy tyString = Left e -> error (show e) Right ty -> void ty +exprState :: FromExprState +exprState = FromExprState {} + spec :: Spec spec = do describe "FromWasmSpec" $ do describe "getOffsetList" $ do it "Tuple of ints" $ do - getOffsetList (unsafeTy "(Int32,Int32,Int64)") - `shouldBe` [0,4,8,16] + flip evalStateT exprState (getOffsetList (unsafeTy "(Int32,Int32,Int64)")) + `shouldBe` Right [0,4,8,16] it "Tuple of smaller ints" $ do - getOffsetList (unsafeTy "(Int8,Int8,Int64)") - `shouldBe` [0,1,2,10] + flip evalStateT exprState (getOffsetList (unsafeTy "(Int8,Int8,Int64)")) + `shouldBe` Right [0,1,2,10] it "Construct with single item" $ do - getOffsetList (unsafeTy "Maybe(Int8)") - `shouldBe` [1,2] + flip evalStateT exprState (getOffsetList (unsafeTy "Maybe(Int8)")) + `shouldBe` Right [1,2] it "Construct with two items" $ do - getOffsetList (unsafeTy "These(Int8,Int64)") - `shouldBe` [1,2,10] + flip evalStateT exprState (getOffsetList (unsafeTy "These(Int8,Int64)")) + `shouldBe` Right [1,2,10] describe "calculateMonomorphisedTypes" $ do it "Ints" $ do @@ -115,7 +120,8 @@ spec = do traverse_ ( \(tyString, wasmFunc) -> do it (show tyString) $ do - createDropFunction 1 (unsafeTy tyString) `shouldBe` Right wasmFunc + flip evalStateT exprState + (createDropFunction 1 (unsafeTy tyString))`shouldBe` Right wasmFunc ) testVals @@ -143,7 +149,8 @@ spec = do traverse_ ( \(tyString, paths) -> do it (show tyString) $ do - typeToDropPaths (unsafeTy tyString) id `shouldBe` paths + flip evalStateT exprState + (typeToDropPaths (unsafeTy tyString) id) `shouldBe` Right paths ) testVals @@ -186,6 +193,7 @@ spec = do traverse_ ( \(predicate, val, expected) -> it (show predicate) $ do - predicateToWasm @_ @() val predicate `shouldBe` Right expected + flip evalStateT exprState (predicateToWasm @_ @() val predicate) + `shouldBe` Right expected ) testVals From 947e9fd6f04b57522c1fb5898aed89c62edb2365 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Thu, 8 Aug 2024 22:41:55 +0100 Subject: [PATCH 06/23] Loads of monad was not needed oh no --- wasm-calc11/src/Calc/Parser/Pattern.hs | 2 - wasm-calc11/src/Calc/Typecheck/Helpers.hs | 11 ++- wasm-calc11/src/Calc/Typecheck/Infer.hs | 2 +- wasm-calc11/src/Calc/Types/Pattern.hs | 2 +- wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs | 44 +++++++----- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 10 +-- wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 37 +++++++--- wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs | 20 ++++-- .../src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 54 +++++++++------ .../Calc/Wasm/FromExpr/Patterns/Predicates.hs | 47 ++++++++----- wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs | 11 +-- wasm-calc11/test/Test/Helpers.hs | 3 +- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 67 ++++++++++++++----- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 6 +- 14 files changed, 203 insertions(+), 113 deletions(-) diff --git a/wasm-calc11/src/Calc/Parser/Pattern.hs b/wasm-calc11/src/Calc/Parser/Pattern.hs index a77075e7..6051116d 100644 --- a/wasm-calc11/src/Calc/Parser/Pattern.hs +++ b/wasm-calc11/src/Calc/Parser/Pattern.hs @@ -91,5 +91,3 @@ patConstructorParser = PConstructor loc cons args ) parser - - diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index d83f4032..acbca895 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} - {-# LANGUAGE LambdaCase #-} + module Calc.Typecheck.Helpers ( runTypecheckM, lookupVar, @@ -12,8 +13,8 @@ module Calc.Typecheck.Helpers lookupGlobal, arrangeDataTypes, calculateMonomorphisedTypes, - lookupConstructor, - matchConstructorTypesToArgs + lookupConstructor, + matchConstructorTypesToArgs, ) where @@ -214,7 +215,6 @@ calculateMonomorphisedTypes typeVars fnArgTys argTys fallbacks = do flipMap :: (Hashable v) => HM.HashMap k v -> HM.HashMap v k flipMap = HM.fromList . fmap (\(k, v) -> (v, k)) . HM.toList - lookupConstructor :: ann -> Constructor -> @@ -227,8 +227,6 @@ lookupConstructor ann constructor = do Nothing -> throwError $ ConstructorNotFound ann constructor - - matchConstructorTypesToArgs :: [TypeVar] -> [Type ann] -> [Type ann] -> [Type ann] matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs = let pairs = M.fromList (zip dataTypeVars tyArgs) @@ -241,4 +239,3 @@ matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs = ) <$> dataTypeArgs in filteredTyArgs - diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index a70a8631..065e3e47 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -350,7 +350,7 @@ checkPattern (TConstructor _ tyDataName tyArgs) (PConstructor ann constructor pa lookupConstructor ann constructor unless (tyDataName == dataTypeName) $ - error "wrong" + error "wrong" let filtered = matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs diff --git a/wasm-calc11/src/Calc/Types/Pattern.hs b/wasm-calc11/src/Calc/Types/Pattern.hs index 1071eb10..7da29f64 100644 --- a/wasm-calc11/src/Calc/Types/Pattern.hs +++ b/wasm-calc11/src/Calc/Types/Pattern.hs @@ -4,11 +4,11 @@ module Calc.Types.Pattern where +import Calc.Types.Constructor import Calc.Types.Identifier import Calc.Types.Prim import qualified Data.List.NonEmpty as NE import qualified Prettyprinter as PP -import Calc.Types.Constructor data Pattern ann = PVar ann Identifier diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs index de5b235b..a096c73c 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Drops.hs @@ -16,8 +16,9 @@ import Calc.Linearity (Drops (..)) import Calc.TypeUtils (monoidType) import Calc.Types import Calc.Wasm.FromExpr.Helpers - ( getOffsetList,addGeneratedFunction, + ( addGeneratedFunction, genericArgName, + getOffsetList, lookupIdent, scalarFromType, ) @@ -111,23 +112,27 @@ addDropsToWasmExpr drops wasmExpr = Nothing -> pure wasmExpr typeToDropPaths :: - (MonadState FromExprState m, MonadError FromWasmError m) => Type ann -> + (MonadState FromExprState m, MonadError FromWasmError m) => + Type ann -> (DropPath ann -> DropPath ann) -> m [DropPath ann] typeToDropPaths ty@(TContainer _ tyItems) addPath = do - offsetList <- getOffsetList ty - innerPaths <- traverse - ( \(index, innerTy) -> - typeToDropPaths - innerTy - ( DropPathSelect innerTy (offsetList !! index) - . addPath - ) - ) - (zip [0 ..] (NE.toList tyItems)) - - pure (mconcat innerPaths - <> [addPath (DropPathFetch Nothing)]) + let offsetList = getOffsetList ty + innerPaths <- + traverse + ( \(index, innerTy) -> + typeToDropPaths + innerTy + ( DropPathSelect innerTy (offsetList !! index) + . addPath + ) + ) + (zip [0 ..] (NE.toList tyItems)) + + pure + ( mconcat innerPaths + <> [addPath (DropPathFetch Nothing)] + ) typeToDropPaths (TVar _ tyVar) addPath = pure [addPath (DropPathFetch (Just tyVar))] typeToDropPaths _ _ = pure mempty @@ -154,8 +159,13 @@ dropFunctionForType ty = dropFunc <- createDropFunction 1 ty WFunctionPointer <$> addGeneratedFunction dropFunc -createDropFunction :: (MonadError FromWasmError m, - MonadState FromExprState m) => Natural -> Type ann -> m WasmFunction +createDropFunction :: + ( MonadError FromWasmError m, + MonadState FromExprState m + ) => + Natural -> + Type ann -> + m WasmFunction createDropFunction natIndex ty = do dropPaths <- typeToDropPaths ty id let typeVarList = S.toList (typeVars ty) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index 3d7a60e0..d4cd2d3e 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -141,7 +141,7 @@ fromMatch expr pats = do foldr ( \(pat, patExpr) wholeExpr -> do preds <- - predicatesFromPattern dataTypes (fst <$> pat) mempty + predicatesFromPattern dataTypes (fst <$> pat) mempty predExprs <- traverse (predicateToWasm (WVar index)) preds wasmPatExpr <- patternBindings pat patExpr index @@ -193,14 +193,14 @@ fromExpr (EPrim (ty, _) prim) = WPrim <$> fromPrim ty prim fromExpr (EMatch _ expr pats) = fromMatch expr pats -fromExpr (EConstructor (ty,_) _constructor args) = do +fromExpr (EConstructor (ty, _) _constructor args) = do -- TODO: add the constructor number in wasmType <- liftEither $ scalarFromType ty index <- addLocal Nothing wasmType - let allItems = zip [0..] args + let allItems = zip [0 ..] args tupleLength = memorySizeForType ty allocate = WAllocate (fromIntegral tupleLength) - offsetList <- getOffsetList ty + let offsetList = getOffsetList ty WSet index allocate <$> traverse ( \(i, item) -> @@ -249,7 +249,7 @@ fromExpr (ETuple (ty, _) a as) = do let allItems = zip [0 ..] (a : NE.toList as) tupleLength = memorySizeForType ty allocate = WAllocate (fromIntegral tupleLength) - offsetList <- getOffsetList ty + let offsetList = getOffsetList ty WSet index allocate <$> traverse ( \(i, item) -> diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index 8966583a..f30a3519 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -15,12 +15,14 @@ module Calc.Wasm.FromExpr.Helpers lookupFunction, genericArgName, monomorphiseTypes, - fromPrim,getOffsetList, boxed,memorySizeForType + fromPrim, + getOffsetList, + getOffsetListForConstructor, + boxed, + memorySizeForType, ) where -import Data.Monoid -import qualified Data.List.NonEmpty as NE import Calc.ExprUtils import Calc.Typecheck ( TypecheckEnv (..), @@ -34,7 +36,9 @@ import Control.Monad (void) import Control.Monad.Except import Control.Monad.State import qualified Data.List as List +import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as M +import Data.Monoid import qualified Data.Set as S import qualified Data.Text as T import GHC.Natural @@ -255,16 +259,28 @@ fromPrim (TPrim _ TInt64) (PIntLit i) = fromPrim ty prim = throwError $ PrimWithNonNumberType prim (void ty) -getOffsetList :: (MonadError FromWasmError m, MonadState FromExprState m) => Type ann -> m [Natural] +getOffsetList :: Type ann -> [Natural] getOffsetList (TContainer _ items) = - pure $ scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) -getOffsetList (TConstructor _ constructor _items) = do - maybeDataType <- gets (M.lookup constructor . fesDataTypes) + scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) +getOffsetList _ = [] + +-- right now, we assume that each polymorphic value inside a type is a Pointer +-- type +getOffsetListForConstructor :: (MonadError FromWasmError m, MonadState FromExprState m) => + Type ann -> Constructor -> m [Natural] +getOffsetListForConstructor (TConstructor _ dataTypeName _items) constructor = do + maybeDataType <- gets (M.lookup dataTypeName . fesDataTypes) dt <- case maybeDataType of Just dt -> pure dt - Nothing -> error "oh fuck" - error (show dt) -getOffsetList _ = pure [] + Nothing -> error $ "oh fuck couldn't find " <> show constructor + let tys = lookupConstructor dt constructor + pure $ scanl (\offset item -> offset + memorySize item) (memorySize I8) tys +getOffsetListForConstructor _ _ = pure [] + +lookupConstructor :: [FromExprConstructor] -> Constructor -> [WasmType] +lookupConstructor (FromExprConstructor constructorA tys : rest) constructor + = if constructor == constructorA then tys else lookupConstructor rest constructor +lookupConstructor [] _ = error "sdfsdf" -- 1 item is a byte, so i8, so i32 is 4 bytes memorySize :: WasmType -> Natural @@ -337,4 +353,3 @@ memorySizeForType (TVar _ _) = memorySize Pointer memorySizeForType (TUnificationVar _ _) = error "memorySizeForType TUnificationVar" - diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs index c1fd4347..176f8e6b 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs @@ -179,18 +179,24 @@ fromGlobal (Global {glbExpr, glbMutability}) = do getDataTypeMap :: [Data ann] -> Either FromWasmError (M.Map DataName [FromExprConstructor]) getDataTypeMap = - fmap mconcat . traverse (\(Data {dtName,dtConstructors}) -> - let withConstructor (dtCon,dtConTypes) = do - wasmTypes <- traverse scalarFromType dtConTypes - pure $ FromExprConstructor { fecConstructor = dtCon, - fecTypes = wasmTypes } - in M.singleton dtName <$> (traverse withConstructor $ M.toList dtConstructors)) + fmap mconcat + . traverse + ( \(Data {dtName, dtConstructors}) -> + let withConstructor (dtCon, dtConTypes) = do + wasmTypes <- traverse scalarFromType dtConTypes + pure $ + FromExprConstructor + { fecConstructor = dtCon, + fecTypes = wasmTypes + } + in M.singleton dtName <$> (traverse withConstructor $ M.toList dtConstructors) + ) fromModule :: (Show ann, Ord ann) => Module (Type ann) -> Either FromWasmError WasmModule -fromModule wholeMod@(Module {mdDataTypes,mdMemory, mdTests, mdGlobals, mdImports, mdFunctions}) = do +fromModule wholeMod@(Module {mdDataTypes, mdMemory, mdTests, mdGlobals, mdImports, mdFunctions}) = do let moduleAbilities = getAbilitiesForModule wholeMod importMap <- getImportMap mdImports funcMap <- getFunctionMap mdFunctions diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index 729a28ba..132744c8 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -11,7 +11,6 @@ module Calc.Wasm.FromExpr.Patterns.Paths ) where -import Control.Monad.State import Calc.ExprUtils import Calc.Linearity (Drops (..)) import Calc.Types @@ -19,6 +18,7 @@ import Calc.Wasm.FromExpr.Helpers import Calc.Wasm.FromExpr.Types import Calc.Wasm.ToWasm.Types import Control.Monad.Except +import Control.Monad.State import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as M import GHC.Natural @@ -33,8 +33,10 @@ data Path ann -- | return a path to every item in Expr marked with `DropMe`. patternToDropPaths :: - (Eq ann, MonadState FromExprState m, - MonadError FromWasmError m) => + ( Eq ann, + MonadState FromExprState m, + MonadError FromWasmError m + ) => Pattern (Type ann, Maybe (Drops ann)) -> (Path ann -> Path ann) -> m [Path ann] @@ -50,18 +52,19 @@ patternToDropPaths (PBox (ty, drops) a) addPath = do patternToDropPaths (PLiteral {}) _ = pure mempty patternToDropPaths (PTuple (ty, drops) a as) addPath = do - offsetList <- getOffsetList ty + let offsetList = getOffsetList ty let dropContainer = ([addPath (PathFetch ty) | drops == Just DropMe]) pathsHead <- - patternToDropPaths a (PathSelect (fst $ getOuterPatternAnnotation a) (head offsetList) . addPath) + patternToDropPaths a (PathSelect (fst $ getOuterPatternAnnotation a) (head offsetList) . addPath) pathsTail <- - traverse ( \(index, innerPat) -> - let innerTy = fst (getOuterPatternAnnotation innerPat) - in patternToDropPaths innerPat (PathSelect innerTy (offsetList !! index) . addPath) - ) - (zip [1 ..] (NE.toList as) - ) + traverse + ( \(index, innerPat) -> + let innerTy = fst (getOuterPatternAnnotation innerPat) + in patternToDropPaths innerPat (PathSelect innerTy (offsetList !! index) . addPath) + ) + ( zip [1 ..] (NE.toList as) + ) pure (pathsHead <> mconcat pathsTail <> dropContainer) patternToDropPaths (PConstructor {}) _ = error "patternToDropPaths: PConstructor" @@ -77,19 +80,32 @@ patternToPaths (PVar ty ident) addPath = patternToPaths (PBox _ pat) addPath = patternToPaths pat (PathSelect (getOuterPatternAnnotation pat) 0 . addPath) patternToPaths (PTuple ty p ps) addPath = do - offsetList <- getOffsetList ty + let offsetList = getOffsetList ty pathsHead <- patternToPaths p (PathSelect (getOuterPatternAnnotation p) (head offsetList) . addPath) - pathsTail <- traverse - ( \(index, pat) -> - let innerTy = getOuterPatternAnnotation pat - in patternToPaths pat (PathSelect innerTy (offsetList !! index) . addPath) - ) - (zip [1 ..] (NE.toList ps)) + pathsTail <- + traverse + ( \(index, pat) -> + let innerTy = getOuterPatternAnnotation pat + in patternToPaths pat (PathSelect innerTy (offsetList !! index) . addPath) + ) + (zip [1 ..] (NE.toList ps)) pure (pathsHead <> mconcat pathsTail) -patternToPaths (PConstructor {}) _ = error "patternToPaths: PConstructor" +patternToPaths (PConstructor ty constructor ps) addPath = do + offsetList <- getOffsetListForConstructor ty constructor + paths <- + traverse + ( \(index, pat) -> + let innerTy = getOuterPatternAnnotation pat + in patternToPaths pat (PathSelect innerTy (offsetList !! index) . addPath) + ) + (zip [1 ..] ps) + + pure (mconcat paths) + + -- | given a path, create AST for fetching it fromPath :: (MonadError FromWasmError m) => Natural -> Path ann -> m WasmExpr diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index 4a7314bb..0966ab23 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -3,11 +3,9 @@ module Calc.Wasm.FromExpr.Patterns.Predicates where -import Control.Monad.State +import Calc.ExprUtils import Calc.TypeUtils -import qualified Data.Map.Strict as M import Calc.Types.DataName -import Calc.ExprUtils import Calc.Types.Op import Calc.Types.Pattern import Calc.Types.Prim @@ -16,16 +14,23 @@ import Calc.Wasm.FromExpr.Helpers import Calc.Wasm.FromExpr.Types import Calc.Wasm.ToWasm.Types import Control.Monad.Except +import Control.Monad.State import qualified Data.List.NonEmpty as NE +import qualified Data.Map.Strict as M import GHC.Natural data Predicate ann = Equals [(Type ann, Natural)] (Type ann) Prim deriving stock (Eq, Ord, Show) -- | Return a list of things that would need to be true for a pattern to match -predicatesFromPattern :: (MonadState FromExprState m, - MonadError FromWasmError m) => - M.Map DataName [FromExprConstructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> m [Predicate ann] +predicatesFromPattern :: + ( MonadState FromExprState m, + MonadError FromWasmError m + ) => + M.Map DataName [FromExprConstructor] -> + Pattern (Type ann) -> + [(Type ann, Natural)] -> + m [Predicate ann] predicatesFromPattern _ (PWildcard {}) _ = pure mempty predicatesFromPattern _ (PLiteral ty prim) path = pure [Equals path ty prim] predicatesFromPattern _ (PVar {}) _ = pure mempty @@ -33,26 +38,34 @@ predicatesFromPattern dataTypes (PBox _ inner) path = predicatesFromPattern dataTypes inner (path <> [(getOuterPatternAnnotation inner, 0)]) predicatesFromPattern dataTypes (PTuple ty p ps) path = do let allPs = zip (p : NE.toList ps) [0 ..] - offsetList <- getOffsetList ty - mconcat <$> traverse ( \(pat, index) -> - predicatesFromPattern dataTypes - pat - (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) - ) - allPs + let offsetList = getOffsetList ty + mconcat + <$> traverse + ( \(pat, index) -> + predicatesFromPattern + dataTypes + pat + (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) + ) + allPs predicatesFromPattern _dataTypes (PConstructor ty _constructor _) path = -- what let _typeName = case ty of - TConstructor _ tn _ -> tn - _ -> error "should be type" + TConstructor _ tn _ -> tn + _ -> error "should be type" -- wrong but yolo constructorValue = 1 in pure $ [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] -- | turn a single `Predicate` into a `WasmExpr` for that predicate, that -- should return a boolean -predicateToWasm :: (MonadState FromExprState m, - MonadError FromWasmError m) => WasmExpr -> Predicate ann -> m WasmExpr +predicateToWasm :: + ( MonadState FromExprState m, + MonadError FromWasmError m + ) => + WasmExpr -> + Predicate ann -> + m WasmExpr predicateToWasm wasmValue (Equals path tyPrim primValue) = do wasmPrim <- fromPrim tyPrim primValue wasmType <- liftEither $ scalarFromType tyPrim diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs index f00cec6d..7f4fc9b3 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs @@ -7,7 +7,8 @@ module Calc.Wasm.FromExpr.Types FromExprFunc (..), FromExprImport (..), FromWasmError (..), - FromExprConstructor(..)) + FromExprConstructor (..), + ) where import Calc.Types @@ -28,10 +29,10 @@ data FromExprState = FromExprState } deriving stock (Eq, Ord, Show) -data FromExprConstructor = FromExprConstructor { - fecConstructor :: Constructor, - fecTypes :: [WasmType] - } +data FromExprConstructor = FromExprConstructor + { fecConstructor :: Constructor, + fecTypes :: [WasmType] + } deriving stock (Eq, Ord, Show) newtype FromExprGlobal = FromExprGlobal diff --git a/wasm-calc11/test/Test/Helpers.hs b/wasm-calc11/test/Test/Helpers.hs index 60b5b0f4..43056c43 100644 --- a/wasm-calc11/test/Test/Helpers.hs +++ b/wasm-calc11/test/Test/Helpers.hs @@ -19,7 +19,7 @@ module Test.Helpers tyVar, patTuple, patInt, - patBool, + patBool, patVar, ) where @@ -88,7 +88,6 @@ patTuple = \case patBool :: (Monoid ann) => Bool -> Pattern ann patBool = PLiteral mempty . PBool - patInt :: (Monoid ann) => Word64 -> Pattern ann patInt = PLiteral mempty . PIntLit diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index 77a50378..b3597445 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -1,9 +1,9 @@ +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} module Test.Wasm.FromWasmSpec (spec) where -import Control.Monad.State import Calc.Parser import Calc.Types import Calc.Wasm.FromExpr.Drops @@ -11,12 +11,14 @@ import Calc.Wasm.FromExpr.Drops createDropFunction, typeToDropPaths, ) -import Calc.Wasm.FromExpr.Types -import Calc.Wasm.FromExpr.Helpers (monomorphiseTypes,getOffsetList) +import Calc.Wasm.FromExpr.Helpers (getOffsetList, getOffsetListForConstructor, monomorphiseTypes) import Calc.Wasm.FromExpr.Patterns.Predicates +import Calc.Wasm.FromExpr.Types import Calc.Wasm.ToWasm.Types import Control.Monad (void) +import Control.Monad.State import Data.Foldable (traverse_) +import qualified Data.Map.Strict as M import qualified Data.Text as T import Test.Helpers import Test.Hspec @@ -28,27 +30,52 @@ unsafeTy tyString = Right ty -> void ty exprState :: FromExprState -exprState = FromExprState {} +exprState = + FromExprState + { fesFunctions = mempty, + fesImports = mempty, + fesGlobals = mempty, + fesVars = mempty, + fesArgs = mempty, + fesGenerated = mempty, + fesDataTypes + } + where + fesDataTypes = + M.fromList + [ ( DataName "Maybe", + [ FromExprConstructor "Just" [Pointer], + FromExprConstructor "Nothing" [] + ] + ), + ( DataName "These", + [ FromExprConstructor "This" [Pointer], + FromExprConstructor "That" [Pointer], + FromExprConstructor "These" [Pointer, Pointer] + ] + ) + ] spec :: Spec spec = do describe "FromWasmSpec" $ do describe "getOffsetList" $ do it "Tuple of ints" $ do - flip evalStateT exprState (getOffsetList (unsafeTy "(Int32,Int32,Int64)")) - `shouldBe` Right [0,4,8,16] + getOffsetList (unsafeTy "(Int32,Int32,Int64)") + `shouldBe` [0, 4, 8, 16] it "Tuple of smaller ints" $ do - flip evalStateT exprState (getOffsetList (unsafeTy "(Int8,Int8,Int64)")) - `shouldBe` Right [0,1,2,10] + getOffsetList (unsafeTy "(Int8,Int8,Int64)") + `shouldBe` [0, 1, 2, 10] + describe "getOffsetListForConstructor" $ do it "Construct with single item" $ do - flip evalStateT exprState (getOffsetList (unsafeTy "Maybe(Int8)")) - `shouldBe` Right [1,2] + flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "Maybe(Int8)") "Just") + `shouldBe` Right [1, 5] it "Construct with two items" $ do - flip evalStateT exprState (getOffsetList (unsafeTy "These(Int8,Int64)")) - `shouldBe` Right [1,2,10] + flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8,Int64)") "These") + `shouldBe` Right [1, 5, 9] describe "calculateMonomorphisedTypes" $ do it "Ints" $ do @@ -120,8 +147,11 @@ spec = do traverse_ ( \(tyString, wasmFunc) -> do it (show tyString) $ do - flip evalStateT exprState - (createDropFunction 1 (unsafeTy tyString))`shouldBe` Right wasmFunc + flip + evalStateT + exprState + (createDropFunction 1 (unsafeTy tyString)) + `shouldBe` Right wasmFunc ) testVals @@ -149,8 +179,11 @@ spec = do traverse_ ( \(tyString, paths) -> do it (show tyString) $ do - flip evalStateT exprState - (typeToDropPaths (unsafeTy tyString) id) `shouldBe` Right paths + flip + evalStateT + exprState + (typeToDropPaths (unsafeTy tyString) id) + `shouldBe` Right paths ) testVals @@ -194,6 +227,6 @@ spec = do ( \(predicate, val, expected) -> it (show predicate) $ do flip evalStateT exprState (predicateToWasm @_ @() val predicate) - `shouldBe` Right expected + `shouldBe` Right expected ) testVals diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index d7ddf8dd..973657b3 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -371,8 +371,10 @@ spec = do ], Wasm.VI64 202 ), - ( joinLines ["type Maybe = Just(a) | Nothing", - asTest "case Just((100: Int64)) { Just(a) -> a + 1, Nothing -> 0 }"], + ( joinLines + [ "type Maybe = Just(a) | Nothing", + asTest "case Just((100: Int64)) { Just(a) -> a + 1, Nothing -> 0 }" + ], Wasm.VI64 101 ) {-, From 2513f12b3466f77fa590c65e69ce795802093f4a Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Sat, 10 Aug 2024 22:15:17 +0100 Subject: [PATCH 07/23] Oh well --- wasm-calc11/src/Calc/Typecheck/Elaborate.hs | 7 +++- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 23 ++++++------ wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 34 +++++++++++------- .../src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 16 ++++++++- wasm-calc11/test/Test/Helpers.hs | 35 +++++++++++++++++-- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 29 --------------- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 4 +-- 7 files changed, 91 insertions(+), 57 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Elaborate.hs b/wasm-calc11/src/Calc/Typecheck/Elaborate.hs index a8bf18a7..6d968639 100644 --- a/wasm-calc11/src/Calc/Typecheck/Elaborate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Elaborate.hs @@ -7,6 +7,7 @@ module Calc.Typecheck.Elaborate ) where +import Calc.Types.Data import Calc.ExprUtils import Calc.Typecheck.Error import Calc.Typecheck.Helpers @@ -90,9 +91,13 @@ elaborateModule mdMemory = elaborateMemory <$> mdMemory, mdGlobals = globals, mdTests = tests, - mdDataTypes = mempty + mdDataTypes = elaborateDataType <$> mdDataTypes } +elaborateDataType :: Data ann -> Data (Type ann) +elaborateDataType (Data dtName vars cons) = + Data dtName vars ((fmap . fmap) (\ty -> ty $> ty) cons) + -- check a test expression has type `Bool` -- later we'll also check it does not use any imports elaborateTest :: Test ann -> TypecheckM ann (Test (Type ann)) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index d4cd2d3e..5809c762 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -193,22 +193,25 @@ fromExpr (EPrim (ty, _) prim) = WPrim <$> fromPrim ty prim fromExpr (EMatch _ expr pats) = fromMatch expr pats -fromExpr (EConstructor (ty, _) _constructor args) = do +fromExpr (EConstructor (ty, _) constructor args) = do + let constructorNumber = WPrim (WPInt32 0) -- TODO: add the constructor number in wasmType <- liftEither $ scalarFromType ty index <- addLocal Nothing wasmType - let allItems = zip [0 ..] args - tupleLength = memorySizeForType ty - allocate = WAllocate (fromIntegral tupleLength) - let offsetList = getOffsetList ty - WSet index allocate - <$> traverse + let allItems = zip [1 ..] args + tupleLength <- memorySizeForType ty + let allocate = WAllocate (fromIntegral tupleLength) + offsetList <- getOffsetListForConstructor ty constructor + + wasmItems <- traverse ( \(i, item) -> (,,) (offsetList !! i) <$> liftEither (scalarFromType (fst $ getOuterAnnotation item)) <*> fromExpr item ) allItems + pure $ WSet index allocate ((0,I8,constructorNumber) : wasmItems) + fromExpr (EBlock (_, Just _) _) = do error "found drops on block" fromExpr (EBlock _ expr) = do @@ -247,9 +250,9 @@ fromExpr (ETuple (ty, _) a as) = do wasmType <- liftEither $ scalarFromType ty index <- addLocal Nothing wasmType let allItems = zip [0 ..] (a : NE.toList as) - tupleLength = memorySizeForType ty - allocate = WAllocate (fromIntegral tupleLength) - let offsetList = getOffsetList ty + tupleLength <- memorySizeForType ty + let allocate = WAllocate (fromIntegral tupleLength) + offsetList = getOffsetList ty WSet index allocate <$> traverse ( \(i, item) -> diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index f30a3519..42b4faa9 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -328,28 +328,38 @@ offsetForType (TUnificationVar _ _) = error "offsetForType TUnificationVar" -- | the actual size of the item in memory -memorySizeForType :: Type ann -> Natural -memorySizeForType (TPrim _ TInt8) = memorySize I8 +-- | for sum types this will be the biggest possible amount +memorySizeForType :: (MonadState FromExprState m) => Type ann -> m Natural +memorySizeForType (TPrim _ TInt8) = pure $ memorySize I8 memorySizeForType (TPrim _ TInt16) = - memorySize I16 + pure $ memorySize I16 memorySizeForType (TPrim _ TInt32) = - memorySize I32 + pure $ memorySize I32 memorySizeForType (TPrim _ TInt64) = - memorySize I64 + pure $ memorySize I64 memorySizeForType (TPrim _ TFloat32) = - memorySize F32 + pure $ memorySize F32 memorySizeForType (TPrim _ TFloat64) = - memorySize F64 + pure $ memorySize F64 memorySizeForType (TPrim _ TBool) = - memorySize I32 + pure $ memorySize I32 memorySizeForType (TPrim _ TVoid) = error "memorySizeForType TVoid" -memorySizeForType (TConstructor {}) = error "memorySizeForType TConstructor" +memorySizeForType (TConstructor _ constructor _) = do + dt <- gets (M.lookup constructor . fesDataTypes) + let discriminator = memorySize I8 + case dt of + Just constructors -> do + let sizeOfConstructor (FromExprConstructor _ tys) = + getSum $ foldMap (Sum . memorySize) tys + let sizes = sizeOfConstructor <$> constructors + pure $ discriminator + maximum sizes + Nothing -> error "fuck" memorySizeForType (TContainer _ as) = - getSum (foldMap (Sum . memorySizeForType) as) + getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeForType) (NE.toList as)) memorySizeForType (TFunction {}) = - memorySize Pointer + pure $ memorySize Pointer memorySizeForType (TVar _ _) = - memorySize Pointer + pure $ memorySize Pointer memorySizeForType (TUnificationVar _ _) = error "memorySizeForType TUnificationVar" diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index 132744c8..3c1690a5 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -66,7 +66,21 @@ patternToDropPaths (PTuple (ty, drops) a as) addPath = do ( zip [1 ..] (NE.toList as) ) pure (pathsHead <> mconcat pathsTail <> dropContainer) -patternToDropPaths (PConstructor {}) _ = error "patternToDropPaths: PConstructor" +patternToDropPaths (PConstructor (ty,drops) constructor ps) addPath = do + offsetList <- getOffsetListForConstructor ty constructor + let dropContainer = + ([addPath (PathFetch ty) | drops == Just DropMe]) + paths <- + traverse + ( \(index, innerPat) -> + let innerTy = fst (getOuterPatternAnnotation innerPat) + in patternToDropPaths innerPat (PathSelect innerTy (offsetList !! index) . addPath) + ) + (zip [1 ..] ps) + + pure (mconcat paths <> dropContainer) + + patternToPaths :: (MonadError FromWasmError m, MonadState FromExprState m) => diff --git a/wasm-calc11/test/Test/Helpers.hs b/wasm-calc11/test/Test/Helpers.hs index 43056c43..272541a4 100644 --- a/wasm-calc11/test/Test/Helpers.hs +++ b/wasm-calc11/test/Test/Helpers.hs @@ -1,6 +1,6 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} - + {-# LANGUAGE NamedFieldPuns #-} module Test.Helpers ( joinLines, int, @@ -20,10 +20,13 @@ module Test.Helpers patTuple, patInt, patBool, - patVar, + patVar,exprState ) where +import qualified Data.Map.Strict as M +import Calc.Wasm.FromExpr.Types +import Calc.Wasm.ToWasm.Types import Calc import qualified Data.List.NonEmpty as NE import Data.String @@ -93,3 +96,31 @@ patInt = PLiteral mempty . PIntLit patVar :: (Monoid ann) => String -> Pattern ann patVar = PVar mempty . fromString + +exprState :: FromExprState +exprState = + FromExprState + { fesFunctions = mempty, + fesImports = mempty, + fesGlobals = mempty, + fesVars = mempty, + fesArgs = mempty, + fesGenerated = mempty, + fesDataTypes + } + where + fesDataTypes = + M.fromList + [ ( DataName "Maybe", + [ FromExprConstructor "Just" [Pointer], + FromExprConstructor "Nothing" [] + ] + ), + ( DataName "These", + [ FromExprConstructor "This" [Pointer], + FromExprConstructor "That" [Pointer], + FromExprConstructor "These" [Pointer, Pointer] + ] + ) + ] + diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index b3597445..4f0aaefa 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -13,12 +13,10 @@ import Calc.Wasm.FromExpr.Drops ) import Calc.Wasm.FromExpr.Helpers (getOffsetList, getOffsetListForConstructor, monomorphiseTypes) import Calc.Wasm.FromExpr.Patterns.Predicates -import Calc.Wasm.FromExpr.Types import Calc.Wasm.ToWasm.Types import Control.Monad (void) import Control.Monad.State import Data.Foldable (traverse_) -import qualified Data.Map.Strict as M import qualified Data.Text as T import Test.Helpers import Test.Hspec @@ -29,33 +27,6 @@ unsafeTy tyString = Left e -> error (show e) Right ty -> void ty -exprState :: FromExprState -exprState = - FromExprState - { fesFunctions = mempty, - fesImports = mempty, - fesGlobals = mempty, - fesVars = mempty, - fesArgs = mempty, - fesGenerated = mempty, - fesDataTypes - } - where - fesDataTypes = - M.fromList - [ ( DataName "Maybe", - [ FromExprConstructor "Just" [Pointer], - FromExprConstructor "Nothing" [] - ] - ), - ( DataName "These", - [ FromExprConstructor "This" [Pointer], - FromExprConstructor "That" [Pointer], - FromExprConstructor "These" [Pointer, Pointer] - ] - ) - ] - spec :: Spec spec = do describe "FromWasmSpec" $ do diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 973657b3..25d517cb 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -373,7 +373,7 @@ spec = do ), ( joinLines [ "type Maybe = Just(a) | Nothing", - asTest "case Just((100: Int64)) { Just(a) -> a + 1, Nothing -> 0 }" + asTest "let boxA: Box(Int64) = Box(100); case Just(boxA) { Just(Box(a)) -> a + 1, Nothing -> 0 }" ], Wasm.VI64 101 ) @@ -392,7 +392,7 @@ spec = do )-} ] - describe "From expressions" $ do + fdescribe "From expressions" $ do traverse_ testWithInterpreter testVals describe "Deallocations for expressions" $ do From 646cd57436554fe16f771700023385ea8dadf116 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Sat, 10 Aug 2024 22:32:12 +0100 Subject: [PATCH 08/23] It works but doesn't --- wasm-calc11/src/Calc/Ability/Check.hs | 3 +++ wasm-calc11/test/Test/Ability/AbilitySpec.hs | 3 +++ wasm-calc11/test/Test/Wasm/WasmSpec.hs | 9 +++++---- 3 files changed, 11 insertions(+), 4 deletions(-) diff --git a/wasm-calc11/src/Calc/Ability/Check.hs b/wasm-calc11/src/Calc/Ability/Check.hs index 875795f6..97cfe466 100644 --- a/wasm-calc11/src/Calc/Ability/Check.hs +++ b/wasm-calc11/src/Calc/Ability/Check.hs @@ -156,6 +156,9 @@ abilityExpr (EBox ann a) = do -- we'll need to account for other allocations in future tell (S.singleton $ AllocateMemory ann) EBox ann <$> abilityExpr a +abilityExpr (EConstructor ann constructor as) = do + tell (S.singleton $ AllocateMemory ann) + EConstructor ann constructor <$> traverse abilityExpr as abilityExpr (EApply ann fn args) = do isImport <- asks (S.member fn . aeImportNames) if isImport diff --git a/wasm-calc11/test/Test/Ability/AbilitySpec.hs b/wasm-calc11/test/Test/Ability/AbilitySpec.hs index b03f68f1..3716ab1f 100644 --- a/wasm-calc11/test/Test/Ability/AbilitySpec.hs +++ b/wasm-calc11/test/Test/Ability/AbilitySpec.hs @@ -57,6 +57,9 @@ spec = do ( "test box = { Box(1) }", emptyModuleAbilities {maTests = M.singleton "box" (S.singleton (AllocateMemory ()))} ), + ( "function main() -> Int32 { let _ = Just(1); 100 }", + emptyModuleAbilities { maFunctions = M.singleton "main" (S.singleton (AllocateMemory ())) } + ), ( "import console.log as consoleLog(number: Int64) -> Void", emptyModuleAbilities {maFunctions = mempty} ), diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 25d517cb..b0ce5198 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -4,6 +4,7 @@ module Test.Wasm.WasmSpec (spec) where +import Debug.Trace import Calc.Dependencies import Calc.Linearity (validateModule) import Calc.Module @@ -72,7 +73,7 @@ spec = do describe "Test with interpreter" $ do let asTest str = "export function test() -> Int64 { " <> str <> " }" let testVals = - [ (asTest "42", Wasm.VI64 42), + [ {-(asTest "42", Wasm.VI64 42), (asTest "(1 + 1)", Wasm.VI64 2), (asTest "1 + 2 + 3 + 4 + 5 + 6", Wasm.VI64 21), (asTest "6 * 6", Wasm.VI64 36), @@ -370,7 +371,7 @@ spec = do "}" ], Wasm.VI64 202 - ), + ), -} ( joinLines [ "type Maybe = Just(a) | Nothing", asTest "let boxA: Box(Int64) = Box(100); case Just(boxA) { Just(Box(a)) -> a + 1, Nothing -> 0 }" @@ -392,7 +393,7 @@ spec = do )-} ] - fdescribe "From expressions" $ do + describe "From expressions" $ do traverse_ testWithInterpreter testVals describe "Deallocations for expressions" $ do @@ -460,7 +461,7 @@ compile input = case FromExpr.fromModule typedMod of Left e -> error (show e) Right wasmMod -> - ToWasm.moduleToWasm (addAllocCount wasmMod) + ToWasm.moduleToWasm (addAllocCount (traceShowId wasmMod)) -- add a `alloccount` function that returns state of allocator addAllocCount :: ToWasm.WasmModule -> ToWasm.WasmModule From 9878b0423b5e5d10de32eeb8a43c3bae8aa2aa76 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Sun, 11 Aug 2024 22:23:44 +0100 Subject: [PATCH 09/23] Nearly ready to work out memory offset, what a chore --- wasm-calc11/src/Calc/Typecheck/Elaborate.hs | 2 +- wasm-calc11/src/Calc/Typecheck/Helpers.hs | 9 +-- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 12 ++-- wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 61 +++++++++++-------- wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs | 22 +++---- .../src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 6 +- .../Calc/Wasm/FromExpr/Patterns/Predicates.hs | 30 ++++----- wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs | 2 +- wasm-calc11/test/Test/Ability/AbilitySpec.hs | 2 +- wasm-calc11/test/Test/Helpers.hs | 49 +++++++++++---- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 4 +- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 6 +- 12 files changed, 111 insertions(+), 94 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Elaborate.hs b/wasm-calc11/src/Calc/Typecheck/Elaborate.hs index 6d968639..bd45c6e4 100644 --- a/wasm-calc11/src/Calc/Typecheck/Elaborate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Elaborate.hs @@ -7,13 +7,13 @@ module Calc.Typecheck.Elaborate ) where -import Calc.Types.Data import Calc.ExprUtils import Calc.Typecheck.Error import Calc.Typecheck.Helpers import Calc.Typecheck.Infer import Calc.Typecheck.Substitute import Calc.Typecheck.Types +import Calc.Types.Data import Calc.Types.Expr import Calc.Types.Function import Calc.Types.Global diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index acbca895..50edad83 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -18,6 +18,7 @@ module Calc.Typecheck.Helpers ) where +import Data.Maybe (mapMaybe) import Calc.Typecheck.Error import Calc.Typecheck.Generalise import Calc.Typecheck.Types @@ -206,11 +207,11 @@ calculateMonomorphisedTypes typeVars fnArgTys argTys fallbacks = do (HM.toList unified) fromTv tv = case M.lookup tv mapped of - Just a -> (tv, a) + Just a -> Just (tv, a) Nothing -> case M.lookup tv fallbacks of - Just a -> (tv, a) - Nothing -> error "could not find" - pure $ fromTv <$> typeVars + Just a -> Just (tv, a) + Nothing -> Nothing + pure $ mapMaybe fromTv typeVars flipMap :: (Hashable v) => HM.HashMap k v -> HM.HashMap v k flipMap = HM.fromList . fmap (\(k, v) -> (v, k)) . HM.toList diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index 5809c762..24f0669f 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -134,14 +134,12 @@ fromMatch expr pats = do -- return type of exprs wasmReturnType <- liftEither $ scalarFromType $ fst $ getOuterAnnotation headExpr - dataTypes <- gets fesDataTypes - -- fold through patterns wasmPatExpr <- foldr ( \(pat, patExpr) wholeExpr -> do preds <- - predicatesFromPattern dataTypes (fst <$> pat) mempty + predicatesFromPattern (fst <$> pat) mempty predExprs <- traverse (predicateToWasm (WVar index)) preds wasmPatExpr <- patternBindings pat patExpr index @@ -201,17 +199,17 @@ fromExpr (EConstructor (ty, _) constructor args) = do let allItems = zip [1 ..] args tupleLength <- memorySizeForType ty let allocate = WAllocate (fromIntegral tupleLength) - offsetList <- getOffsetListForConstructor ty constructor + offsetList <- getOffsetListForConstructor ty constructor - wasmItems <- traverse + wasmItems <- + traverse ( \(i, item) -> (,,) (offsetList !! i) <$> liftEither (scalarFromType (fst $ getOuterAnnotation item)) <*> fromExpr item ) allItems - pure $ WSet index allocate ((0,I8,constructorNumber) : wasmItems) - + pure $ WSet index allocate ((0, I8, constructorNumber) : wasmItems) fromExpr (EBlock (_, Just _) _) = do error "found drops on block" fromExpr (EBlock _ expr) = do diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index 42b4faa9..d927d108 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -5,6 +5,7 @@ module Calc.Wasm.FromExpr.Helpers ( getAbilitiesForFunction, scalarFromType, + lookupDataType, addLocal, lookupGlobal, lookupIdent, @@ -17,12 +18,13 @@ module Calc.Wasm.FromExpr.Helpers monomorphiseTypes, fromPrim, getOffsetList, - getOffsetListForConstructor, + getOffsetListForConstructor, boxed, memorySizeForType, ) where +import Debug.Trace import Calc.ExprUtils import Calc.Typecheck ( TypecheckEnv (..), @@ -264,23 +266,34 @@ getOffsetList (TContainer _ items) = scanl (\offset item -> offset + offsetForType item) 0 (NE.toList items) getOffsetList _ = [] --- right now, we assume that each polymorphic value inside a type is a Pointer --- type -getOffsetListForConstructor :: (MonadError FromWasmError m, MonadState FromExprState m) => - Type ann -> Constructor -> m [Natural] -getOffsetListForConstructor (TConstructor _ dataTypeName _items) constructor = do +lookupDataType :: (MonadState FromExprState m) => DataName -> m (Data ()) +lookupDataType dataTypeName = do maybeDataType <- gets (M.lookup dataTypeName . fesDataTypes) - dt <- case maybeDataType of + case maybeDataType of Just dt -> pure dt - Nothing -> error $ "oh fuck couldn't find " <> show constructor - let tys = lookupConstructor dt constructor - pure $ scanl (\offset item -> offset + memorySize item) (memorySize I8) tys -getOffsetListForConstructor _ _ = pure [] + Nothing -> error $ "oh fuck couldn't find " <> show dataTypeName -lookupConstructor :: [FromExprConstructor] -> Constructor -> [WasmType] -lookupConstructor (FromExprConstructor constructorA tys : rest) constructor - = if constructor == constructorA then tys else lookupConstructor rest constructor -lookupConstructor [] _ = error "sdfsdf" +getOffsetListForConstructor :: + (MonadError FromWasmError m, MonadState FromExprState m) => + Type ann -> + Constructor -> + m [Natural] +getOffsetListForConstructor (TConstructor _ dataTypeName tyItems) constructor = do + (Data _ dtVars constructors) <- lookupDataType dataTypeName + wasmTys <- case M.lookup constructor constructors of + Just constructorTys -> do + -- for `Just(I32)`, replace `a` in Maybe with I32 + let replacements = monomorphiseTypes dtVars constructorTys (void <$> tyItems ) + + -- now go through `tyItems`, swapping out TVar with `replacements` + -- then finally, run `memorySizeForType` on everything + traceShowM replacements + + _ <- error "Fix me now please" + traverse (liftEither . scalarFromType) constructorTys + Nothing -> error $ "did not find constructor " <> show constructor + pure $ scanl (\offset item -> offset + memorySize item) (memorySize I8) wasmTys +getOffsetListForConstructor _ _ = pure [] -- 1 item is a byte, so i8, so i32 is 4 bytes memorySize :: WasmType -> Natural @@ -315,7 +328,8 @@ offsetForType (TPrim _ TFloat64) = memorySize F64 offsetForType (TPrim _ TBool) = memorySize I32 -offsetForType (TConstructor {}) = error "offsetForType TConstructor" +offsetForType (TConstructor {}) = + memorySize Pointer offsetForType (TPrim _ TVoid) = error "offsetForType TVoid" offsetForType (TContainer _ _) = @@ -345,16 +359,13 @@ memorySizeForType (TPrim _ TBool) = pure $ memorySize I32 memorySizeForType (TPrim _ TVoid) = error "memorySizeForType TVoid" -memorySizeForType (TConstructor _ constructor _) = do - dt <- gets (M.lookup constructor . fesDataTypes) +memorySizeForType (TConstructor _ dataTypeName _) = do + (Data _ _ constructors) <- lookupDataType dataTypeName let discriminator = memorySize I8 - case dt of - Just constructors -> do - let sizeOfConstructor (FromExprConstructor _ tys) = - getSum $ foldMap (Sum . memorySize) tys - let sizes = sizeOfConstructor <$> constructors - pure $ discriminator + maximum sizes - Nothing -> error "fuck" + sizeOfConstructor tys = + getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeForType) tys) + sizes <- traverse sizeOfConstructor (M.elems constructors) + pure $ discriminator + maximum sizes memorySizeForType (TContainer _ as) = getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeForType) (NE.toList as)) memorySizeForType (TFunction {}) = diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs index 176f8e6b..b2fe818e 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs @@ -82,7 +82,7 @@ fromFunction :: M.Map FunctionName FromExprFunc -> M.Map FunctionName FromExprImport -> M.Map Identifier FromExprGlobal -> - M.Map DataName [FromExprConstructor] -> + M.Map DataName (Data ()) -> [WasmFunction] -> Function (Type ann) -> Either FromWasmError ([WasmFunction], WasmFunction) @@ -177,20 +177,12 @@ fromGlobal (Global {glbExpr, glbMutability}) = do wgType <- scalarFromType (getOuterAnnotation glbExpr) pure $ WasmGlobal {wgExpr, wgType, wgMutable} -getDataTypeMap :: [Data ann] -> Either FromWasmError (M.Map DataName [FromExprConstructor]) +getDataTypeMap :: [Data ann] -> M.Map DataName (Data ()) getDataTypeMap = - fmap mconcat - . traverse - ( \(Data {dtName, dtConstructors}) -> - let withConstructor (dtCon, dtConTypes) = do - wasmTypes <- traverse scalarFromType dtConTypes - pure $ - FromExprConstructor - { fecConstructor = dtCon, - fecTypes = wasmTypes - } - in M.singleton dtName <$> (traverse withConstructor $ M.toList dtConstructors) - ) + foldMap + ( \(Data {dtName, dtVars, dtConstructors}) -> + M.singleton dtName $ Data {dtVars, dtName, dtConstructors = (fmap . fmap) void dtConstructors} + ) fromModule :: (Show ann, Ord ann) => @@ -201,7 +193,7 @@ fromModule wholeMod@(Module {mdDataTypes, mdMemory, mdTests, mdGlobals, mdImport importMap <- getImportMap mdImports funcMap <- getFunctionMap mdFunctions globalMap <- getGlobalMap mdGlobals - dataTypeMap <- getDataTypeMap mdDataTypes + let dataTypeMap = getDataTypeMap mdDataTypes wasmGlobals <- traverse fromGlobal mdGlobals diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index 3c1690a5..cfe65329 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -66,7 +66,7 @@ patternToDropPaths (PTuple (ty, drops) a as) addPath = do ( zip [1 ..] (NE.toList as) ) pure (pathsHead <> mconcat pathsTail <> dropContainer) -patternToDropPaths (PConstructor (ty,drops) constructor ps) addPath = do +patternToDropPaths (PConstructor (ty, drops) constructor ps) addPath = do offsetList <- getOffsetListForConstructor ty constructor let dropContainer = ([addPath (PathFetch ty) | drops == Just DropMe]) @@ -80,8 +80,6 @@ patternToDropPaths (PConstructor (ty,drops) constructor ps) addPath = do pure (mconcat paths <> dropContainer) - - patternToPaths :: (MonadError FromWasmError m, MonadState FromExprState m) => Pattern (Type ann) -> @@ -119,8 +117,6 @@ patternToPaths (PConstructor ty constructor ps) addPath = do pure (mconcat paths) - - -- | given a path, create AST for fetching it fromPath :: (MonadError FromWasmError m) => Natural -> Path ann -> m WasmExpr fromPath wholeExprIndex (PathFetch _ty) = diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index 0966ab23..f3a37713 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -5,7 +5,6 @@ module Calc.Wasm.FromExpr.Patterns.Predicates where import Calc.ExprUtils import Calc.TypeUtils -import Calc.Types.DataName import Calc.Types.Op import Calc.Types.Pattern import Calc.Types.Prim @@ -16,7 +15,6 @@ import Calc.Wasm.ToWasm.Types import Control.Monad.Except import Control.Monad.State import qualified Data.List.NonEmpty as NE -import qualified Data.Map.Strict as M import GHC.Natural data Predicate ann = Equals [(Type ann, Natural)] (Type ann) Prim @@ -27,35 +25,33 @@ predicatesFromPattern :: ( MonadState FromExprState m, MonadError FromWasmError m ) => - M.Map DataName [FromExprConstructor] -> Pattern (Type ann) -> [(Type ann, Natural)] -> m [Predicate ann] -predicatesFromPattern _ (PWildcard {}) _ = pure mempty -predicatesFromPattern _ (PLiteral ty prim) path = pure [Equals path ty prim] -predicatesFromPattern _ (PVar {}) _ = pure mempty -predicatesFromPattern dataTypes (PBox _ inner) path = - predicatesFromPattern dataTypes inner (path <> [(getOuterPatternAnnotation inner, 0)]) -predicatesFromPattern dataTypes (PTuple ty p ps) path = do +predicatesFromPattern (PWildcard {}) _ = pure mempty +predicatesFromPattern (PLiteral ty prim) path = pure [Equals path ty prim] +predicatesFromPattern (PVar {}) _ = pure mempty +predicatesFromPattern (PBox _ inner) path = + predicatesFromPattern inner (path <> [(getOuterPatternAnnotation inner, 0)]) +predicatesFromPattern (PTuple ty p ps) path = do let allPs = zip (p : NE.toList ps) [0 ..] let offsetList = getOffsetList ty mconcat <$> traverse ( \(pat, index) -> predicatesFromPattern - dataTypes pat (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) ) allPs -predicatesFromPattern _dataTypes (PConstructor ty _constructor _) path = +predicatesFromPattern (PConstructor ty _constructor _) path = do -- what - let _typeName = case ty of - TConstructor _ tn _ -> tn - _ -> error "should be type" - -- wrong but yolo - constructorValue = 1 - in pure $ [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] + _dt <- case ty of + TConstructor _ dataTypeName _ -> lookupDataType dataTypeName + _ -> error "should be type" + -- wrong but yolo + let constructorValue = 0 + pure $ [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] -- | turn a single `Predicate` into a `WasmExpr` for that predicate, that -- should return a boolean diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs index 7f4fc9b3..65b41b80 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Types.hs @@ -25,7 +25,7 @@ data FromExprState = FromExprState fesVars :: [(Maybe Identifier, WasmType)], fesArgs :: [(Identifier, WasmType)], fesGenerated :: [WasmFunction], - fesDataTypes :: M.Map DataName [FromExprConstructor] + fesDataTypes :: M.Map DataName (Data ()) } deriving stock (Eq, Ord, Show) diff --git a/wasm-calc11/test/Test/Ability/AbilitySpec.hs b/wasm-calc11/test/Test/Ability/AbilitySpec.hs index 3716ab1f..10772222 100644 --- a/wasm-calc11/test/Test/Ability/AbilitySpec.hs +++ b/wasm-calc11/test/Test/Ability/AbilitySpec.hs @@ -58,7 +58,7 @@ spec = do emptyModuleAbilities {maTests = M.singleton "box" (S.singleton (AllocateMemory ()))} ), ( "function main() -> Int32 { let _ = Just(1); 100 }", - emptyModuleAbilities { maFunctions = M.singleton "main" (S.singleton (AllocateMemory ())) } + emptyModuleAbilities {maFunctions = M.singleton "main" (S.singleton (AllocateMemory ()))} ), ( "import console.log as consoleLog(number: Int64) -> Void", emptyModuleAbilities {maFunctions = mempty} diff --git a/wasm-calc11/test/Test/Helpers.hs b/wasm-calc11/test/Test/Helpers.hs index 272541a4..f8c07bf1 100644 --- a/wasm-calc11/test/Test/Helpers.hs +++ b/wasm-calc11/test/Test/Helpers.hs @@ -1,6 +1,7 @@ {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} - {-# LANGUAGE NamedFieldPuns #-} + module Test.Helpers ( joinLines, int, @@ -20,15 +21,15 @@ module Test.Helpers patTuple, patInt, patBool, - patVar,exprState + patVar, + exprState, ) where -import qualified Data.Map.Strict as M -import Calc.Wasm.FromExpr.Types -import Calc.Wasm.ToWasm.Types import Calc +import Calc.Wasm.FromExpr.Types import qualified Data.List.NonEmpty as NE +import qualified Data.Map.Strict as M import Data.String import qualified Data.Text as T import Data.Word @@ -112,15 +113,37 @@ exprState = fesDataTypes = M.fromList [ ( DataName "Maybe", - [ FromExprConstructor "Just" [Pointer], - FromExprConstructor "Nothing" [] - ] + Data + { dtName = DataName "Maybe", + dtVars = ["a"], + dtConstructors = + M.fromList + [ ("Nothing", []), + ("Just", [TVar mempty "a"]) + ] + } + ), + ( DataName "Either", + Data + { dtName = DataName "Either", + dtVars = ["e", "a"], + dtConstructors = + M.fromList + [ ("Left", [TVar mempty "e"]), + ("Right", [TVar mempty "a"]) + ] + } ), ( DataName "These", - [ FromExprConstructor "This" [Pointer], - FromExprConstructor "That" [Pointer], - FromExprConstructor "These" [Pointer, Pointer] - ] + Data + { dtName = DataName "These", + dtVars = ["a", "b"], + dtConstructors = + M.fromList + [ ("This", [TVar mempty "a"]), + ("That", [TVar mempty "b"]), + ("These", [TVar mempty "a", TVar mempty "b"]) + ] + } ) ] - diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index 4f0aaefa..c4d7eae7 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -42,11 +42,11 @@ spec = do describe "getOffsetListForConstructor" $ do it "Construct with single item" $ do flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "Maybe(Int8)") "Just") - `shouldBe` Right [1, 5] + `shouldBe` Right [1, 2] it "Construct with two items" $ do flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8,Int64)") "These") - `shouldBe` Right [1, 5, 9] + `shouldBe` Right [1, 2, 6] describe "calculateMonomorphisedTypes" $ do it "Ints" $ do diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index b0ce5198..b25e8970 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -4,7 +4,6 @@ module Test.Wasm.WasmSpec (spec) where -import Debug.Trace import Calc.Dependencies import Calc.Linearity (validateModule) import Calc.Module @@ -21,6 +20,7 @@ import Data.FileEmbed import Data.Foldable (traverse_) import Data.Hashable (hash) import qualified Data.Text as T +import Debug.Trace import qualified Language.Wasm.Interpreter as Wasm import qualified Language.Wasm.Structure as Wasm import System.IO.Temp @@ -374,7 +374,7 @@ spec = do ), -} ( joinLines [ "type Maybe = Just(a) | Nothing", - asTest "let boxA: Box(Int64) = Box(100); case Just(boxA) { Just(Box(a)) -> a + 1, Nothing -> 0 }" + asTest "let a: Int64 = 100; case Just(a) { Just(a) -> a + 1, Nothing -> 0 }" ], Wasm.VI64 101 ) @@ -393,7 +393,7 @@ spec = do )-} ] - describe "From expressions" $ do + fdescribe "From expressions" $ do traverse_ testWithInterpreter testVals describe "Deallocations for expressions" $ do From 4ccc6628eeaa91c8b3651f04552718bd20b213d6 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Mon, 12 Aug 2024 13:10:22 +0100 Subject: [PATCH 10/23] A broken case --- wasm-calc11/src/Calc/Parser/Expr.hs | 2 +- .../src/Calc/Typecheck/Error/TypeError.hs | 22 ++++++++++++ wasm-calc11/src/Calc/Typecheck/Helpers.hs | 24 +++++++------ wasm-calc11/src/Calc/Typecheck/Infer.hs | 4 +-- wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs | 7 ++-- wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 35 ++++++++++++++----- .../src/Calc/Wasm/FromExpr/Patterns/Paths.hs | 4 +-- .../Calc/Wasm/FromExpr/Patterns/Predicates.hs | 33 ++++++++++++----- wasm-calc11/test/Test/Parser/ParserSpec.hs | 1 + .../test/Test/Typecheck/TypecheckSpec.hs | 6 ++++ wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 6 +++- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 26 ++++++++++---- 12 files changed, 127 insertions(+), 43 deletions(-) diff --git a/wasm-calc11/src/Calc/Parser/Expr.hs b/wasm-calc11/src/Calc/Parser/Expr.hs index 69b496f2..03143f8a 100644 --- a/wasm-calc11/src/Calc/Parser/Expr.hs +++ b/wasm-calc11/src/Calc/Parser/Expr.hs @@ -201,7 +201,7 @@ constructorParser = stringLiteral ")" pure args in label "constructor" $ addLocation $ do - constructor <- constructorParserInternal + constructor <- myLexeme constructorParserInternal args <- try argsParser <|> pure mempty pure $ EConstructor mempty constructor args diff --git a/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs b/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs index 9b8517d5..1beb0f11 100644 --- a/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs +++ b/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs @@ -40,6 +40,7 @@ data TypeError ann | ManualMemoryAccessOutsideLimit ann Natural Natural -- limit, value | CantSetConstant ann Identifier | ConstructorNotFound ann Constructor + | UnknownGenericInConstructor ann Constructor TypeVar | PatternMatchError (PatternMatchError ann) deriving stock (Eq, Ord, Show) @@ -111,6 +112,27 @@ typeErrorDiagnostic input e = ] ) [] + (UnknownGenericInConstructor ann constructor var) -> + Diag.addReport diag $ + Diag.Err + Nothing + ( prettyPrint $ "Constructor " <> PP.pretty constructor <> " does not provide a type for var" <> PP.pretty var + ) + ( catMaybes + [ (,) + <$> positionFromAnnotation + filename + input + ann + <*> pure + ( Diag.This + ( prettyPrint + "Perhaps add a type annotation so that we know what should go here?" + ) + ) + ] + ) + [] (CantSetConstant ann ident) -> Diag.addReport diag $ Diag.Err diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index 50edad83..2a5f984f 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -18,7 +18,6 @@ module Calc.Typecheck.Helpers ) where -import Data.Maybe (mapMaybe) import Calc.Typecheck.Error import Calc.Typecheck.Generalise import Calc.Typecheck.Types @@ -33,6 +32,7 @@ import qualified Data.HashMap.Strict as HM import Data.Hashable import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as M +import Data.Maybe (mapMaybe) import qualified Data.Set as S -- | run a typechecking computation, discarding any Writer output @@ -146,7 +146,7 @@ identifiersFromPattern (PConstructor ann constructor ps) (TConstructor _ _ tyArg (_dataTypeName, dataTypeVars, dataTypeArgs) <- lookupConstructor ann constructor - let filtered = matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs + filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs allIdents <- zipWithM identifiersFromPattern ps filtered pure $ mconcat allIdents @@ -228,15 +228,17 @@ lookupConstructor ann constructor = do Nothing -> throwError $ ConstructorNotFound ann constructor -matchConstructorTypesToArgs :: [TypeVar] -> [Type ann] -> [Type ann] -> [Type ann] -matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs = +-- given the arguments to a constructor, match them to the data types's vars +-- if we cannot find one (ie, because user has typed `Nothing` so we don't know +-- the `a` in `Maybe`, explode, expecting a type annotation +matchConstructorTypesToArgs :: Constructor -> [TypeVar] -> [Type ann] -> [Type ann] -> TypecheckM ann [Type ann] +matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs = let pairs = M.fromList (zip dataTypeVars tyArgs) - filteredTyArgs = + in traverse ( \case - TVar _ var -> case M.lookup var pairs of - Just ty -> ty - Nothing -> error "cannot find" - otherTy -> otherTy + TVar ann var -> case M.lookup var pairs of + Just ty -> pure ty + Nothing -> throwError (UnknownGenericInConstructor ann constructor var) + otherTy -> pure otherTy ) - <$> dataTypeArgs - in filteredTyArgs + dataTypeArgs diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 065e3e47..d5847765 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -352,7 +352,7 @@ checkPattern (TConstructor _ tyDataName tyArgs) (PConstructor ann constructor pa unless (tyDataName == dataTypeName) $ error "wrong" - let filtered = matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs + filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs typedArgs <- zipWithM checkPattern filtered patArgs @@ -405,7 +405,7 @@ checkConstructor maybeTy ann constructor args = do Just (tyCons, tyArgs) -> do unless (tyCons == dataTypeName) $ error "wrong" - let filtered = matchConstructorTypesToArgs dataTypeVars tyArgs dataTypeArgs + filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs typedArgs <- zipWithM check filtered args pure ( typedArgs, diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs index 24f0669f..37be9bb8 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Expr.hs @@ -192,11 +192,12 @@ fromExpr (EPrim (ty, _) prim) = fromExpr (EMatch _ expr pats) = fromMatch expr pats fromExpr (EConstructor (ty, _) constructor args) = do - let constructorNumber = WPrim (WPInt32 0) - -- TODO: add the constructor number in + -- what is the underlying discriminator value? + constructorNumber <- WPrim . WPInt32 . fromIntegral <$> getConstructorNumber ty constructor + wasmType <- liftEither $ scalarFromType ty index <- addLocal Nothing wasmType - let allItems = zip [1 ..] args + let allItems = zip [0 ..] args tupleLength <- memorySizeForType ty let allocate = WAllocate (fromIntegral tupleLength) offsetList <- getOffsetListForConstructor ty constructor diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index d927d108..c6626a66 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -21,10 +21,10 @@ module Calc.Wasm.FromExpr.Helpers getOffsetListForConstructor, boxed, memorySizeForType, + getConstructorNumber, ) where -import Debug.Trace import Calc.ExprUtils import Calc.Typecheck ( TypecheckEnv (..), @@ -282,16 +282,23 @@ getOffsetListForConstructor (TConstructor _ dataTypeName tyItems) constructor = (Data _ dtVars constructors) <- lookupDataType dataTypeName wasmTys <- case M.lookup constructor constructors of Just constructorTys -> do - -- for `Just(I32)`, replace `a` in Maybe with I32 - let replacements = monomorphiseTypes dtVars constructorTys (void <$> tyItems ) - + -- for `Just(I32)`, replace `a` in Maybe with I32 + let replacements = M.fromList $ monomorphiseTypes dtVars constructorTys (void <$> tyItems) + -- now go through `tyItems`, swapping out TVar with `replacements` -- then finally, run `memorySizeForType` on everything - traceShowM replacements - - _ <- error "Fix me now please" - traverse (liftEither . scalarFromType) constructorTys - Nothing -> error $ "did not find constructor " <> show constructor + + -- now we've learned about the types, swap the polymorphic ones for the + -- monomorphised ones + let toWasm ty = case ty of + TVar _ identifier -> case M.lookup identifier replacements of + Just a -> liftEither (scalarFromType a) + Nothing -> pure Pointer -- polymorphic values become "Pointer", this seems boringly safe + other -> liftEither (scalarFromType other) + + traverse toWasm constructorTys + Nothing -> + error $ "did not find constructor " <> show constructor pure $ scanl (\offset item -> offset + memorySize item) (memorySize I8) wasmTys getOffsetListForConstructor _ _ = pure [] @@ -374,3 +381,13 @@ memorySizeForType (TVar _ _) = pure $ memorySize Pointer memorySizeForType (TUnificationVar _ _) = error "memorySizeForType TUnificationVar" + +getConstructorNumber :: (MonadState FromExprState m) => Type ann -> Constructor -> m Natural +getConstructorNumber ty constructor = do + (Data _ _ constructors) <- case ty of + TConstructor _ dataTypeName _ -> lookupDataType dataTypeName + _ -> error $ "expected TConstructor, got " <> show (void ty) + let numberMap = M.fromList $ zip (M.keys constructors) [0 ..] + case M.lookup constructor numberMap of + Just nat -> pure nat + Nothing -> error $ "constructor not found " <> show constructor diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs index cfe65329..06537bfd 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Paths.hs @@ -76,7 +76,7 @@ patternToDropPaths (PConstructor (ty, drops) constructor ps) addPath = do let innerTy = fst (getOuterPatternAnnotation innerPat) in patternToDropPaths innerPat (PathSelect innerTy (offsetList !! index) . addPath) ) - (zip [1 ..] ps) + (zip [0 ..] ps) pure (mconcat paths <> dropContainer) @@ -113,7 +113,7 @@ patternToPaths (PConstructor ty constructor ps) addPath = do let innerTy = getOuterPatternAnnotation pat in patternToPaths pat (PathSelect innerTy (offsetList !! index) . addPath) ) - (zip [1 ..] ps) + (zip [0 ..] ps) pure (mconcat paths) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs index f3a37713..d5b67716 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Patterns/Predicates.hs @@ -44,14 +44,31 @@ predicatesFromPattern (PTuple ty p ps) path = do (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) ) allPs -predicatesFromPattern (PConstructor ty _constructor _) path = do - -- what - _dt <- case ty of - TConstructor _ dataTypeName _ -> lookupDataType dataTypeName - _ -> error "should be type" - -- wrong but yolo - let constructorValue = 0 - pure $ [Equals path (TPrim (getOuterTypeAnnotation ty) TInt32) (PIntLit constructorValue)] +predicatesFromPattern (PConstructor ty constructor ps) path = do + constructorValue <- getConstructorNumber ty constructor + -- make sure we've got the correct constructor + let discriminatorType = TPrim (getOuterTypeAnnotation ty) TInt8 + let discriminatorPath = path <> [(discriminatorType, 0)] + let discriminatorMatch = + Equals + discriminatorPath + discriminatorType + (PIntLit (fromIntegral constructorValue)) + + offsetList <- getOffsetListForConstructor ty constructor + + -- make sure any nested patterns work too + let indexedPs = zip ps [0 ..] + predicates <- + mconcat + <$> traverse + ( \(pat, index) -> + predicatesFromPattern + pat + (path <> [(getOuterPatternAnnotation pat, offsetList !! index)]) + ) + indexedPs + pure $ discriminatorMatch : predicates -- | turn a single `Predicate` into a `WasmExpr` for that predicate, that -- should return a boolean diff --git a/wasm-calc11/test/Test/Parser/ParserSpec.hs b/wasm-calc11/test/Test/Parser/ParserSpec.hs index 7f0cb187..7c7bbdc9 100644 --- a/wasm-calc11/test/Test/Parser/ParserSpec.hs +++ b/wasm-calc11/test/Test/Parser/ParserSpec.hs @@ -455,6 +455,7 @@ spec = do (bool False) ), ("Red", EConstructor () "Red" []), + ("Nothing ", EConstructor () "Nothing" []), ("Some(1)", EConstructor () "Some" [int 1]), ( "case a { (1,2) -> 0, (a,b) -> a + b }", EMatch diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index 3ce5d2e2..4da7f7ab 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -159,6 +159,12 @@ spec = do ], tyConstructor "Maybe" [tyInt32] ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + "function main() -> Maybe(Int32) { Nothing }" + ], + tyConstructor "Maybe" [tyInt32] + ), ( joinLines [ "type Either = Left(e) | Right(a)", "function main() -> Either(Boolean,Int32) { Right(100) }" diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index c4d7eae7..0004fbe9 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -46,7 +46,11 @@ spec = do it "Construct with two items" $ do flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8,Int64)") "These") - `shouldBe` Right [1, 2, 6] + `shouldBe` Right [1, 2, 10] + + it "Construct with two items" $ do + flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8, Int64)") "This") + `shouldBe` Right [1, 2] describe "calculateMonomorphisedTypes" $ do it "Ints" $ do diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index b25e8970..7ddfb347 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -20,7 +20,6 @@ import Data.FileEmbed import Data.Foldable (traverse_) import Data.Hashable (hash) import qualified Data.Text as T -import Debug.Trace import qualified Language.Wasm.Interpreter as Wasm import qualified Language.Wasm.Structure as Wasm import System.IO.Temp @@ -73,7 +72,7 @@ spec = do describe "Test with interpreter" $ do let asTest str = "export function test() -> Int64 { " <> str <> " }" let testVals = - [ {-(asTest "42", Wasm.VI64 42), + [ (asTest "42", Wasm.VI64 42), (asTest "(1 + 1)", Wasm.VI64 2), (asTest "1 + 2 + 3 + 4 + 5 + 6", Wasm.VI64 21), (asTest "6 * 6", Wasm.VI64 36), @@ -371,13 +370,28 @@ spec = do "}" ], Wasm.VI64 202 - ), -} + ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + asTest "case (Nothing:Maybe(Int64)) { Just(a) -> a + 1, Nothing -> 0 }" + ], + Wasm.VI64 0 -- quite disappointing we can't infer this from use, really we need to go all-in on HM to make all of this a bit friendlier + ), ( joinLines [ "type Maybe = Just(a) | Nothing", - asTest "let a: Int64 = 100; case Just(a) { Just(a) -> a + 1, Nothing -> 0 }" + asTest "case Just((100: Int64)) { Just(a) -> a + 1, Nothing -> 0 }" ], Wasm.VI64 101 + ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", + asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" + ], + Wasm.VI64 100 ) + + {-, -- absolutely baffled why `allocated` is not dropped here when we -- generate what looks like the correct IR @@ -393,7 +407,7 @@ spec = do )-} ] - fdescribe "From expressions" $ do + describe "From expressions" $ do traverse_ testWithInterpreter testVals describe "Deallocations for expressions" $ do @@ -461,7 +475,7 @@ compile input = case FromExpr.fromModule typedMod of Left e -> error (show e) Right wasmMod -> - ToWasm.moduleToWasm (addAllocCount (traceShowId wasmMod)) + ToWasm.moduleToWasm (addAllocCount wasmMod) -- add a `alloccount` function that returns state of allocator addAllocCount :: ToWasm.WasmModule -> ToWasm.WasmModule From 7d86d7bf365802a3c5fc6611835069462fd0fa5f Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Mon, 12 Aug 2024 14:10:21 +0100 Subject: [PATCH 11/23] More tests --- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 7ddfb347..ccc27be2 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -383,6 +383,24 @@ spec = do ], Wasm.VI64 101 ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + asTest "case Just(Box((100: Int64))) { Just(Box(a)) -> a + 1, Nothing -> 0 }" + ], + Wasm.VI64 101 + ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + asTest "case Just(Just(Box((100: Int64)))) { Just(Just(Box(a))) -> a + 1, Nothing -> 0 }" + ], + Wasm.VI64 101 + ), + + + ( joinLines + [ "type Colour = Red | Green | Blue", + asTest "case Blue { Red -> 1, Green -> 2, Blue -> 3 }"], + Wasm.VI64 3), ( joinLines [ "type Maybe = Just(a) | Nothing", "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", From a66196dbc1bbc812811492994cb15fe5d243a0db Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Mon, 12 Aug 2024 15:07:28 +0100 Subject: [PATCH 12/23] Well shit --- lsp-log.txt | 1889 ++++++++++++++++++++ wasm-calc11/demo/draw.calc | 26 +- wasm-calc11/src/Calc/Parser/Pattern.hs | 22 +- wasm-calc11/src/Calc/Types/Expr.hs | 16 +- wasm-calc11/src/Calc/Types/Pattern.hs | 3 +- wasm-calc11/src/Calc/Types/Type.hs | 2 + wasm-calc11/test/Test/Parser/ParserSpec.hs | 5 +- wasm-calc11/test/Test/Wasm/WasmSpec.hs | 57 +- wasm-calc11/test/static/datatypes.calc | 18 +- 9 files changed, 1990 insertions(+), 48 deletions(-) create mode 100644 lsp-log.txt diff --git a/lsp-log.txt b/lsp-log.txt new file mode 100644 index 00000000..f9cd503d --- /dev/null +++ b/lsp-log.txt @@ -0,0 +1,1889 @@ + +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} +workspaceFolders [] +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: (Int64,Int64,Int64)\n) -> (Int64,Int64,Int64) { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = color; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n (r,g,b)\n}\n\nfunction cycle(color: (Int64,Int64,Int64)) -> (Int64,\nInt64,\nInt64) { let (r,g,b) = color; (g,b,r)}\n\nfunction initial(index: Int64) -> (Int64,Int64,Int64) { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n (r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 1 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 2 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 3 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 4 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 5 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 6 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 7 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 8 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 9 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 10 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 11 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 12 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 13 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 14 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 15 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 16 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 17 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 18 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 19 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 20 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 21 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 22 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 23 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 24 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 25 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 26 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 27 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 28 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 29 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 30 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 31 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 32 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 33 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 34 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 35 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 36 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 37 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 38 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 39 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 40 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 41 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 42 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 43 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 44 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 45 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 46 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 47 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 48 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 49 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 50 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 51 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 52 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 53 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 54 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 55 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 56 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 57 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 58 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 59 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 60 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 61 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 62 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 63 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 64 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 65 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 66 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 67 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 68 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 69 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 70 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 71 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 72 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 73 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 74 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 75 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 76 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 77 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 78 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 79 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 80 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 81 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 82 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 83 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 84 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 85 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 86 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 87 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 88 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 89 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 90 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 91 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 92 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 93 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 94 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 95 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 96 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 97 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 98 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 99 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 100 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 101 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 102 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 103 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 104 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 105 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 106 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 107 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 108 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 109 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 110 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 111 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 112 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 113 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 114 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 115 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 116 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 117 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 118 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 119 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 120 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 121 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 122 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 123 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 124 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 125 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 126 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 127 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 128 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 129 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 130 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 131 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 132 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 133 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 134 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 135 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 136 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 137 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 138 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 139 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 140 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 141 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 142 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 143 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 144 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 145 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 146 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 147 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 148 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 149 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 150 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 151 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 152 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 153 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 154 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 155 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 156 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 157 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 158 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 159 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 160 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 161 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 162 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 163 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 164 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 165 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 166 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 167 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 168 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 169 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 170 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 171 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 172 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 173 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 174 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 175 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 176 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 177 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 178 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 179 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 180 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 181 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 182 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 183 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 184 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 185 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 186 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 187 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 188 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 189 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 190 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 191 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 192 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 193 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 194 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 195 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 196 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 197 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 198 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 199 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 200 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 201 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 202 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 203 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 204 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 205 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 206 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 207 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 208 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 209 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 210 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 211 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 212 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 213 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 214 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 215 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 216 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 217 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 218 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 219 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 220 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 221 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 222 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 223 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 224 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 225 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 226 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 227 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 228 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 229 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 230 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 231 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 232 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 233 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 234 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 235 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 236 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 237 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 238 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 239 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 240 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 241 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 242 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 243 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 244 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 245 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 246 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 247 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 248 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 249 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 250 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 251 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 252 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 253 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 254 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 255 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 256 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 257 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 258 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 259 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 260 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 261 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 262 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 263 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 264 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 265 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 266 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 267 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 268 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 269 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 270 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 271 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 272 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 273 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 274 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 275 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 276 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 277 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 278 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 279 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 280 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 281 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 282 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 283 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 284 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 285 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 286 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 287 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 288 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 289 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 290 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 291 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 292 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 293 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 294 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 295 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 296 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 297 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 298 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 299 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 300 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 301 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 302 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 303 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 304 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 305 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 306 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 307 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 308 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 309 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 310 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 311 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 312 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 313 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 314 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 315 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 316 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 317 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 318 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 319 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 320 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 321 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 322 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 323 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 324 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color()\n) -> Color() { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color()) -> Color() { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} +workspaceFolders [] +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color()\n) -> Color() { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color()) -> Color() { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 1 +Found the virtual file: 1 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 2 +Found the virtual file: 2 +textDocumentDidSave +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} +workspaceFolders [] +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color() { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color()) -> Color() { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}\n"}}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 1 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 2 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} +workspaceFolders [] +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "type Colour = Blue | Green | Red\n\ntype Maybe = Just(a) | Nothing\n\ntype Either = Left(e) | Right(a)\n\ntype These = That(b) | These(a, b) | This(a)\n\ntype Expr = EBool(ann, Boolean) | EInt(ann, Int32)"}}} +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 1 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 2 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 3 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 4 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 5 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 6 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 7 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 8 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 9 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 10 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 11 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 12 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 13 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 14 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 15 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 16 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 17 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 18 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 19 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 20 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 21 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 22 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 23 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 24 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 25 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 26 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 27 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 28 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 29 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 30 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 31 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 32 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 33 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 34 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 35 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 36 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 37 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 38 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 39 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 40 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 41 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 42 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 43 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 44 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 45 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 46 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 47 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 48 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 49 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 50 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 51 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 52 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 53 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 54 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 55 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 56 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 57 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 58 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 59 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 60 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 61 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 62 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 63 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 64 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 65 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 66 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 67 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 68 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 69 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 70 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 71 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 72 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 73 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 74 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 75 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 76 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 77 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 78 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 79 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 80 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 81 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 82 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 83 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 84 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 85 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 86 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 87 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 88 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 89 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 90 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 91 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 92 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 93 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 94 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 95 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 96 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 97 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 98 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 99 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 100 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 101 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 102 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 103 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 104 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 105 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 106 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 107 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 108 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 109 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 110 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 111 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 112 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 113 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 114 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 115 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 116 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 117 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 118 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 119 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 120 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 121 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 122 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 123 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 124 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 125 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 126 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 127 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 128 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 129 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 130 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 131 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 132 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 133 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 134 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 135 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 136 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 137 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 138 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 139 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 140 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 141 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 142 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 143 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 144 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 145 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 146 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 147 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 148 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 149 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 150 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 151 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 152 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 153 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 154 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 155 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 156 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 157 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 158 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 159 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 160 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 161 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 162 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 163 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 164 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 165 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 166 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 167 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 168 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 169 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 170 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 171 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 172 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 173 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 174 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 175 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 176 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 177 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 178 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 179 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 180 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 181 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 182 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 183 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 184 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 185 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 186 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 187 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 188 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 189 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 190 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 191 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 192 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 193 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 194 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 195 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 196 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 197 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 198 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 199 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 200 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 201 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 202 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 203 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 204 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 205 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 206 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 207 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 208 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 209 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 210 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 211 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 212 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 213 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 214 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 215 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 216 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 217 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 218 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 219 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 220 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 221 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 222 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 223 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 224 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 225 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 226 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 227 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 228 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 229 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 230 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 231 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 232 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 233 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 234 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 235 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 236 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 237 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 238 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 239 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 240 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 241 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 242 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 243 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 244 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 245 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 246 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 247 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 248 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 249 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 250 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 251 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 252 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 253 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 254 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 255 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 256 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 257 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 258 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 259 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 260 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 261 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 262 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 263 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 264 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 265 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 266 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 267 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 268 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 269 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 270 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 271 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 272 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 273 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 274 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 275 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 276 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 277 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 278 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 279 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 280 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 281 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 282 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 283 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 284 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 285 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 286 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 287 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 288 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 289 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 290 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 291 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 292 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 293 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 294 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 295 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 296 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 297 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 298 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 299 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 300 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 301 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 302 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 303 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 304 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 305 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 306 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 307 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 308 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 309 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 310 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 311 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 312 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 313 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 314 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 315 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 316 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 317 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 318 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 319 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 320 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 321 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 322 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 323 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 324 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 325 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 326 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 327 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 328 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 329 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 330 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 331 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 332 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 333 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 334 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 335 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 336 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 337 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 338 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 339 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 340 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 341 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 342 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 343 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 344 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 345 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 346 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 347 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 348 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 349 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 350 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 351 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 352 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 353 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 354 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 355 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 356 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 357 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 358 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 359 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 360 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 361 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 362 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 363 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 364 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 365 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 366 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 367 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 368 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 369 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 370 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 371 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 372 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 373 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 374 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 375 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 376 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 377 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 378 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 379 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 380 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 381 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 382 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 383 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 384 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 385 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 386 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 387 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 388 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 389 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 390 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 391 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 392 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 393 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 394 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 395 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 396 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 397 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 398 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 399 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 400 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 401 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 402 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 403 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 404 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 405 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 406 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 407 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 408 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 409 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 410 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 411 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 412 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 413 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 414 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 415 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 416 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 417 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 418 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 419 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 420 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 421 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 422 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 423 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 424 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 425 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 426 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 427 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 428 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 429 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 430 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 431 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 432 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 433 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 434 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 435 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 436 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 437 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 438 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 439 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 440 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 441 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 442 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 443 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 444 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 445 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 446 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 447 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 448 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 449 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 450 +Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" +Found the virtual file: 451 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 3 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 4 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 5 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 6 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} +workspaceFolders [] +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color) -> Color { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}\n"}}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 1 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 2 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 3 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 4 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 5 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 6 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 7 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 8 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 9 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 10 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 11 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 12 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 13 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 14 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 15 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 16 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 17 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 18 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 19 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 20 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 21 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 22 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 23 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 24 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 25 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 26 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 27 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 28 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 29 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 30 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 31 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 32 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 33 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 34 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 35 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 36 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 37 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 38 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 39 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 40 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 41 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 42 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 43 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 44 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 45 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 46 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 47 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 48 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 49 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 50 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 51 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 52 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 53 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 54 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 55 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 56 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 57 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 58 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 59 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 60 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 61 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 62 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 63 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 64 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 65 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 66 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 67 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 68 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 69 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 70 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 71 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 72 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 73 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 74 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 75 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 76 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 77 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 78 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 79 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 80 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 81 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 82 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 83 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 84 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 85 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 86 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 87 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 88 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 89 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 90 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 91 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 92 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 93 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 94 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 95 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 96 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 97 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 98 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 99 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 100 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 101 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 102 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 103 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 104 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 105 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 106 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 107 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 108 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 109 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 110 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 111 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 112 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 113 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 114 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 115 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 116 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 117 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 118 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 119 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 120 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 121 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 122 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 123 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 124 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 125 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 126 +Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" +Found the virtual file: 127 +textDocumentDidSave +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} +workspaceFolders [] +textDocumentDidOpen +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {\n RGB(r, g, b) -> (r,g,b), \n Greyscale(grey) -> (grey,grey,grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} \ No newline at end of file diff --git a/wasm-calc11/demo/draw.calc b/wasm-calc11/demo/draw.calc index 79e8d7dc..1691698a 100644 --- a/wasm-calc11/demo/draw.calc +++ b/wasm-calc11/demo/draw.calc @@ -1,5 +1,7 @@ global mut index: Int64 = 1 +type Color = Greyscale(Int64) | RGB(Int64, Int64, Int64) + import imports.draw as draw( x: Int64, y: Int64, r: Int64, g: Int64, b: Int64 ) -> Void @@ -17,26 +19,32 @@ function clamp( ) -> Int64 { min(floor, max(ceiling, value))} function drawBounded( - x: Int64, y: Int64, color: (Int64,Int64,Int64) -) -> (Int64,Int64,Int64) { + x: Int64, y: Int64, color: Color +) -> Color { let maxWidth: Int64 = 600; let maxHeight: Int64 = 600; - let (r,g,b) = color; + let (r,g,b) = case color { + RGB(r, g, b) -> (r,g,b), + Greyscale(grey) -> (grey,grey,grey) + }; draw( clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b ); - (r,g,b) + RGB(r, g, b) } -function cycle(color: (Int64,Int64,Int64)) -> (Int64, -Int64, -Int64) { let (r,g,b) = color; (g,b,r)} +function cycle(color: Color) -> Color { + case color { + RGB(r, g, b) -> RGB(g, b, r), + Greyscale(grey) -> Greyscale(grey) + } +} -function initial(index: Int64) -> (Int64,Int64,Int64) { +function initial(index: Int64) -> Color { let r = clamp(0, 255, index * 2); let g = clamp(0, 255, 255 - r); let b = clamp(0, 255, r * 3); - (r,g,b) + RGB(r, g, b) } export function test() -> Void { diff --git a/wasm-calc11/src/Calc/Parser/Pattern.hs b/wasm-calc11/src/Calc/Parser/Pattern.hs index 6051116d..da34f90b 100644 --- a/wasm-calc11/src/Calc/Parser/Pattern.hs +++ b/wasm-calc11/src/Calc/Parser/Pattern.hs @@ -19,12 +19,12 @@ patternParser = label "pattern match" ( orInBrackets - ( try patTupleParser - <|> try patWildcardParser + ( try patWildcardParser + <|> patPrimParser <|> try patVariableParser - <|> patBoxParser + <|> try patBoxParser <|> patConstructorParser - <|> patPrimParser + <|> patTupleParser ) ) @@ -75,16 +75,20 @@ patPrimParser = ---- -argsParser :: Parser [ParserPattern] -argsParser = try someP <|> pure [] - where - someP = some patternParser +patArgsParser :: Parser [ParserPattern] +patArgsParser = + let argsWithBrackets = do + stringLiteral "(" + args <- sepBy1 patternParser (stringLiteral ",") + stringLiteral ")" + pure args + in try argsWithBrackets <|> pure [] patConstructorParser :: Parser ParserPattern patConstructorParser = let parser = do cons <- myLexeme constructorParserInternal - args <- argsParser + args <- patArgsParser pure (cons, args) in withLocation ( \loc (cons, args) -> diff --git a/wasm-calc11/src/Calc/Types/Expr.hs b/wasm-calc11/src/Calc/Types/Expr.hs index a13c080c..39257f3b 100644 --- a/wasm-calc11/src/Calc/Types/Expr.hs +++ b/wasm-calc11/src/Calc/Types/Expr.hs @@ -67,17 +67,23 @@ instance PP.Pretty (Expr ann) where <> ";" <+> PP.line <> PP.pretty rest - pretty (EMatch _ expr _pats) = + pretty (EMatch _ expr pats) = "case" - <+> PP.pretty expr - <+> "{" - <> "}" + <+> PP.pretty expr <+> + "{" <> + PP.group (PP.line <> + indentMulti 2 (PP.cat + (PP.punctuate ", " (prettyPat <$> NE.toList pats))) + <+> PP.line') <> "}" + where + prettyPat (pat,patExpr) = + PP.pretty pat <+> "->" <+> PP.pretty patExpr pretty (EConstructor _ constructor []) = PP.pretty constructor pretty (EConstructor _ constructor args) = PP.pretty constructor <> "(" - <> PP.cat (PP.punctuate "," (PP.pretty <$> args)) + <> PP.cat (PP.punctuate ", " (PP.pretty <$> args)) <> ")" pretty (EInfix _ op a b) = PP.pretty a <+> PP.pretty op <+> PP.pretty b diff --git a/wasm-calc11/src/Calc/Types/Pattern.hs b/wasm-calc11/src/Calc/Types/Pattern.hs index 7da29f64..a6bcd380 100644 --- a/wasm-calc11/src/Calc/Types/Pattern.hs +++ b/wasm-calc11/src/Calc/Types/Pattern.hs @@ -29,5 +29,6 @@ instance PP.Pretty (Pattern ann) where where tupleItems :: a -> NE.NonEmpty a -> [a] tupleItems b bs = b : NE.toList bs + pretty (PConstructor _ constructor []) = PP.pretty constructor pretty (PConstructor _ constructor as) = - PP.pretty constructor <> "(" <> PP.cat (PP.punctuate "," (PP.pretty <$> as)) <> ")" + PP.pretty constructor <> "(" <> PP.cat (PP.punctuate ", " (PP.pretty <$> as)) <> ")" diff --git a/wasm-calc11/src/Calc/Types/Type.hs b/wasm-calc11/src/Calc/Types/Type.hs index fecd61d2..0b8f8694 100644 --- a/wasm-calc11/src/Calc/Types/Type.hs +++ b/wasm-calc11/src/Calc/Types/Type.hs @@ -54,5 +54,7 @@ instance PP.Pretty (Type ann) where "Box(" <> PP.pretty (NE.head as) <> ")" pretty (TContainer _ as) = "(" <> PP.cat (PP.punctuate "," (PP.pretty <$> NE.toList as)) <> ")" + pretty (TConstructor _ dataName []) = + PP.pretty dataName pretty (TConstructor _ dataName vars) = PP.pretty dataName <> "(" <> PP.cat (PP.punctuate "," (PP.pretty <$> vars)) <> ")" diff --git a/wasm-calc11/test/Test/Parser/ParserSpec.hs b/wasm-calc11/test/Test/Parser/ParserSpec.hs index 7c7bbdc9..b34fcd8d 100644 --- a/wasm-calc11/test/Test/Parser/ParserSpec.hs +++ b/wasm-calc11/test/Test/Parser/ParserSpec.hs @@ -393,7 +393,9 @@ spec = do ("a", PVar () "a"), ("Box(_)", PBox () (PWildcard ())), ("1", patInt 1), - ("Just(True)", PConstructor () "Just" [patBool True]) + ("Just(True)", PConstructor () "Just" [patBool True]), + ("These(True,False)", PConstructor () "These" [patBool True, patBool False]), + ("These(1,2)", PConstructor () "These" [patInt 1, patInt 2]) ] traverse_ ( \(str, pat) -> it (T.unpack str) $ do @@ -457,6 +459,7 @@ spec = do ("Red", EConstructor () "Red" []), ("Nothing ", EConstructor () "Nothing" []), ("Some(1)", EConstructor () "Some" [int 1]), + ("These(True,False)", EConstructor () "These" [bool True, bool False]), ( "case a { (1,2) -> 0, (a,b) -> a + b }", EMatch () diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index ccc27be2..05d1940f 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -395,34 +395,47 @@ spec = do ], Wasm.VI64 101 ), - - ( joinLines [ "type Colour = Red | Green | Blue", - asTest "case Blue { Red -> 1, Green -> 2, Blue -> 3 }"], - Wasm.VI64 3), + asTest "case Blue { Red -> 1, Green -> 2, Blue -> 3 }" + ], + Wasm.VI64 3 + ), ( joinLines - [ "type Maybe = Just(a) | Nothing", - "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", - asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" + [ "type These = This(a) | That(b) | These(a,b)", + "export function test() -> Boolean { case These(True,False) { This(a) -> a , That(b) -> b , These(a,b) -> a && b } }" ], - Wasm.VI64 100 - ) + Wasm.VI32 0 + ) {-, + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + asTest "let value: List(Int64) = Cons((1:Int64),Cons((2:Int64),Nil)); case value { Cons(a,Cons(b,Nil)) -> a + b, _ -> 0 }" + ], + Wasm.VI64 3 + ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", + asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" + ], + Wasm.VI64 100 + )- + -} - {-, - -- absolutely baffled why `allocated` is not dropped here when we - -- generate what looks like the correct IR - ( asTest $ - joinLines - [ "let pair = ((1:Int64),False);", - "case pair { ", - "(a,False) -> { let allocated = Box((100: Int64)); let Box(b) = allocated; b + a },", - "_ -> 400 ", - "}" - ], - Wasm.VI64 101 - )-} + {-, + -- absolutely baffled why `allocated` is not dropped here when we + -- generate what looks like the correct IR + ( asTest $ + joinLines + [ "let pair = ((1:Int64),False);", + "case pair { ", + "(a,False) -> { let allocated = Box((100: Int64)); let Box(b) = allocated; b + a },", + "_ -> 400 ", + "}" + ], + Wasm.VI64 101 + )-} ] describe "From expressions" $ do diff --git a/wasm-calc11/test/static/datatypes.calc b/wasm-calc11/test/static/datatypes.calc index aed29c82..25a66219 100644 --- a/wasm-calc11/test/static/datatypes.calc +++ b/wasm-calc11/test/static/datatypes.calc @@ -6,4 +6,20 @@ type Either = Left(e) | Right(a) type These = That(b) | These(a, b) | This(a) -type Expr = EBool(ann, Boolean) | EInt(ann, Int32) \ No newline at end of file +type Expr = EBool(ann, Boolean) | EInt(ann, Int32) + +type List = Cons(a, List(a)) | Nil + +function matchList() -> Boolean { + let list = Cons(True, Cons(False, Cons(True, Nil))); + case list { + Cons(a, Cons(b, Cons(c, Nil))) -> a && b && c, + _ -> False + } +} + +function listId(list: List(a)) -> List(a) { list} + +function nextColour(colour: Colour) -> Colour { + case colour { Red -> Green, Green -> Blue, Blue -> Red } +} \ No newline at end of file From 78557fcb3719f46e8c0f2e589f1616753ae8067a Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Mon, 12 Aug 2024 15:10:35 +0100 Subject: [PATCH 13/23] Beautiful --- lsp-log.txt | 1884 +------------------------ wasm-calc11/demo/draw.calc | 6 +- wasm-calc11/src/Calc/Types/Expr.hs | 2 +- wasm-calc11/src/Calc/Types/Pattern.hs | 2 +- wasm-calc11/test/static/noalloc.calc | 2 +- 5 files changed, 9 insertions(+), 1887 deletions(-) diff --git a/lsp-log.txt b/lsp-log.txt index f9cd503d..c0db1deb 100644 --- a/lsp-log.txt +++ b/lsp-log.txt @@ -1,1889 +1,11 @@ -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} -workspaceFolders [] -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: (Int64,Int64,Int64)\n) -> (Int64,Int64,Int64) { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = color; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n (r,g,b)\n}\n\nfunction cycle(color: (Int64,Int64,Int64)) -> (Int64,\nInt64,\nInt64) { let (r,g,b) = color; (g,b,r)}\n\nfunction initial(index: Int64) -> (Int64,Int64,Int64) { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n (r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 1 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 2 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 3 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 4 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 5 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 6 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 7 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 8 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 9 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 10 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 11 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 12 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 13 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 14 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 15 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 16 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 17 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 18 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 19 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 20 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 21 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 22 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 23 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 24 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 25 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 26 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 27 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 28 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 29 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 30 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 31 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 32 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 33 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 34 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 35 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 36 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 37 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 38 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 39 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 40 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 41 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 42 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 43 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 44 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 45 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 46 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 47 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 48 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 49 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 50 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 51 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 52 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 53 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 54 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 55 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 56 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 57 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 58 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 59 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 60 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 61 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 62 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 63 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 64 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 65 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 66 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 67 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 68 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 69 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 70 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 71 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 72 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 73 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 74 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 75 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 76 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 77 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 78 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 79 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 80 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 81 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 82 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 83 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 84 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 85 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 86 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 87 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 88 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 89 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 90 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 91 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 92 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 93 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 94 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 95 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 96 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 97 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 98 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 99 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 100 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 101 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 102 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 103 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 104 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 105 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 106 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 107 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 108 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 109 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 110 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 111 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 112 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 113 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 114 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 115 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 116 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 117 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 118 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 119 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 120 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 121 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 122 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 123 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 124 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 125 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 126 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 127 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 128 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 129 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 130 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 131 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 132 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 133 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 134 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 135 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 136 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 137 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 138 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 139 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 140 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 141 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 142 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 143 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 144 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 145 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 146 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 147 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 148 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 149 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 150 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 151 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 152 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 153 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 154 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 155 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 156 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 157 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 158 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 159 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 160 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 161 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 162 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 163 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 164 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 165 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 166 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 167 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 168 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 169 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 170 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 171 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 172 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 173 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 174 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 175 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 176 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 177 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 178 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 179 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 180 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 181 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 182 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 183 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 184 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 185 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 186 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 187 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 188 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 189 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 190 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 191 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 192 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 193 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 194 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 195 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 196 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 197 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 198 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 199 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 200 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 201 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 202 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 203 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 204 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 205 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 206 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 207 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 208 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 209 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 210 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 211 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 212 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 213 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 214 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 215 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 216 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 217 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 218 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 219 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 220 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 221 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 222 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 223 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 224 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 225 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 226 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 227 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 228 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 229 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 230 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 231 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 232 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 233 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 234 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 235 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 236 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 237 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 238 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 239 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 240 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 241 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 242 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 243 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 244 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 245 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 246 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 247 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 248 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 249 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 250 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 251 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 252 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 253 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 254 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 255 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 256 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 257 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 258 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 259 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 260 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 261 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 262 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 263 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 264 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 265 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 266 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 267 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 268 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 269 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 270 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 271 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 272 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 273 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 274 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 275 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 276 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 277 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 278 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 279 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 280 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 281 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 282 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 283 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 284 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 285 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 286 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 287 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 288 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 289 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 290 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 291 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 292 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 293 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 294 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 295 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 296 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 297 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 298 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 299 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 300 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 301 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 302 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 303 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 304 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 305 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 306 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 307 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 308 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 309 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 310 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 311 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 312 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 313 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 314 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 315 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 316 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 317 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 318 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 319 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 320 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 321 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 322 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 323 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 324 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color()\n) -> Color() { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color()) -> Color() { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} -workspaceFolders [] -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color()\n) -> Color() { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color()) -> Color() { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 1 -Found the virtual file: 1 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 2 -Found the virtual file: 2 -textDocumentDidSave -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} -workspaceFolders [] -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color() { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color()) -> Color() { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}\n"}}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 1 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 2 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} -workspaceFolders [] textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "type Colour = Blue | Green | Red\n\ntype Maybe = Just(a) | Nothing\n\ntype Either = Left(e) | Right(a)\n\ntype These = That(b) | These(a, b) | This(a)\n\ntype Expr = EBool(ann, Boolean) | EInt(ann, Int32)"}}} -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 1 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 2 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 3 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 4 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 5 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 6 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 7 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 8 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 9 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 10 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 11 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 12 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 13 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 14 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 15 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 16 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 17 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 18 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 19 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 20 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 21 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 22 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 23 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 24 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 25 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 26 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 27 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 28 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 29 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 30 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 31 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 32 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 33 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 34 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 35 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 36 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 37 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 38 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 39 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 40 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 41 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 42 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 43 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 44 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 45 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 46 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 47 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 48 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 49 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 50 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 51 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 52 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 53 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 54 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 55 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 56 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 57 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 58 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 59 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 60 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 61 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 62 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 63 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 64 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 65 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 66 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 67 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 68 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 69 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 70 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 71 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 72 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 73 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 74 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 75 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 76 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 77 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 78 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 79 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 80 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 81 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 82 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 83 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 84 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 85 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 86 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 87 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 88 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 89 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 90 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 91 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 92 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 93 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 94 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 95 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 96 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 97 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 98 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 99 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 100 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 101 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 102 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 103 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 104 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 105 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 106 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 107 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 108 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 109 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 110 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 111 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 112 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 113 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 114 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 115 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 116 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 117 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 118 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 119 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 120 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 121 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 122 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 123 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 124 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 125 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 126 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 127 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 128 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 129 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 130 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 131 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 132 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 133 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 134 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 135 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 136 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 137 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 138 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 139 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 140 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 141 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 142 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 143 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 144 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 145 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 146 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 147 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 148 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 149 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 150 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 151 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 152 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 153 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 154 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 155 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 156 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 157 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 158 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 159 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 160 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 161 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 162 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 163 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 164 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 165 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 166 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 167 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 168 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 169 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 170 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 171 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 172 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 173 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 174 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 175 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 176 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 177 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 178 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 179 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 180 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 181 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 182 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 183 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 184 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 185 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 186 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 187 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 188 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 189 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 190 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 191 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 192 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 193 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 194 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 195 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 196 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 197 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 198 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 199 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 200 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 201 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 202 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 203 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 204 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 205 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 206 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 207 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 208 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 209 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 210 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 211 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 212 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 213 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 214 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 215 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 216 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 217 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 218 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 219 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 220 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 221 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 222 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 223 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 224 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 225 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 226 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 227 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 228 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 229 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 230 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 231 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 232 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 233 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 234 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 235 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 236 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 237 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 238 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 239 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 240 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 241 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 242 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 243 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 244 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 245 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 246 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 247 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 248 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 249 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 250 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 251 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 252 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 253 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 254 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 255 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 256 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 257 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 258 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 259 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 260 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 261 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 262 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 263 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 264 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 265 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 266 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 267 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 268 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 269 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 270 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 271 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 272 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 273 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 274 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 275 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 276 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 277 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 278 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 279 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 280 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 281 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 282 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 283 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 284 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 285 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 286 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 287 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 288 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 289 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 290 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 291 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 292 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 293 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 294 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 295 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 296 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 297 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 298 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 299 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 300 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 301 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 302 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 303 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 304 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 305 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 306 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 307 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 308 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 309 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 310 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 311 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 312 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 313 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 314 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 315 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 316 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 317 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 318 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 319 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 320 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 321 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 322 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 323 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 324 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 325 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 326 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 327 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 328 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 329 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 330 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 331 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 332 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 333 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 334 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 335 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 336 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 337 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 338 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 339 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 340 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 341 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 342 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 343 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 344 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 345 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 346 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 347 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 348 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 349 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 350 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 351 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 352 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 353 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 354 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 355 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 356 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 357 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 358 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 359 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 360 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 361 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 362 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 363 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 364 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 365 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 366 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 367 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 368 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 369 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 370 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 371 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 372 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 373 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 374 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 375 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 376 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 377 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 378 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 379 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 380 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 381 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 382 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 383 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 384 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 385 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 386 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 387 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 388 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 389 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 390 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 391 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 392 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 393 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 394 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 395 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 396 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 397 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 398 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 399 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 400 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 401 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 402 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 403 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 404 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 405 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 406 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 407 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 408 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 409 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 410 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 411 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 412 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 413 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 414 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 415 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 416 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 417 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 418 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 419 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 420 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 421 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 422 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 423 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 424 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 425 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 426 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 427 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 428 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 429 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 430 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 431 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 432 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 433 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 434 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 435 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 436 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 437 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 438 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 439 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 440 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 441 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 442 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 443 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 444 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 445 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 446 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 447 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 448 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 449 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 450 -Processing DidChangeTextDocument for: NormalizedUri 1336244196612393608 "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc" -Found the virtual file: 451 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/test/static/datatypes.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 3 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 4 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 5 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 6 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r, g, b) = case color {\n RGB(r, g, b) -> (r, g, b), \n Greyscale(grey) -> (grey, grey, grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} workspaceFolders [] textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {}; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r,g,b)\n}\n\nfunction cycle(color: Color) -> Color { case color {}}\n\nfunction initial(index: Int64) -> Color() { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r,g,b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}\n"}}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 1 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 2 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 3 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 4 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 5 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 6 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 7 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 8 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 9 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 10 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 11 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 12 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 13 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 14 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 15 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 16 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 17 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 18 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 19 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 20 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 21 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 22 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 23 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 24 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 25 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 26 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 27 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 28 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 29 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 30 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 31 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 32 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 33 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 34 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 35 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 36 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 37 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 38 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 39 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 40 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 41 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 42 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 43 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 44 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 45 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 46 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 47 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 48 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 49 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 50 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 51 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 52 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 53 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 54 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 55 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 56 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 57 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 58 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 59 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 60 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 61 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 62 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 63 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 64 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 65 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 66 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 67 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 68 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 69 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 70 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 71 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 72 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 73 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 74 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 75 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 76 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 77 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 78 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 79 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 80 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 81 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 82 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 83 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 84 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 85 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 86 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 87 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 88 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 89 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 90 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 91 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 92 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 93 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 94 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 95 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 96 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 97 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 98 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 99 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 100 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 101 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 102 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 103 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 104 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 105 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 106 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 107 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 108 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 109 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 110 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 111 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 112 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 113 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 114 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 115 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 116 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 117 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 118 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 119 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 120 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 121 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 122 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 123 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 124 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 125 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 126 -Processing DidChangeTextDocument for: NormalizedUri (-7880369104437011469) "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc" -Found the virtual file: 127 -textDocumentDidSave -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidSave, _params = DidSaveTextDocumentParams {_textDocument = TextDocumentIdentifier {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}}, _text = Nothing}} +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r, g, b) = case color {\n RGB(r, g, b) -> (r, g, b), \n Greyscale(grey) -> (grey, grey, grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} workspaceFolders [] textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r,g,b) = case color {\n RGB(r, g, b) -> (r,g,b), \n Greyscale(grey) -> (grey,grey,grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} \ No newline at end of file +TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r, g, b) = case color {\n RGB(r, g, b) -> (r, g, b), \n Greyscale(grey) -> (grey, grey, grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} \ No newline at end of file diff --git a/wasm-calc11/demo/draw.calc b/wasm-calc11/demo/draw.calc index 1691698a..321a93de 100644 --- a/wasm-calc11/demo/draw.calc +++ b/wasm-calc11/demo/draw.calc @@ -23,9 +23,9 @@ function drawBounded( ) -> Color { let maxWidth: Int64 = 600; let maxHeight: Int64 = 600; - let (r,g,b) = case color { - RGB(r, g, b) -> (r,g,b), - Greyscale(grey) -> (grey,grey,grey) + let (r, g, b) = case color { + RGB(r, g, b) -> (r, g, b), + Greyscale(grey) -> (grey, grey, grey) }; draw( clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b diff --git a/wasm-calc11/src/Calc/Types/Expr.hs b/wasm-calc11/src/Calc/Types/Expr.hs index 39257f3b..23b8f64d 100644 --- a/wasm-calc11/src/Calc/Types/Expr.hs +++ b/wasm-calc11/src/Calc/Types/Expr.hs @@ -108,7 +108,7 @@ instance PP.Pretty (Expr ann) where where pArgs = PP.punctuate ", " (PP.pretty <$> args) pretty (ETuple _ a as) = - "(" <> PP.cat (PP.punctuate "," (PP.pretty <$> tupleItems a as)) <> ")" + "(" <> PP.cat (PP.punctuate ", " (PP.pretty <$> tupleItems a as)) <> ")" where tupleItems :: a -> NE.NonEmpty a -> [a] tupleItems b bs = b : NE.toList bs diff --git a/wasm-calc11/src/Calc/Types/Pattern.hs b/wasm-calc11/src/Calc/Types/Pattern.hs index a6bcd380..0195f6dc 100644 --- a/wasm-calc11/src/Calc/Types/Pattern.hs +++ b/wasm-calc11/src/Calc/Types/Pattern.hs @@ -25,7 +25,7 @@ instance PP.Pretty (Pattern ann) where pretty (PLiteral _ prim) = PP.pretty prim pretty (PBox _ inner) = "Box(" <> PP.pretty inner <> ")" pretty (PTuple _ a as) = - "(" <> PP.cat (PP.punctuate "," (PP.pretty <$> tupleItems a as)) <> ")" + "(" <> PP.cat (PP.punctuate ", " (PP.pretty <$> tupleItems a as)) <> ")" where tupleItems :: a -> NE.NonEmpty a -> [a] tupleItems b bs = b : NE.toList bs diff --git a/wasm-calc11/test/static/noalloc.calc b/wasm-calc11/test/static/noalloc.calc index 502089f2..5f2de2b5 100644 --- a/wasm-calc11/test/static/noalloc.calc +++ b/wasm-calc11/test/static/noalloc.calc @@ -7,6 +7,6 @@ function id(a: a) -> a { a} export function test(index: Int8) -> Int8 { let a: Box(Int8) = Box(1); let b: Box(Int8) = Box(2); - let (Box(c),Box(d)) = (id(a),id(b)); + let (Box(c), Box(d)) = (id(a), id(b)); add(c, d) } \ No newline at end of file From 34c3a74b5be23accfa26c1f796a479c6507f11a9 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Mon, 12 Aug 2024 15:53:33 +0100 Subject: [PATCH 14/23] Woof --- lsp-log.txt | 11 ----------- wasm-calc11/src/Calc/Typecheck/Helpers.hs | 18 +++++++++--------- wasm-calc11/src/Calc/Typecheck/Infer.hs | 6 +++++- .../test/Test/Typecheck/TypecheckSpec.hs | 10 ++++++++++ wasm-calc11/test/Test/Wasm/WasmSpec.hs | 7 +++---- 5 files changed, 27 insertions(+), 25 deletions(-) delete mode 100644 lsp-log.txt diff --git a/lsp-log.txt b/lsp-log.txt deleted file mode 100644 index c0db1deb..00000000 --- a/lsp-log.txt +++ /dev/null @@ -1,11 +0,0 @@ - -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r, g, b) = case color {\n RGB(r, g, b) -> (r, g, b), \n Greyscale(grey) -> (grey, grey, grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} -workspaceFolders [] -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r, g, b) = case color {\n RGB(r, g, b) -> (r, g, b), \n Greyscale(grey) -> (grey, grey, grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_Initialized, _params = InitializedParams} -workspaceFolders [] -textDocumentDidOpen -TNotificationMessage {_jsonrpc = "2.0", _method = SMethod_TextDocumentDidOpen, _params = DidOpenTextDocumentParams {_textDocument = TextDocumentItem {_uri = Uri {getUri = "file:///Users/danielharvey/Git/wasm-calc/wasm-calc11/demo/draw.calc"}, _languageId = LanguageKind_Custom "calc", _version = 0, _text = "global mut index: Int64 = 1\n\ntype Color = Greyscale(Int64) | RGB(Int64, Int64, Int64)\n\nimport imports.draw as draw(\n x: Int64, y: Int64, r: Int64, g: Int64, b: Int64\n) -> Void\n\nfunction min(floor: Int64, value: Int64) -> Int64 { \n if value > floor then value else floor\n}\n\nfunction max(ceiling: Int64, value: Int64) -> Int64 { \n if value < ceiling then value else ceiling\n}\n\nfunction clamp(\n floor: Int64, ceiling: Int64, value: Int64\n) -> Int64 { min(floor, max(ceiling, value))}\n\nfunction drawBounded(\n x: Int64, y: Int64, color: Color\n) -> Color { \n let maxWidth: Int64 = 600; \n let maxHeight: Int64 = 600; \n let (r, g, b) = case color {\n RGB(r, g, b) -> (r, g, b), \n Greyscale(grey) -> (grey, grey, grey) \n }; \n draw(\n clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b\n ); \n RGB(r, g, b)\n}\n\nfunction cycle(color: Color) -> Color { \n case color {\n RGB(r, g, b) -> RGB(g, b, r), \n Greyscale(grey) -> Greyscale(grey) \n }\n}\n\nfunction initial(index: Int64) -> Color { \n let r = clamp(0, 255, index * 2); \n let g = clamp(0, 255, 255 - r); \n let b = clamp(0, 255, r * 3); \n RGB(r, g, b)\n}\n\nexport function test() -> Void { \n let color = drawBounded(\n index * 2, index * 3, initial(index)\n ); \n let color2 = drawBounded(\n 100 - index, index * 3, cycle(color)\n ); \n let color3 = drawBounded(\n 10 + index * 3, 50 - index * 2, cycle(color2)\n ); \n drawBounded(index * 4, 200 - index * 3, cycle(color3)); \n if index < 200 then\n set(index, index + 1)\n else\n set(index, 0)\n}"}}} \ No newline at end of file diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index 2a5f984f..d9096915 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} - + {-# LANGUAGE FlexibleContexts #-} module Calc.Typecheck.Helpers ( runTypecheckM, lookupVar, @@ -18,6 +18,7 @@ module Calc.Typecheck.Helpers ) where +import Calc.TypeUtils import Calc.Typecheck.Error import Calc.Typecheck.Generalise import Calc.Typecheck.Types @@ -234,11 +235,10 @@ lookupConstructor ann constructor = do matchConstructorTypesToArgs :: Constructor -> [TypeVar] -> [Type ann] -> [Type ann] -> TypecheckM ann [Type ann] matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs = let pairs = M.fromList (zip dataTypeVars tyArgs) - in traverse - ( \case - TVar ann var -> case M.lookup var pairs of - Just ty -> pure ty - Nothing -> throwError (UnknownGenericInConstructor ann constructor var) - otherTy -> pure otherTy - ) - dataTypeArgs + replaceTy outerTy = case outerTy of + TVar ann var -> case M.lookup var pairs of + Just ty -> pure ty + Nothing -> throwError (UnknownGenericInConstructor ann constructor var) + otherTy -> bindType replaceTy otherTy + + in traverse replaceTy dataTypeArgs diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index d5847765..4b63f3a8 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -6,7 +6,7 @@ module Calc.Typecheck.Infer checkPattern, ) where - +import Debug.Trace import Calc.ExprUtils import Calc.TypeUtils import Calc.Typecheck.Error @@ -406,6 +406,10 @@ checkConstructor maybeTy ann constructor args = do unless (tyCons == dataTypeName) $ error "wrong" filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs + + traceShowM ("filtered" :: String, void <$> filtered) + traceShowM ("args" ::String, void <$> args) + typedArgs <- zipWithM check filtered args pure ( typedArgs, diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index 4da7f7ab..7bc5993f 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -183,6 +183,16 @@ spec = do ], tyInt32 ), + (joinLines + ["type List = Cons(a, List(a)) | Nil", + "function main() -> Int32 { let _: List(Boolean) = Cons(True, Cons(False, Nil)); 100 }"], + tyInt32), + (joinLines + ["type List = Cons(a, List(a)) | Nil", + "function main() -> Int32 { let _ = Cons(True, Cons(False, Nil)); 100 }"], + tyInt32), + + ( "function main() -> Int32 { case True { True -> 1, False -> 2 } }", tyInt32 ) diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 05d1940f..b24207a3 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -406,13 +406,13 @@ spec = do "export function test() -> Boolean { case These(True,False) { This(a) -> a , That(b) -> b , These(a,b) -> a && b } }" ], Wasm.VI32 0 - ) {-, + ) , ( joinLines [ "type List = Cons(a, List(a)) | Nil", asTest "let value: List(Int64) = Cons((1:Int64),Cons((2:Int64),Nil)); case value { Cons(a,Cons(b,Nil)) -> a + b, _ -> 0 }" ], Wasm.VI64 3 - ), + ){-, ( joinLines [ "type Maybe = Just(a) | Nothing", @@ -420,8 +420,7 @@ spec = do asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" ], Wasm.VI64 100 - )- - -} + )-} {-, -- absolutely baffled why `allocated` is not dropped here when we From 50e3325b0141f7d724ce036ca58256a5ae04e3c5 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 14 Aug 2024 12:11:00 +0100 Subject: [PATCH 15/23] Fix unification --- wasm-calc11/src/Calc/Typecheck/Infer.hs | 22 +++++++++++---- wasm-calc11/src/Calc/Typecheck/Unify.hs | 21 +++++++++----- .../test/Test/Typecheck/TypecheckSpec.hs | 28 +++++++++++++++---- 3 files changed, 52 insertions(+), 19 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 4b63f3a8..6dad0a02 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -6,7 +6,8 @@ module Calc.Typecheck.Infer checkPattern, ) where -import Debug.Trace + +import Calc.Typecheck.Generalise import Calc.ExprUtils import Calc.TypeUtils import Calc.Typecheck.Error @@ -403,21 +404,30 @@ checkConstructor maybeTy ann constructor args = do (typedArgs, fallbackTypes) <- case maybeTy of Just (tyCons, tyArgs) -> do + -- we have a type signature to check this against unless (tyCons == dataTypeName) $ error "wrong" filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs - traceShowM ("filtered" :: String, void <$> filtered) - traceShowM ("args" ::String, void <$> args) - typedArgs <- zipWithM check filtered args + + let fallbackTypes = M.fromList (zip dataTypeVars tyArgs) + pure ( typedArgs, - M.fromList (zip dataTypeVars tyArgs) + fallbackTypes ) Nothing -> do + -- we have no type signature to check this against typedArgs <- traverse infer args - pure (typedArgs, mempty) + + -- create fresh unification types (ie, guess!) to fill in any + -- gaps. Ie, when inferring the type of `Nothing` we don't know + -- what the `a` is in `Maybe`, but also, we don't care, so say + -- "it's a thing, you can decide later" + fallbackTypes <- M.fromList <$> traverse (\var -> (,) var <$> (TUnificationVar ann <$> freshUnificationVariable)) dataTypeVars + + pure (typedArgs, fallbackTypes) monomorphisedArgs <- calculateMonomorphisedTypes dataTypeVars dataTypeArgs (getOuterAnnotation <$> typedArgs) fallbackTypes diff --git a/wasm-calc11/src/Calc/Typecheck/Unify.hs b/wasm-calc11/src/Calc/Typecheck/Unify.hs index 6c9b08e7..64493dfe 100644 --- a/wasm-calc11/src/Calc/Typecheck/Unify.hs +++ b/wasm-calc11/src/Calc/Typecheck/Unify.hs @@ -30,11 +30,24 @@ unify (TContainer ann as) (TContainer _ bs) = <$> ( NE.fromList <$> zipWithM unify (NE.toList as) (NE.toList bs) ) +unify (TConstructor ann dataNameA argsA) (TConstructor _ dataNameB argsB) + | dataNameA == dataNameB && length argsA == length argsB + = TConstructor ann dataNameA <$> zipWithM unify argsA argsB unify tyA tyB = if void tyA == void tyB then pure tyA else throwError (TypeMismatch tyA tyB) +storeUnified :: Natural -> Type ann -> TypecheckM ann () +storeUnified nat ty + = modify + ( \tcs -> + tcs + { tcsUnified = + HM.insert nat ty (tcsUnified tcs) + } + ) + -- | given a unification variable, either save it and return the type -- or explode because we've already unified it with something else unifyVariableWithType :: @@ -47,13 +60,7 @@ unifyVariableWithType nat ty = case existing of Nothing -> do -- this is the first match, store it and return the passed-in type - modify - ( \tcs -> - tcs - { tcsUnified = - HM.insert nat ty (tcsUnified tcs) - } - ) + storeUnified nat ty pure ty Just existingTy -> do unify existingTy ty diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index 7bc5993f..b583ed5f 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -50,7 +50,7 @@ spec = do describe "Module" $ do let succeeding = [ ( joinLines - [ "function ignore() -> Int64 { 1 }", + [ "function ignore() -> Int64 { 1 }", "function main() -> Int64 { 42 }" ], tyInt64 @@ -190,14 +190,25 @@ spec = do (joinLines ["type List = Cons(a, List(a)) | Nil", "function main() -> Int32 { let _ = Cons(True, Cons(False, Nil)); 100 }"], - tyInt32), - - + tyInt32) , ( "function main() -> Int32 { case True { True -> 1, False -> 2 } }", tyInt32 + ), + ( joinLines ["type Either = Left(e) | Right(a)", + "function main() -> Int32 { case Right((42:Int32)) { Right(a) -> a, Left(_) -> 0 } }"], + tyInt32 + ), + ( joinLines ["type Either = Left(e) | Right(a)", + "function main() -> Int32 { case Right((42:Int32)) { Right(a) -> a, Left(e) -> e } }"], + tyInt32 + ), + ( joinLines ["type Either = Left(e) | Right(a)", + "function main() -> Int32 { let either: Either(Boolean,Int32) = Right(42); case either { Right(a) -> a, Left(_) -> 0 } }"], + tyInt32 ) + ] - describe "Successfully typechecking modules" $ do + fdescribe "Successfully typechecking modules" $ do traverse_ testSucceedingModule succeeding let failing = @@ -230,7 +241,12 @@ spec = do [ "global counter: Int32 = 0", "function setsNonMutableGlobal() -> Void { set(counter, 1) }" ], - joinLines ["test itsNotABool = (1: Int32)"] + joinLines ["test itsNotABool = (1: Int32)"], + joinLines ["type Either = Left(e) | Right(a)", + "function main() -> Int32 { case Right((42:Int32)) { Right(int) -> int, Left(bool) -> bool && True } }"] + + + ] describe "Failing typechecking modules" $ do traverse_ testFailingModule failing From a3a9ca57ff2ad021fc1c1c4ea39577a733aa0b1d Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 14 Aug 2024 12:35:42 +0100 Subject: [PATCH 16/23] Well, shit --- wasm-calc11/src/Calc/Typecheck/Infer.hs | 2 ++ wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 11 +++++++++-- wasm-calc11/test/Test/Helpers.hs | 14 ++++++++++++++ .../test/Test/Typecheck/TypecheckSpec.hs | 2 +- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 5 +++++ wasm-calc11/test/Test/Wasm/WasmSpec.hs | 17 +++++++++-------- 6 files changed, 40 insertions(+), 11 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 6dad0a02..a76c51ab 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -266,6 +266,8 @@ unifyPrimitives (TFunction _ argA bodyA) (TFunction _ argB bodyB) = do unifyPrimitives bodyA bodyB unifyPrimitives (TContainer _ as) (TContainer _ bs) = zipWithM_ unifyPrimitives (NE.toList as) (NE.toList bs) +unifyPrimitives (TConstructor _ _ as) (TConstructor _ _ bs) = + zipWithM_ unifyPrimitives as bs unifyPrimitives tyA tyB = if void tyA == void tyB then pure () diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index c6626a66..eeff1095 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -370,11 +370,11 @@ memorySizeForType (TConstructor _ dataTypeName _) = do (Data _ _ constructors) <- lookupDataType dataTypeName let discriminator = memorySize I8 sizeOfConstructor tys = - getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeForType) tys) + getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeInsideConstructor) tys) sizes <- traverse sizeOfConstructor (M.elems constructors) pure $ discriminator + maximum sizes memorySizeForType (TContainer _ as) = - getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeForType) (NE.toList as)) + getSum <$> (mconcat <$> traverse (fmap Sum . memorySizeInsideConstructor) (NE.toList as)) memorySizeForType (TFunction {}) = pure $ memorySize Pointer memorySizeForType (TVar _ _) = @@ -382,6 +382,13 @@ memorySizeForType (TVar _ _) = memorySizeForType (TUnificationVar _ _) = error "memorySizeForType TUnificationVar" +-- nested data types only take up "Pointer" +memorySizeInsideConstructor :: (MonadState FromExprState m) => Type ann -> m Natural +memorySizeInsideConstructor (TContainer {}) = pure $ memorySize Pointer +memorySizeInsideConstructor (TConstructor {}) = pure $ memorySize Pointer +memorySizeInsideConstructor other = memorySizeForType other + + getConstructorNumber :: (MonadState FromExprState m) => Type ann -> Constructor -> m Natural getConstructorNumber ty constructor = do (Data _ _ constructors) <- case ty of diff --git a/wasm-calc11/test/Test/Helpers.hs b/wasm-calc11/test/Test/Helpers.hs index f8c07bf1..12d7b470 100644 --- a/wasm-calc11/test/Test/Helpers.hs +++ b/wasm-calc11/test/Test/Helpers.hs @@ -145,5 +145,19 @@ exprState = ("These", [TVar mempty "a", TVar mempty "b"]) ] } + ), + ( DataName "List", + Data + { dtName = DataName "List", + dtVars = ["a" ], + dtConstructors = + M.fromList + [ ("Cons", [ + TVar mempty "a", + TConstructor mempty (DataName "List") [TVar mempty "a"]]), + ("Nil", []) + ] + } ) + ] diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index b583ed5f..fdac6f98 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -208,7 +208,7 @@ spec = do ) ] - fdescribe "Successfully typechecking modules" $ do + describe "Successfully typechecking modules" $ do traverse_ testSucceedingModule succeeding let failing = diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index 0004fbe9..7f00a0d1 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -52,6 +52,11 @@ spec = do flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8, Int64)") "This") `shouldBe` Right [1, 2] + it "Recursive type" $ do + flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "List(Int64)") "Cons") + `shouldBe` Right [1, 9, 13] + + describe "calculateMonomorphisedTypes" $ do it "Ints" $ do monomorphiseTypes @() ["a", "b"] [tyVar "a", tyVar "b"] [tyInt32, tyInt64] diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index b24207a3..9b931801 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -407,20 +407,21 @@ spec = do ], Wasm.VI32 0 ) , - ( joinLines - [ "type List = Cons(a, List(a)) | Nil", - asTest "let value: List(Int64) = Cons((1:Int64),Cons((2:Int64),Nil)); case value { Cons(a,Cons(b,Nil)) -> a + b, _ -> 0 }" - ], - Wasm.VI64 3 - ){-, - ( joinLines [ "type Maybe = Just(a) | Nothing", "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" ], Wasm.VI64 100 - )-} + ), + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + asTest "let value: List(Int64) = Cons((1:Int64),Cons((2:Int64),Nil)); case value { Cons(a,Cons(b,Nil)) -> a + b, _ -> 0 }" + ], + Wasm.VI64 3 + ) + + {-, -- absolutely baffled why `allocated` is not dropped here when we From b5c0f685bfa6b9c35ccbd11ac4341d7af99a855a Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 14 Aug 2024 15:43:52 +0100 Subject: [PATCH 17/23] Tests for List --- wasm-calc11/src/Calc/Typecheck/Helpers.hs | 12 ++-- wasm-calc11/src/Calc/Typecheck/Infer.hs | 2 +- wasm-calc11/src/Calc/Typecheck/Unify.hs | 20 +++--- wasm-calc11/src/Calc/Types/Expr.hs | 20 ++++-- wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs | 1 - wasm-calc11/test/Test/Helpers.hs | 11 +-- .../test/Test/Typecheck/TypecheckSpec.hs | 50 +++++++------ wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 1 - wasm-calc11/test/Test/Wasm/WasmSpec.hs | 72 +++++++++++-------- 9 files changed, 107 insertions(+), 82 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index d9096915..9efb46d8 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -1,7 +1,8 @@ {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} - {-# LANGUAGE FlexibleContexts #-} + module Calc.Typecheck.Helpers ( runTypecheckM, lookupVar, @@ -236,9 +237,8 @@ matchConstructorTypesToArgs :: Constructor -> [TypeVar] -> [Type ann] -> [Type a matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs = let pairs = M.fromList (zip dataTypeVars tyArgs) replaceTy outerTy = case outerTy of - TVar ann var -> case M.lookup var pairs of - Just ty -> pure ty - Nothing -> throwError (UnknownGenericInConstructor ann constructor var) - otherTy -> bindType replaceTy otherTy - + TVar ann var -> case M.lookup var pairs of + Just ty -> pure ty + Nothing -> throwError (UnknownGenericInConstructor ann constructor var) + otherTy -> bindType replaceTy otherTy in traverse replaceTy dataTypeArgs diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index a76c51ab..3933b8bf 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -7,10 +7,10 @@ module Calc.Typecheck.Infer ) where -import Calc.Typecheck.Generalise import Calc.ExprUtils import Calc.TypeUtils import Calc.Typecheck.Error +import Calc.Typecheck.Generalise import Calc.Typecheck.Helpers import Calc.Typecheck.Patterns import Calc.Typecheck.Substitute diff --git a/wasm-calc11/src/Calc/Typecheck/Unify.hs b/wasm-calc11/src/Calc/Typecheck/Unify.hs index 64493dfe..7d9e7e3d 100644 --- a/wasm-calc11/src/Calc/Typecheck/Unify.hs +++ b/wasm-calc11/src/Calc/Typecheck/Unify.hs @@ -31,22 +31,22 @@ unify (TContainer ann as) (TContainer _ bs) = <$> zipWithM unify (NE.toList as) (NE.toList bs) ) unify (TConstructor ann dataNameA argsA) (TConstructor _ dataNameB argsB) - | dataNameA == dataNameB && length argsA == length argsB - = TConstructor ann dataNameA <$> zipWithM unify argsA argsB + | dataNameA == dataNameB && length argsA == length argsB = + TConstructor ann dataNameA <$> zipWithM unify argsA argsB unify tyA tyB = if void tyA == void tyB then pure tyA else throwError (TypeMismatch tyA tyB) storeUnified :: Natural -> Type ann -> TypecheckM ann () -storeUnified nat ty - = modify - ( \tcs -> - tcs - { tcsUnified = - HM.insert nat ty (tcsUnified tcs) - } - ) +storeUnified nat ty = + modify + ( \tcs -> + tcs + { tcsUnified = + HM.insert nat ty (tcsUnified tcs) + } + ) -- | given a unification variable, either save it and return the type -- or explode because we've already unified it with something else diff --git a/wasm-calc11/src/Calc/Types/Expr.hs b/wasm-calc11/src/Calc/Types/Expr.hs index 23b8f64d..93e50cfb 100644 --- a/wasm-calc11/src/Calc/Types/Expr.hs +++ b/wasm-calc11/src/Calc/Types/Expr.hs @@ -69,14 +69,20 @@ instance PP.Pretty (Expr ann) where <> PP.pretty rest pretty (EMatch _ expr pats) = "case" - <+> PP.pretty expr <+> - "{" <> - PP.group (PP.line <> - indentMulti 2 (PP.cat - (PP.punctuate ", " (prettyPat <$> NE.toList pats))) - <+> PP.line') <> "}" + <+> PP.pretty expr + <+> "{" + <> PP.group + ( PP.line + <> indentMulti + 2 + ( PP.cat + (PP.punctuate ", " (prettyPat <$> NE.toList pats)) + ) + <+> PP.line' + ) + <> "}" where - prettyPat (pat,patExpr) = + prettyPat (pat, patExpr) = PP.pretty pat <+> "->" <+> PP.pretty patExpr pretty (EConstructor _ constructor []) = PP.pretty constructor diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs index eeff1095..2bc11c0f 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Helpers.hs @@ -388,7 +388,6 @@ memorySizeInsideConstructor (TContainer {}) = pure $ memorySize Pointer memorySizeInsideConstructor (TConstructor {}) = pure $ memorySize Pointer memorySizeInsideConstructor other = memorySizeForType other - getConstructorNumber :: (MonadState FromExprState m) => Type ann -> Constructor -> m Natural getConstructorNumber ty constructor = do (Data _ _ constructors) <- case ty of diff --git a/wasm-calc11/test/Test/Helpers.hs b/wasm-calc11/test/Test/Helpers.hs index 12d7b470..f230c470 100644 --- a/wasm-calc11/test/Test/Helpers.hs +++ b/wasm-calc11/test/Test/Helpers.hs @@ -149,15 +149,16 @@ exprState = ( DataName "List", Data { dtName = DataName "List", - dtVars = ["a" ], + dtVars = ["a"], dtConstructors = M.fromList - [ ("Cons", [ - TVar mempty "a", - TConstructor mempty (DataName "List") [TVar mempty "a"]]), + [ ( "Cons", + [ TVar mempty "a", + TConstructor mempty (DataName "List") [TVar mempty "a"] + ] + ), ("Nil", []) ] } ) - ] diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index fdac6f98..9027ff4d 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -50,7 +50,7 @@ spec = do describe "Module" $ do let succeeding = [ ( joinLines - [ "function ignore() -> Int64 { 1 }", + [ "function ignore() -> Int64 { 1 }", "function main() -> Int64 { 42 }" ], tyInt64 @@ -183,30 +183,39 @@ spec = do ], tyInt32 ), - (joinLines - ["type List = Cons(a, List(a)) | Nil", - "function main() -> Int32 { let _: List(Boolean) = Cons(True, Cons(False, Nil)); 100 }"], - tyInt32), - (joinLines - ["type List = Cons(a, List(a)) | Nil", - "function main() -> Int32 { let _ = Cons(True, Cons(False, Nil)); 100 }"], - tyInt32) , + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + "function main() -> Int32 { let _: List(Boolean) = Cons(True, Cons(False, Nil)); 100 }" + ], + tyInt32 + ), + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + "function main() -> Int32 { let _ = Cons(True, Cons(False, Nil)); 100 }" + ], + tyInt32 + ), ( "function main() -> Int32 { case True { True -> 1, False -> 2 } }", tyInt32 ), - ( joinLines ["type Either = Left(e) | Right(a)", - "function main() -> Int32 { case Right((42:Int32)) { Right(a) -> a, Left(_) -> 0 } }"], + ( joinLines + [ "type Either = Left(e) | Right(a)", + "function main() -> Int32 { case Right((42:Int32)) { Right(a) -> a, Left(_) -> 0 } }" + ], tyInt32 ), - ( joinLines ["type Either = Left(e) | Right(a)", - "function main() -> Int32 { case Right((42:Int32)) { Right(a) -> a, Left(e) -> e } }"], + ( joinLines + [ "type Either = Left(e) | Right(a)", + "function main() -> Int32 { case Right((42:Int32)) { Right(a) -> a, Left(e) -> e } }" + ], tyInt32 ), - ( joinLines ["type Either = Left(e) | Right(a)", - "function main() -> Int32 { let either: Either(Boolean,Int32) = Right(42); case either { Right(a) -> a, Left(_) -> 0 } }"], + ( joinLines + [ "type Either = Left(e) | Right(a)", + "function main() -> Int32 { let either: Either(Boolean,Int32) = Right(42); case either { Right(a) -> a, Left(_) -> 0 } }" + ], tyInt32 ) - ] describe "Successfully typechecking modules" $ do traverse_ testSucceedingModule succeeding @@ -242,11 +251,10 @@ spec = do "function setsNonMutableGlobal() -> Void { set(counter, 1) }" ], joinLines ["test itsNotABool = (1: Int32)"], - joinLines ["type Either = Left(e) | Right(a)", - "function main() -> Int32 { case Right((42:Int32)) { Right(int) -> int, Left(bool) -> bool && True } }"] - - - + joinLines + [ "type Either = Left(e) | Right(a)", + "function main() -> Int32 { case Right((42:Int32)) { Right(int) -> int, Left(bool) -> bool && True } }" + ] ] describe "Failing typechecking modules" $ do traverse_ testFailingModule failing diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index 7f00a0d1..1c177e11 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -56,7 +56,6 @@ spec = do flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "List(Int64)") "Cons") `shouldBe` Right [1, 9, 13] - describe "calculateMonomorphisedTypes" $ do it "Ints" $ do monomorphiseTypes @() ["a", "b"] [tyVar "a", tyVar "b"] [tyInt32, tyInt64] diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 9b931801..60128fa1 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -406,36 +406,48 @@ spec = do "export function test() -> Boolean { case These(True,False) { This(a) -> a , That(b) -> b , These(a,b) -> a && b } }" ], Wasm.VI32 0 - ) , - ( joinLines - [ "type Maybe = Just(a) | Nothing", - "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", - asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" - ], - Wasm.VI64 100 - ), - ( joinLines - [ "type List = Cons(a, List(a)) | Nil", - asTest "let value: List(Int64) = Cons((1:Int64),Cons((2:Int64),Nil)); case value { Cons(a,Cons(b,Nil)) -> a + b, _ -> 0 }" - ], - Wasm.VI64 3 - ) - - - - {-, - -- absolutely baffled why `allocated` is not dropped here when we - -- generate what looks like the correct IR - ( asTest $ - joinLines - [ "let pair = ((1:Int64),False);", - "case pair { ", - "(a,False) -> { let allocated = Box((100: Int64)); let Box(b) = allocated; b + a },", - "_ -> 400 ", - "}" - ], - Wasm.VI64 101 - )-} + ), + ( joinLines + [ "type Maybe = Just(a) | Nothing", + "function fromMaybe(maybe: Maybe(a), default: a) -> a { case maybe { Just(a) -> a, Nothing -> default } }", + asTest "let matchValue: Maybe(Box(Int64)) = Just(Box(100)); let default: Box(Int64) = Box(0); let Box(result) = fromMaybe(matchValue, default); result" + ], + Wasm.VI64 100 + ), + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + asTest "let value: List(Int64) = Cons((1:Int64),Cons((2:Int64),Nil)); case value { Cons(a,Cons(b,Nil)) -> a + b, _ -> 0 }" + ], + Wasm.VI64 3 + ), + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + "function sum(list:List(Int64)) -> Int64 { case list { Cons(a, rest) -> a + sum(rest), Nil -> 0 } }", + asTest "sum(Cons(1,Cons(2,Cons(3,Cons(4,Nil)))))" + ], + Wasm.VI64 10 + ), + ( joinLines + [ "type List = Cons(a, List(a)) | Nil", + "function repeat(value: Int64, repeats: Int64 ) -> List(Int64) { if repeats < 1 then Nil else Cons(value, repeat(value, repeats - 1)) }", + "function sum(accum: Int64,list:List(Int64)) -> Int64 { case list { Cons(a, rest) -> sum(accum + a, rest), Nil -> accum } }", + asTest "sum(0,repeat(6,100))" -- surprisingly easy to pop the stack by increasing this value + ], + Wasm.VI64 600 + ) + {-, + -- absolutely baffled why `allocated` is not dropped here when we + -- generate what looks like the correct IR + ( asTest $ + joinLines + [ "let pair = ((1:Int64),False);", + "case pair { ", + "(a,False) -> { let allocated = Box((100: Int64)); let Box(b) = allocated; b + a },", + "_ -> 400 ", + "}" + ], + Wasm.VI64 101 + )-} ] describe "From expressions" $ do From 7ea43088b8e453a3ad61bb5b59f9001a77734efd Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 14 Aug 2024 15:46:07 +0100 Subject: [PATCH 18/23] Oh yes --- wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index 9027ff4d..a0e8504c 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -254,7 +254,12 @@ spec = do joinLines [ "type Either = Left(e) | Right(a)", "function main() -> Int32 { case Right((42:Int32)) { Right(int) -> int, Left(bool) -> bool && True } }" + ], + joinLines + [ "type List = Cons(a, List(a)) | Nil", + "function main() -> Int32 { let _ = Cons(True, Cons((42:Int32),Nil)); 100 }" ] + ] describe "Failing typechecking modules" $ do traverse_ testFailingModule failing From 39d4bdf8fc2e6a79c48f3a4602d907ffdaef196e Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 14 Aug 2024 23:45:34 +0100 Subject: [PATCH 19/23] Well, well, well --- wasm-calc11/src/Calc/Typecheck/Infer.hs | 11 +++- .../src/Calc/Typecheck/Patterns/Annihilate.hs | 8 +-- .../src/Calc/Typecheck/Patterns/Generate.hs | 65 +++++++++++++++--- .../src/Calc/Typecheck/Patterns/Validate.hs | 18 +++-- .../test/Test/Typecheck/PatternsSpec.hs | 66 ++++++++++++++----- .../test/Test/Typecheck/TypecheckSpec.hs | 1 - wasm-calc11/test/Test/Wasm/WasmSpec.hs | 4 +- 7 files changed, 131 insertions(+), 42 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 3933b8bf..242c077a 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -451,9 +451,13 @@ checkLet maybeReturnTy ann pat expr rest = do case maybeReturnTy of Just returnTy -> check returnTy rest Nothing -> infer rest - case validatePatterns ann [typedPat] of + + env <- ask + case validatePatterns env ann [typedPat] of Right _ -> pure () - Left patternMatchError -> throwError (PatternMatchError patternMatchError) + Left patternMatchError -> + throwError (PatternMatchError patternMatchError) + pure $ ELet (getOuterAnnotation typedRest $> ann) typedPat typedExpr typedRest checkMatch :: Maybe (Type ann) -> ann -> Expr ann -> NE.NonEmpty (Pattern ann, Expr ann) -> TypecheckM ann (Expr (Type ann)) @@ -469,7 +473,8 @@ checkMatch maybeTy ann matchExpr pats = do elabPats <- traverse withPair pats let allTypes = getOuterAnnotation . snd <$> elabPats typ <- combineMany allTypes - case validatePatterns ann (fst <$> NE.toList elabPats) of + env <- ask + case validatePatterns env ann (fst <$> NE.toList elabPats) of Right _ -> pure () Left patternMatchError -> throwError (PatternMatchError patternMatchError) pure (EMatch (mapOuterTypeAnnotation (const ann) typ) elabExpr elabPats) diff --git a/wasm-calc11/src/Calc/Typecheck/Patterns/Annihilate.hs b/wasm-calc11/src/Calc/Typecheck/Patterns/Annihilate.hs index 916d7504..72ed08fd 100644 --- a/wasm-calc11/src/Calc/Typecheck/Patterns/Annihilate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Patterns/Annihilate.hs @@ -31,10 +31,10 @@ annihilate l r = (PTuple _ a as, PTuple _ b bs) -> let allPairs = zip ([a] <> NE.toList as) ([b] <> NE.toList bs) in annihilateAll allPairs - {- (PConstructor _ tyConA argsA, PConstructor _ tyConB argsB) -> - (tyConA == tyConB) - && annihilateAll - (zip argsA argsB) -} + (PConstructor _ tyConA argsA, PConstructor _ tyConB argsB) -> + (tyConA == tyConB) + && annihilateAll + (zip argsA argsB) (PTuple _ a as, _) -> isComplete a && getAll (foldMap (All . isComplete) as) _ -> False diff --git a/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs b/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs index 2c8b9209..8b097a35 100644 --- a/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs @@ -1,15 +1,19 @@ {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE NamedFieldPuns #-} module Calc.Typecheck.Patterns.Generate ( generate, ) where +import Calc.Typecheck.Types +import Calc.Types.Constructor import Calc.Types.Pattern import Calc.Types.Prim import Calc.Types.Type import Data.Functor (void) import qualified Data.List.NonEmpty as NE +import qualified Data.Map.Strict as M import qualified Data.Set as S generateFromType :: Type ann -> S.Set (Pattern ()) @@ -17,26 +21,67 @@ generateFromType (TPrim _ TBool) = S.fromList [PLiteral () (PBool True), PLitera generateFromType (TPrim _ _) = S.singleton (PWildcard ()) generateFromType _ = mempty +-- generateFromType, except if we get nothing, we return PWildcard, +-- to stop cartesian product being eliminated by empty value +safeGenerateFromType :: Type ann -> S.Set (Pattern ()) +safeGenerateFromType ty = + let pats = generateFromType ty + in if S.null pats then S.singleton (PWildcard ()) else pats + -- generateFromPattern, except if we get nothing, we return ourselves, -- to stop cartesian product being eliminated by empty value -safeGenerateFromPattern :: Pattern (Type ann) -> S.Set (Pattern ()) -safeGenerateFromPattern pat = - let pats = generateFromPattern pat +safeGenerateFromPattern :: TypecheckEnv ann -> Pattern (Type ann) -> S.Set (Pattern ()) +safeGenerateFromPattern env pat = + let pats = generateFromPattern env pat in if S.null pats then S.singleton (void pat) else pats -generateFromPattern :: Pattern (Type ann) -> S.Set (Pattern ()) -generateFromPattern (PLiteral ty _) = +generateFromPattern :: TypecheckEnv ann -> Pattern (Type ann) -> S.Set (Pattern ()) +generateFromPattern _ (PLiteral ty _) = generateFromType ty -generateFromPattern (PTuple _ty patA patAs) = +generateFromPattern env (PTuple _ty patA patAs) = let pats = patA : NE.toList patAs - manyRows = traverse (fmap void . S.toList . safeGenerateFromPattern) pats + manyRows = traverse (fmap void . S.toList . safeGenerateFromPattern env) pats fromRow patList = case patList of (a : b : bs) -> S.singleton $ PTuple () a (b NE.:| bs) other -> error (show other) in foldMap fromRow manyRows -generateFromPattern pat = S.singleton (void pat) +generateFromPattern env@(TypecheckEnv {tceDataTypes}) (PConstructor _ty constructor pats) = + let generatedPatsForThisConstructor = + traverse (fmap void . S.toList . safeGenerateFromPattern env) pats + fromRow patList = + S.singleton $ PConstructor () constructor patList + patternsForThisConstructors = + foldMap fromRow generatedPatsForThisConstructor + + otherConstructors = findMatches tceDataTypes constructor + otherPatterns = foldMap + ( \(cn,tys) -> + let generatedPats = traverse (fmap void . S.toList . safeGenerateFromType) tys + fromRow2 patList = + S.singleton $ PConstructor () cn patList + in foldMap fromRow2 generatedPats + ) + otherConstructors + in patternsForThisConstructors <> otherPatterns +generateFromPattern _ pat = S.singleton (void pat) + +findMatches :: + M.Map Constructor (TCDataType ann) -> + Constructor -> + S.Set (Constructor,[Type ()]) +findMatches tceDataTypes constructor = + case M.lookup constructor tceDataTypes of + Just (TCDataType {tcdtName}) -> + let matchesDataName (TCDataType {tcdtName = thisDataType}) = + tcdtName == thisDataType + extract (cn, TCDataType { tcdtArgs}) = (cn,void <$> tcdtArgs) + in S.fromList $ extract <$> M.toList (M.filter matchesDataName tceDataTypes) + Nothing -> error "sdfsdf" -- | generate all the patterns, then remove ourselves -generate :: Pattern (Type ann) -> S.Set (Pattern ()) -generate pat = S.difference (generateFromPattern pat) (S.singleton $ void pat) +generate :: TypecheckEnv ann -> Pattern (Type ann) -> S.Set (Pattern ()) +generate env pat = + S.difference + (generateFromPattern env pat) + (S.singleton $ void pat) diff --git a/wasm-calc11/src/Calc/Typecheck/Patterns/Validate.hs b/wasm-calc11/src/Calc/Typecheck/Patterns/Validate.hs index 8e0e2615..772887f1 100644 --- a/wasm-calc11/src/Calc/Typecheck/Patterns/Validate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Patterns/Validate.hs @@ -11,6 +11,7 @@ import Calc.TypeUtils import Calc.Typecheck.Error.PatternMatchError import Calc.Typecheck.Patterns.Annihilate import Calc.Typecheck.Patterns.Generate +import Calc.Typecheck.Types import Calc.Types.Pattern import Calc.Types.Type import Control.Monad.Except @@ -22,16 +23,17 @@ import qualified Data.Set as S validatePatterns :: ( MonadError (PatternMatchError ann) m ) => + TypecheckEnv ann -> ann -> [Pattern (Type ann)] -> m () -validatePatterns ann patterns = do - let missing = missingPatterns patterns +validatePatterns env ann patterns = do + let missing = missingPatterns env patterns case missing of [] -> pure () _ -> throwError (MissingPatterns ann missing) - let redundant = redundantPatterns patterns + let redundant = redundantPatterns env patterns case redundant of [] -> pure () _ -> do @@ -40,19 +42,21 @@ validatePatterns ann patterns = do -- | given a list of patterns, return a list of missing patterns missingPatterns :: + TypecheckEnv ann -> [Pattern (Type ann)] -> [Pattern ()] -missingPatterns patterns = - let generated = mconcat $ generate <$> patterns +missingPatterns env patterns = + let generated = mconcat $ generate env <$> patterns in nub $ foldr (annihilatePattern . void) (S.toList generated) patterns ----- what about redundent stuff? redundantPatterns :: + TypecheckEnv ann -> [Pattern (Type ann)] -> [Pattern (Type ann)] -redundantPatterns patterns = do - let generated = mconcat $ generate <$> patterns +redundantPatterns env patterns = do + let generated = mconcat $ generate env <$> patterns originalPatterns = void <$> patterns -- add index, the first pattern is never redundant patternsWithIndex = zip patterns ([0 ..] :: [Int]) diff --git a/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs b/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs index edaa98e9..ffaac52d 100644 --- a/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs @@ -6,10 +6,13 @@ module Test.Typecheck.PatternsSpec (spec) where import Calc.Parser import Calc.Typecheck import Calc.Typecheck.Patterns +import Calc.Types.DataName import Control.Monad import Data.Foldable (traverse_) +import qualified Data.Map.Strict as M import qualified Data.Set as S import qualified Data.Text as T +import Test.Helpers import Test.Hspec spec :: Spec @@ -34,7 +37,9 @@ spec = do "(_,False,True)", "(_,True,False)" ] - ) + ), + ("Red", "Colour", ["Green", "Blue"]), + ("Nothing", "Maybe", ["Just(_)"]) ] describe "Successfully generates patterns" $ do @@ -45,7 +50,10 @@ spec = do [ (["_"], "a", []), (["True"], "Boolean", ["False"]), (["True", "False"], "Boolean", []), - (["1", "2", "3"], "Int32", ["_"]) + (["1", "2", "3"], "Int32", ["_"]), + (["Just(Just(1))"], "Maybe(Maybe(Int32))",["Just(_)","Just(Just(_))","Just(Nothing)","Nothing"]), + (["Just(Just(_))"], "Maybe(Maybe(Int32))",["Just(_)","Just(Nothing)","Nothing"]) + ] describe "Successfully returns missing patterns" $ do @@ -57,7 +65,8 @@ spec = do (["True", "False"], "Boolean", []), (["_", "1"], "Int32", ["1"]), (["1", "_"], "Int32", []), - (["1", "2", "_"], "Int32", []) + (["1", "2", "_"], "Int32", []), + (["Just(_)", "Just(1)"], "Maybe(Int32)", ["Just(1)"]) ] describe "Successfully returns redundant patterns" $ do @@ -70,7 +79,7 @@ testGeneratePattern (patStr, typeStr, expectedStrs) = do ty = fromRight $ parseTypeAndFormatError typeStr typedPat = fromRight $ runTC (checkPattern ty pat) expected = S.fromList $ fromRight . parsePatternAndFormatError <$> expectedStrs - generate typedPat `shouldBe` S.map void expected + generate typecheckEnv typedPat `shouldBe` S.map void expected testMissingPatterns :: ([T.Text], T.Text, [T.Text]) -> Spec testMissingPatterns (patStrs, typeStr, expectedStrs) = do @@ -79,7 +88,7 @@ testMissingPatterns (patStrs, typeStr, expectedStrs) = do ty = fromRight $ parseTypeAndFormatError typeStr typedPats = fromRight $ runTC (traverse (checkPattern ty) pats) expected = fromRight . parsePatternAndFormatError <$> expectedStrs - missingPatterns typedPats `shouldBe` void <$> expected + missingPatterns typecheckEnv typedPats `shouldBe` void <$> expected testRedundantPatterns :: ([T.Text], T.Text, [T.Text]) -> Spec testRedundantPatterns (patStrs, typeStr, expectedStrs) = do @@ -88,18 +97,45 @@ testRedundantPatterns (patStrs, typeStr, expectedStrs) = do ty = fromRight $ parseTypeAndFormatError typeStr typedPats = fromRight $ runTC (traverse (checkPattern ty) pats) expected = fromRight . parsePatternAndFormatError <$> expectedStrs - void <$> redundantPatterns typedPats `shouldBe` void <$> expected + void <$> redundantPatterns typecheckEnv typedPats `shouldBe` void <$> expected -runTC :: TypecheckM ann a -> Either (TypeError ann) a -runTC = - runTypecheckM - ( TypecheckEnv - { tceVars = mempty, - tceGenerics = mempty, - tceMemoryLimit = 0, - tceDataTypes = mempty +typecheckEnv :: (Monoid ann) => TypecheckEnv ann +typecheckEnv = + TypecheckEnv + { tceVars = mempty, + tceGenerics = mempty, + tceMemoryLimit = 0, + tceDataTypes = + M.fromList + [ ("Red", colourType), + ("Green", colourType), + ("Blue", colourType), + ("Just", justType), + ("Nothing", nothingType) + ] + } + where + colourType = + TCDataType + { tcdtName = DataName "Colour", + tcdtGenerics = mempty, + tcdtArgs = mempty + } + justType = + TCDataType + { tcdtName = DataName "Maybe", + tcdtGenerics = ["a"], + tcdtArgs = [tyVar "a"] } - ) + nothingType = + TCDataType + { tcdtName = DataName "Maybe", + tcdtGenerics = ["a"], + tcdtArgs = [] + } + +runTC :: (Monoid ann) => TypecheckM ann a -> Either (TypeError ann) a +runTC = runTypecheckM typecheckEnv fromRight :: (Show e) => Either e a -> a fromRight = \case diff --git a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs index a0e8504c..fa973620 100644 --- a/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/TypecheckSpec.hs @@ -259,7 +259,6 @@ spec = do [ "type List = Cons(a, List(a)) | Nil", "function main() -> Int32 { let _ = Cons(True, Cons((42:Int32),Nil)); 100 }" ] - ] describe "Failing typechecking modules" $ do traverse_ testFailingModule failing diff --git a/wasm-calc11/test/Test/Wasm/WasmSpec.hs b/wasm-calc11/test/Test/Wasm/WasmSpec.hs index 60128fa1..88de1ad2 100644 --- a/wasm-calc11/test/Test/Wasm/WasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/WasmSpec.hs @@ -385,13 +385,13 @@ spec = do ), ( joinLines [ "type Maybe = Just(a) | Nothing", - asTest "case Just(Box((100: Int64))) { Just(Box(a)) -> a + 1, Nothing -> 0 }" + asTest "case Just(Box((100: Int64))) { Just(Box(a)) -> a + 1, _ -> 0 }" ], Wasm.VI64 101 ), ( joinLines [ "type Maybe = Just(a) | Nothing", - asTest "case Just(Just(Box((100: Int64)))) { Just(Just(Box(a))) -> a + 1, Nothing -> 0 }" + asTest "case Just(Just(Box((100: Int64)))) { Just(Just(Box(a))) -> a + 1, _ -> 0 }" ], Wasm.VI64 101 ), From 58e4df15b39a68c95a10117ae34cf610503d6f6e Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Wed, 14 Aug 2024 23:51:36 +0100 Subject: [PATCH 20/23] Linties --- wasm-calc11/src/Calc/Typecheck/Helpers.hs | 1 - wasm-calc11/src/Calc/Typecheck/Infer.hs | 3 +- .../src/Calc/Typecheck/Patterns/Generate.hs | 31 ++++++++++--------- .../test/Test/Typecheck/PatternsSpec.hs | 5 ++- wasm-calc11/test/Test/Wasm/FromWasmSpec.hs | 27 +++++++--------- 5 files changed, 31 insertions(+), 36 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index 9efb46d8..a1adf253 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -1,6 +1,5 @@ {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} module Calc.Typecheck.Helpers diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 242c077a..53ca1098 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE LambdaCase #-} - module Calc.Typecheck.Infer ( infer, check, @@ -473,6 +471,7 @@ checkMatch maybeTy ann matchExpr pats = do elabPats <- traverse withPair pats let allTypes = getOuterAnnotation . snd <$> elabPats typ <- combineMany allTypes + env <- ask case validatePatterns env ann (fst <$> NE.toList elabPats) of Right _ -> pure () diff --git a/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs b/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs index 8b097a35..b8fb34e1 100644 --- a/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs @@ -47,35 +47,36 @@ generateFromPattern env (PTuple _ty patA patAs) = other -> error (show other) in foldMap fromRow manyRows generateFromPattern env@(TypecheckEnv {tceDataTypes}) (PConstructor _ty constructor pats) = - let generatedPatsForThisConstructor = + let generatedPatsForThisConstructor = traverse (fmap void . S.toList . safeGenerateFromPattern env) pats - fromRow patList = + fromRow patList = S.singleton $ PConstructor () constructor patList - patternsForThisConstructors = + patternsForThisConstructors = foldMap fromRow generatedPatsForThisConstructor otherConstructors = findMatches tceDataTypes constructor - otherPatterns = foldMap - ( \(cn,tys) -> - let generatedPats = traverse (fmap void . S.toList . safeGenerateFromType) tys - fromRow2 patList = - S.singleton $ PConstructor () cn patList - in foldMap fromRow2 generatedPats - ) - otherConstructors - in patternsForThisConstructors <> otherPatterns + otherPatterns = + foldMap + ( \(cn, tys) -> + let generatedPats = traverse (fmap void . S.toList . safeGenerateFromType) tys + fromRow2 patList = + S.singleton $ PConstructor () cn patList + in foldMap fromRow2 generatedPats + ) + otherConstructors + in patternsForThisConstructors <> otherPatterns generateFromPattern _ pat = S.singleton (void pat) findMatches :: M.Map Constructor (TCDataType ann) -> Constructor -> - S.Set (Constructor,[Type ()]) + S.Set (Constructor, [Type ()]) findMatches tceDataTypes constructor = case M.lookup constructor tceDataTypes of Just (TCDataType {tcdtName}) -> let matchesDataName (TCDataType {tcdtName = thisDataType}) = - tcdtName == thisDataType - extract (cn, TCDataType { tcdtArgs}) = (cn,void <$> tcdtArgs) + tcdtName == thisDataType + extract (cn, TCDataType {tcdtArgs}) = (cn, void <$> tcdtArgs) in S.fromList $ extract <$> M.toList (M.filter matchesDataName tceDataTypes) Nothing -> error "sdfsdf" diff --git a/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs b/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs index ffaac52d..ab4030ae 100644 --- a/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs +++ b/wasm-calc11/test/Test/Typecheck/PatternsSpec.hs @@ -51,9 +51,8 @@ spec = do (["True"], "Boolean", ["False"]), (["True", "False"], "Boolean", []), (["1", "2", "3"], "Int32", ["_"]), - (["Just(Just(1))"], "Maybe(Maybe(Int32))",["Just(_)","Just(Just(_))","Just(Nothing)","Nothing"]), - (["Just(Just(_))"], "Maybe(Maybe(Int32))",["Just(_)","Just(Nothing)","Nothing"]) - + (["Just(Just(1))"], "Maybe(Maybe(Int32))", ["Just(_)", "Just(Just(_))", "Just(Nothing)", "Nothing"]), + (["Just(Just(_))"], "Maybe(Maybe(Int32))", ["Just(_)", "Just(Nothing)", "Nothing"]) ] describe "Successfully returns missing patterns" $ do diff --git a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs index 1c177e11..4fedf1e6 100644 --- a/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs +++ b/wasm-calc11/test/Test/Wasm/FromWasmSpec.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} @@ -41,19 +40,19 @@ spec = do describe "getOffsetListForConstructor" $ do it "Construct with single item" $ do - flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "Maybe(Int8)") "Just") + evalStateT (getOffsetListForConstructor (unsafeTy "Maybe(Int8)") "Just") exprState `shouldBe` Right [1, 2] it "Construct with two items" $ do - flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8,Int64)") "These") + evalStateT (getOffsetListForConstructor (unsafeTy "These(Int8,Int64)") "These") exprState `shouldBe` Right [1, 2, 10] it "Construct with two items" $ do - flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "These(Int8, Int64)") "This") + evalStateT (getOffsetListForConstructor (unsafeTy "These(Int8, Int64)") "This") exprState `shouldBe` Right [1, 2] it "Recursive type" $ do - flip evalStateT exprState (getOffsetListForConstructor (unsafeTy "List(Int64)") "Cons") + evalStateT (getOffsetListForConstructor (unsafeTy "List(Int64)") "Cons") exprState `shouldBe` Right [1, 9, 13] describe "calculateMonomorphisedTypes" $ do @@ -125,11 +124,10 @@ spec = do ] traverse_ ( \(tyString, wasmFunc) -> do - it (show tyString) $ do - flip - evalStateT - exprState + it (show tyString) $ + evalStateT (createDropFunction 1 (unsafeTy tyString)) + exprState `shouldBe` Right wasmFunc ) testVals @@ -157,11 +155,10 @@ spec = do traverse_ ( \(tyString, paths) -> do - it (show tyString) $ do - flip - evalStateT - exprState + it (show tyString) $ + evalStateT (typeToDropPaths (unsafeTy tyString) id) + exprState `shouldBe` Right paths ) testVals @@ -204,8 +201,8 @@ spec = do ] traverse_ ( \(predicate, val, expected) -> - it (show predicate) $ do - flip evalStateT exprState (predicateToWasm @_ @() val predicate) + it (show predicate) $ + evalStateT (predicateToWasm @_ @() val predicate) exprState `shouldBe` Right expected ) testVals From 7f14c1865af41f158171dd03e4b45b0bf0abae44 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Thu, 15 Aug 2024 08:54:08 +0100 Subject: [PATCH 21/23] Revert demo --- wasm-calc11/demo/draw.calc | 26 +++++++++----------------- 1 file changed, 9 insertions(+), 17 deletions(-) diff --git a/wasm-calc11/demo/draw.calc b/wasm-calc11/demo/draw.calc index 321a93de..79e8d7dc 100644 --- a/wasm-calc11/demo/draw.calc +++ b/wasm-calc11/demo/draw.calc @@ -1,7 +1,5 @@ global mut index: Int64 = 1 -type Color = Greyscale(Int64) | RGB(Int64, Int64, Int64) - import imports.draw as draw( x: Int64, y: Int64, r: Int64, g: Int64, b: Int64 ) -> Void @@ -19,32 +17,26 @@ function clamp( ) -> Int64 { min(floor, max(ceiling, value))} function drawBounded( - x: Int64, y: Int64, color: Color -) -> Color { + x: Int64, y: Int64, color: (Int64,Int64,Int64) +) -> (Int64,Int64,Int64) { let maxWidth: Int64 = 600; let maxHeight: Int64 = 600; - let (r, g, b) = case color { - RGB(r, g, b) -> (r, g, b), - Greyscale(grey) -> (grey, grey, grey) - }; + let (r,g,b) = color; draw( clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b ); - RGB(r, g, b) + (r,g,b) } -function cycle(color: Color) -> Color { - case color { - RGB(r, g, b) -> RGB(g, b, r), - Greyscale(grey) -> Greyscale(grey) - } -} +function cycle(color: (Int64,Int64,Int64)) -> (Int64, +Int64, +Int64) { let (r,g,b) = color; (g,b,r)} -function initial(index: Int64) -> Color { +function initial(index: Int64) -> (Int64,Int64,Int64) { let r = clamp(0, 255, index * 2); let g = clamp(0, 255, 255 - r); let b = clamp(0, 255, r * 3); - RGB(r, g, b) + (r,g,b) } export function test() -> Void { From b89ff5f6e01946ceba6cd81b2ed2747dfd190f4b Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Thu, 15 Aug 2024 09:36:56 +0100 Subject: [PATCH 22/23] Get rid of rando errors --- .../src/Calc/Typecheck/Error/TypeError.hs | 87 +++++++++++++++++++ wasm-calc11/src/Calc/Typecheck/Infer.hs | 15 ++-- .../src/Calc/Typecheck/Patterns/Generate.hs | 2 +- 3 files changed, 96 insertions(+), 8 deletions(-) diff --git a/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs b/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs index 1beb0f11..5cc83859 100644 --- a/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs +++ b/wasm-calc11/src/Calc/Typecheck/Error/TypeError.hs @@ -42,6 +42,10 @@ data TypeError ann | ConstructorNotFound ann Constructor | UnknownGenericInConstructor ann Constructor TypeVar | PatternMatchError (PatternMatchError ann) + | DataTypeMismatch ann DataName DataName -- expected, actual + | StoringNonPrimitiveType ann (Type ann) + | LoadingNonPrimitiveType ann (Type ann) + | UnknownLoadType ann deriving stock (Eq, Ord, Show) positionFromAnnotation :: @@ -70,6 +74,69 @@ typeErrorDiagnostic input e = in case e of (PatternMatchError patternMatchError) -> patternMatchErrorDiagnostic input patternMatchError + (UnknownLoadType ann) -> + Diag.addReport diag $ + Diag.Err + Nothing + ( prettyPrint "Can't load into unknown type." + ) + ( catMaybes + [ (,) + <$> positionFromAnnotation + filename + input + ann + <*> pure + ( Diag.This + ( prettyPrint + "Consider providing a type annotation" + ) + ) + ] + ) + [] + (StoringNonPrimitiveType ann ty) -> + Diag.addReport diag $ + Diag.Err + Nothing + ( prettyPrint "Can only store primitive types" + ) + ( catMaybes + [ (,) + <$> positionFromAnnotation + filename + input + ann + <*> pure + ( Diag.This + ( prettyPrint $ + "This is trying to store " <> PP.pretty ty + ) + ) + ] + ) + [] + (LoadingNonPrimitiveType ann ty) -> + Diag.addReport diag $ + Diag.Err + Nothing + ( prettyPrint "Can only load primitive types" + ) + ( catMaybes + [ (,) + <$> positionFromAnnotation + filename + input + ann + <*> pure + ( Diag.This + ( prettyPrint $ + "This is trying to load " <> PP.pretty ty + ) + ) + ] + ) + [] (ExpectedInteger ann tyPrim) -> Diag.addReport diag $ Diag.Err @@ -154,6 +221,26 @@ typeErrorDiagnostic input e = ] ) [] + (DataTypeMismatch ann expected actual) -> + Diag.addReport diag $ + Diag.Err + Nothing + ( prettyPrint $ "Unexpected data type. Found " <> PP.pretty actual + ) + ( catMaybes + [ (,) + <$> positionFromAnnotation + filename + input + ann + <*> pure + ( Diag.This + ( prettyPrint $ "Expected " <> PP.pretty expected + ) + ) + ] + ) + [] (ConstructorNotFound ann constructor) -> Diag.addReport diag $ Diag.Err diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 53ca1098..9db12f98 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -70,8 +70,8 @@ check ty expr = do pure (mapOuterExprAnnotation (const unifiedTy) exprA) checkLoad :: Maybe (Type ann) -> ann -> Expr ann -> TypecheckM ann (Expr (Type ann)) -checkLoad Nothing _ann _index = - error "Can't infer ELoad type" +checkLoad Nothing ann _index = + throwError (UnknownLoadType ann) checkLoad (Just ty) ann index = do typedIndex <- check (TPrim ann TInt32) index _memLimit <- asks tceMemoryLimit @@ -82,7 +82,7 @@ checkLoad (Just ty) ann index = do -} if isNumber ty then pure $ ELoad (ty $> ann) typedIndex - else error "can only load primitive values" + else throwError (LoadingNonPrimitiveType ann ty) -- | store always returns Void checkStore :: @@ -101,7 +101,7 @@ checkStore maybeTy ann index expr = do ManualMemoryAccessOutsideLimit ann memLimit index -} unless (isNumber $ getOuterAnnotation typedExpr) $ - error "can only store primitive values" + throwError (StoringNonPrimitiveType ann (getOuterAnnotation typedExpr)) let tyVoid = TPrim ann TVoid case maybeTy of Just ty -> void (unify tyVoid ty) @@ -351,7 +351,7 @@ checkPattern (TConstructor _ tyDataName tyArgs) (PConstructor ann constructor pa lookupConstructor ann constructor unless (tyDataName == dataTypeName) $ - error "wrong" + throwError (DataTypeMismatch ann tyDataName dataTypeName) filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs @@ -403,9 +403,10 @@ checkConstructor maybeTy ann constructor args = do lookupConstructor ann constructor (typedArgs, fallbackTypes) <- case maybeTy of - Just (tyCons, tyArgs) -> do + Just (tyDataName, tyArgs) -> do -- we have a type signature to check this against - unless (tyCons == dataTypeName) $ error "wrong" + unless (tyDataName == dataTypeName) $ + throwError (DataTypeMismatch ann tyDataName dataTypeName) filtered <- matchConstructorTypesToArgs constructor dataTypeVars tyArgs dataTypeArgs diff --git a/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs b/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs index b8fb34e1..44e9ea48 100644 --- a/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs +++ b/wasm-calc11/src/Calc/Typecheck/Patterns/Generate.hs @@ -78,7 +78,7 @@ findMatches tceDataTypes constructor = tcdtName == thisDataType extract (cn, TCDataType {tcdtArgs}) = (cn, void <$> tcdtArgs) in S.fromList $ extract <$> M.toList (M.filter matchesDataName tceDataTypes) - Nothing -> error "sdfsdf" + Nothing -> mempty -- | generate all the patterns, then remove ourselves generate :: TypecheckEnv ann -> Pattern (Type ann) -> S.Set (Pattern ()) From 9ada7f89a6f1b9de6042f5e1378729c61a0fc8b8 Mon Sep 17 00:00:00 2001 From: Daniel Harvey Date: Thu, 15 Aug 2024 10:23:38 +0100 Subject: [PATCH 23/23] That'll do --- wasm-calc11/demo/draw.calc | 8 ++++---- wasm-calc11/src/Calc/Typecheck/Generalise.hs | 12 ++++++------ wasm-calc11/src/Calc/Typecheck/Helpers.hs | 7 +++---- wasm-calc11/src/Calc/Typecheck/Infer.hs | 7 +++++-- wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs | 7 ++++--- 5 files changed, 22 insertions(+), 19 deletions(-) diff --git a/wasm-calc11/demo/draw.calc b/wasm-calc11/demo/draw.calc index 79e8d7dc..304b037f 100644 --- a/wasm-calc11/demo/draw.calc +++ b/wasm-calc11/demo/draw.calc @@ -21,22 +21,22 @@ function drawBounded( ) -> (Int64,Int64,Int64) { let maxWidth: Int64 = 600; let maxHeight: Int64 = 600; - let (r,g,b) = color; + let (r, g, b) = color; draw( clamp(0, maxWidth, x), clamp(0, maxHeight, y), r, g, b ); - (r,g,b) + (r, g, b) } function cycle(color: (Int64,Int64,Int64)) -> (Int64, Int64, -Int64) { let (r,g,b) = color; (g,b,r)} +Int64) { let (r, g, b) = color; (g, b, r)} function initial(index: Int64) -> (Int64,Int64,Int64) { let r = clamp(0, 255, index * 2); let g = clamp(0, 255, 255 - r); let b = clamp(0, 255, r * 3); - (r,g,b) + (r, g, b) } export function test() -> Void { diff --git a/wasm-calc11/src/Calc/Typecheck/Generalise.hs b/wasm-calc11/src/Calc/Typecheck/Generalise.hs index 6cc074ed..43712377 100644 --- a/wasm-calc11/src/Calc/Typecheck/Generalise.hs +++ b/wasm-calc11/src/Calc/Typecheck/Generalise.hs @@ -10,7 +10,7 @@ import Calc.Typecheck.Types import Calc.Types.Type import Calc.Types.TypeVar import Control.Monad.State -import qualified Data.HashMap.Strict as HM +import qualified Data.Map.Strict as M import qualified Data.Set as S import GHC.Natural @@ -20,10 +20,10 @@ freshUnificationVariable = do modify (\tcs -> tcs {tcsUnique = tcsUnique tcs + 1}) gets tcsUnique -allFresh :: S.Set TypeVar -> TypecheckM ann (HM.HashMap TypeVar Natural) +allFresh :: S.Set TypeVar -> TypecheckM ann (M.Map TypeVar Natural) allFresh generics = let freshOne typeVar = - HM.singleton typeVar <$> freshUnificationVariable + M.singleton typeVar <$> freshUnificationVariable in mconcat <$> traverse freshOne (S.toList generics) -- given a type, replace anything that should be generic with unification @@ -34,7 +34,7 @@ generalise generics ty = fresh <- allFresh generics pure $ generaliseInternal fresh ty -generaliseMany :: S.Set TypeVar -> [Type ann] -> TypecheckM ann (HM.HashMap TypeVar Natural, [Type ann]) +generaliseMany :: S.Set TypeVar -> [Type ann] -> TypecheckM ann (M.Map TypeVar Natural, [Type ann]) generaliseMany generics tys = do fresh <- allFresh generics @@ -43,9 +43,9 @@ generaliseMany generics tys = -- given a type, replace anything that should be generic with unification -- variables so that we know to replace them with types easily -generaliseInternal :: HM.HashMap TypeVar Natural -> Type ann -> Type ann +generaliseInternal :: M.Map TypeVar Natural -> Type ann -> Type ann generaliseInternal fresh (TVar ann var) = - case HM.lookup var fresh of + case M.lookup var fresh of Just nat -> TUnificationVar ann nat Nothing -> error "oh no generalise error" diff --git a/wasm-calc11/src/Calc/Typecheck/Helpers.hs b/wasm-calc11/src/Calc/Typecheck/Helpers.hs index a1adf253..a8b49fbc 100644 --- a/wasm-calc11/src/Calc/Typecheck/Helpers.hs +++ b/wasm-calc11/src/Calc/Typecheck/Helpers.hs @@ -30,7 +30,6 @@ import Control.Monad.Reader import Control.Monad.State import Data.Foldable (traverse_) import qualified Data.HashMap.Strict as HM -import Data.Hashable import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as M import Data.Maybe (mapMaybe) @@ -201,7 +200,7 @@ calculateMonomorphisedTypes typeVars fnArgTys argTys fallbacks = do let fixedMap = flipMap fresh mapped = foldMap - ( \(k, a) -> case HM.lookup k fixedMap of + ( \(k, a) -> case M.lookup k fixedMap of Just tv -> M.singleton tv a Nothing -> mempty ) @@ -214,8 +213,8 @@ calculateMonomorphisedTypes typeVars fnArgTys argTys fallbacks = do Nothing -> Nothing pure $ mapMaybe fromTv typeVars -flipMap :: (Hashable v) => HM.HashMap k v -> HM.HashMap v k -flipMap = HM.fromList . fmap (\(k, v) -> (v, k)) . HM.toList +flipMap :: (Ord v) => M.Map k v -> M.Map v k +flipMap = M.fromList . fmap (\(k, v) -> (v, k)) . M.toList lookupConstructor :: ann -> diff --git a/wasm-calc11/src/Calc/Typecheck/Infer.hs b/wasm-calc11/src/Calc/Typecheck/Infer.hs index 9db12f98..2d1fb748 100644 --- a/wasm-calc11/src/Calc/Typecheck/Infer.hs +++ b/wasm-calc11/src/Calc/Typecheck/Infer.hs @@ -22,6 +22,7 @@ import Control.Monad.State import Data.Functor import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as M +import qualified Data.Set as S check :: Type ann -> Expr ann -> TypecheckM ann (Expr (Type ann)) check ty (EApply ann fn args) = @@ -419,14 +420,16 @@ checkConstructor maybeTy ann constructor args = do fallbackTypes ) Nothing -> do + (updates, newTys) <- generaliseMany (S.fromList dataTypeVars) dataTypeArgs + -- we have no type signature to check this against - typedArgs <- traverse infer args + typedArgs <- zipWithM check newTys args -- create fresh unification types (ie, guess!) to fill in any -- gaps. Ie, when inferring the type of `Nothing` we don't know -- what the `a` is in `Maybe`, but also, we don't care, so say -- "it's a thing, you can decide later" - fallbackTypes <- M.fromList <$> traverse (\var -> (,) var <$> (TUnificationVar ann <$> freshUnificationVariable)) dataTypeVars + let fallbackTypes = TUnificationVar ann <$> updates pure (typedArgs, fallbackTypes) diff --git a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs index b2fe818e..db1994d2 100644 --- a/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs +++ b/wasm-calc11/src/Calc/Wasm/FromExpr/Module.hs @@ -51,9 +51,10 @@ fromTest :: (Eq ann, Show ann) => M.Map FunctionName FromExprFunc -> M.Map Identifier FromExprGlobal -> + M.Map DataName (Data ()) -> Test (Type ann) -> Either FromWasmError WasmTest -fromTest funcMap globalMap (Test {tesName = Identifier testName, tesExpr}) = do +fromTest funcMap globalMap dataTypeMap (Test {tesName = Identifier testName, tesExpr}) = do (expr, fes) <- runStateT (fromExpr ((,Nothing) <$> tesExpr)) @@ -64,7 +65,7 @@ fromTest funcMap globalMap (Test {tesName = Identifier testName, tesExpr}) = do fesImports = mempty, fesFunctions = funcMap, fesGenerated = mempty, - fesDataTypes = mempty + fesDataTypes = dataTypeMap } ) @@ -209,7 +210,7 @@ fromModule wholeMod@(Module {mdDataTypes, mdMemory, mdTests, mdGlobals, mdImport wasmImports <- traverse fromImport mdImports - wasmTests <- traverse (fromTest funcMap globalMap) mdTests + wasmTests <- traverse (fromTest funcMap globalMap dataTypeMap) mdTests pure $ WasmModule