From e21950dba6dd1b50c917ac967202c368a3da52c0 Mon Sep 17 00:00:00 2001 From: RJ Date: Fri, 13 May 2022 14:55:44 +0100 Subject: [PATCH] effectalias init MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit desalias inline alias = effectname and typename | init merge into 1 construct ok; still 2 contexts merge type and effect aliases contexts effectname body desugared into effectname allow better printing Revert "desalias inline" This reverts commit 49a9a61591382ca4a15408b644c7673c8b325dcc. Revert "effectname body desugared into effectname" This reverts commit 51506157c10f54f6e6423de8317cff90484a741e. "effectname" in links-mode.el cleaning before pr re-cleaning effectname -> typename _::Kind Update bin/repl.ml Co-authored-by: Daniel Hillerström Update bin/repl.ml Co-authored-by: Daniel Hillerström Update bin/repl.ml Co-authored-by: Daniel Hillerström Update bin/repl.ml Co-authored-by: Daniel Hillerström Update bin/repl.ml Co-authored-by: Daniel Hillerström Update core/desugarDatatypes.mli Co-authored-by: Daniel Hillerström Update bin/repl.ml Co-authored-by: Daniel Hillerström Update core/defaultAliases.ml Co-authored-by: Daniel Hillerström Update core/desugarDatatypes.ml Co-authored-by: Daniel Hillerström Update core/desugarDatatypes.ml Co-authored-by: Daniel Hillerström rename alias_env -> tycon_env as originally Update core/desugarDatatypes.ml Co-authored-by: Daniel Hillerström idem fixes & add primary kind in aliases new error kind mismatch fix : embeded errors fixes fix : underscore in effect app various fixes short type in effectname + short fun non desugar comment Attempted workaround for #1136 (#1138) always desugar op type with type application correction tests default arg in repl Effect aliasing (#1141) I added the possibility to write effect aliases, similarly as what already exists for types. - there is a new keyword `effectname` - to write an alias for an effect row : `effectname MyEffectRow(a, ... ,e::Eff, ...) = { Op1 : type, ... | e }` the arguments being type variable of any kind (kinds other than type must be explicit) - we can have, as above, an open row (the row variable is a parameter of the effect alias) or a closed one (just do not write the `| e` - To use it in a signature or in another type or effect alias just apply it with the right arguments as for `typename` things. - In arrows, we can use them as row variables: `() -MyEffectRow(args)-> ()` (idem with `~>`) - However, due to lack of kind inference, row variables and aliases have to be used carefully so that links does not think they are of kind type. We need to write them most of the time between braces ` { | ... }`. For instance, if you have `effectname E(a::Eff) = {X : ... | a }` and a row variable `e::Eff`, you will have to write `E({ |e})`. (Idem for another effect alias instead of the variable). This makes the usage of several nested aliases a bit messy, it would be nice if we could avoid it. - We cannot write recursive effect aliases for now. In the branch `visitor`, I added another transformer that makes possible simple recursion by inlining a mu type in one pass. - For now the aliases are replaced by the row they correspond to : we do not keep aliases. - In the repl, effect alias definitions are printed but without the braces ! Rows are in general printed without braces and the alias body is a row. => this might need to be enhanced About implementation, I copied and then merged most of the time what existed for `typename`. Co-authored-by: Daniel Hillerström Fix assert error with relational lenses (#1143) The `Lens` type traversal was unimplemented and filled in with an `assert false`. As a result, all RL code fails. I don't think there is any really sensible default traversal due to the complexity of the Lens types, so I have just filled it in with the identity. This doesn't stop someone implementing a traversal -- they'll just need to write one for `Lens.Type.t` type and plug it in as usual. Make `custom_js_runtime` a multi option (#1146) Added the ability to link multiple custom js runtime files. Co-authored-by: s1908422 Co-authored-by: Daniel Hillerström Allow 'default' as an argument to settings in the REPL (#1147) Some settings has the value 'default'. Prior to this patch the value 'default' could not be written in the REPL, because it is token. This patch rectifies this problem by allowing the token 'default' to appear in settings argument position in the REPL. Co-authored-by: Daniel Hillerström Allow record extension in presence of temporal projections (#1129) * Allow record extension in presence of temporal projections This allows record extension to play nicely with temporal projections. I was forgetting that all arguments to reduce_artifacts are already eta-expanded, so we can work with record literals. Fixes #1124. * Allow extension to work with (shallow) temporal projections We don't have the full generality due to #1130, but this patch should allow record extension to be used on temporal projections on variables / record literals. Removal of unused headless testing (#1152) The headless testing has been unused for about a year, because it is unmaintained. Even though it is not used, it generates a ton of security warnings here on GitHub. I am not interested in dealing with those, therefore this patch removes the headless testing directory from the source tree. Attempted workaround for #1136 (#1138) always desugar op type with type application correction tests default arg in repl Option -> Maybe fix (#1142) The `Option -> Maybe` refactoring patch #1131 missed one instance: the `max` function. This patch changes the type signature of `max` to use `Maybe` rather than `Option`. Effect aliasing (#1141) I added the possibility to write effect aliases, similarly as what already exists for types. - there is a new keyword `effectname` - to write an alias for an effect row : `effectname MyEffectRow(a, ... ,e::Eff, ...) = { Op1 : type, ... | e }` the arguments being type variable of any kind (kinds other than type must be explicit) - we can have, as above, an open row (the row variable is a parameter of the effect alias) or a closed one (just do not write the `| e` - To use it in a signature or in another type or effect alias just apply it with the right arguments as for `typename` things. - In arrows, we can use them as row variables: `() -MyEffectRow(args)-> ()` (idem with `~>`) - However, due to lack of kind inference, row variables and aliases have to be used carefully so that links does not think they are of kind type. We need to write them most of the time between braces ` { | ... }`. For instance, if you have `effectname E(a::Eff) = {X : ... | a }` and a row variable `e::Eff`, you will have to write `E({ |e})`. (Idem for another effect alias instead of the variable). This makes the usage of several nested aliases a bit messy, it would be nice if we could avoid it. - We cannot write recursive effect aliases for now. In the branch `visitor`, I added another transformer that makes possible simple recursion by inlining a mu type in one pass. - For now the aliases are replaced by the row they correspond to : we do not keep aliases. - In the repl, effect alias definitions are printed but without the braces ! Rows are in general printed without braces and the alias body is a row. => this might need to be enhanced About implementation, I copied and then merged most of the time what existed for `typename`. Co-authored-by: Daniel Hillerström Fix assert error with relational lenses (#1143) The `Lens` type traversal was unimplemented and filled in with an `assert false`. As a result, all RL code fails. I don't think there is any really sensible default traversal due to the complexity of the Lens types, so I have just filled it in with the identity. This doesn't stop someone implementing a traversal -- they'll just need to write one for `Lens.Type.t` type and plug it in as usual. Make `custom_js_runtime` a multi option (#1146) Added the ability to link multiple custom js runtime files. Co-authored-by: s1908422 Co-authored-by: Daniel Hillerström wip Allow 'default' as an argument to settings in the REPL (#1147) Some settings has the value 'default'. Prior to this patch the value 'default' could not be written in the REPL, because it is token. This patch rectifies this problem by allowing the token 'default' to appear in settings argument position in the REPL. Co-authored-by: Daniel Hillerström Allow record extension in presence of temporal projections (#1129) * Allow record extension in presence of temporal projections This allows record extension to play nicely with temporal projections. I was forgetting that all arguments to reduce_artifacts are already eta-expanded, so we can work with record literals. Fixes #1124. * Allow extension to work with (shallow) temporal projections We don't have the full generality due to #1130, but this patch should allow record extension to be used on temporal projections on variables / record literals. Removal of unused headless testing (#1152) The headless testing has been unused for about a year, because it is unmaintained. Even though it is not used, it generates a ton of security warnings here on GitHub. I am not interested in dealing with those, therefore this patch removes the headless testing directory from the source tree. --- bin/driver.ml | 41 +- core/basicsettings.ml | 6 +- core/defaultAliases.ml | 6 +- core/desugarDatatypes.ml | 157 +- core/desugarEffects.ml | 144 +- core/desugarModules.ml | 6 +- core/desugarPages.ml | 2 +- core/desugarTypeVariables.ml | 8 +- core/errors.ml | 14 +- core/errors.mli | 6 + core/generalise.ml | 2 +- core/instantiate.ml | 11 +- core/irCheck.ml | 4 +- core/irTraversals.ml | 2 +- core/lens_type_conv.ml | 4 +- core/lexer.mll | 1 + core/lib.ml | 4 +- core/moduleUtils.ml | 4 +- core/parser.mly | 38 +- core/query/query.ml | 24 +- core/query/temporalQuery.ml | 9 +- core/sugarTraversals.ml | 84 +- core/sugarTraversals.mli | 18 +- core/sugartoir.ml | 2 +- core/sugartypes.ml | 17 +- core/transformSugar.ml | 20 +- core/typeSugar.ml | 30 +- core/typeUtils.ml | 4 +- core/types.ml | 91 +- core/types.mli | 5 +- core/typevarcheck.ml | 6 +- core/unify.ml | 4 +- core/webif.ml | 24 +- links-mode.el | 1 + tests/effectname.tests | 62 + tests/effectname/effect-same-name.links | 8 + tests/effectname/handler.links | 38 + tests/effectname/mutual.links | 7 + tests/effectname/nested-decl.links | 8 + tests/effectname/one.links | 6 + tests/effectname/recursive.links | 10 + tests/effectname/simple-decl.links | 16 + tests/effectname/two-nested.links | 9 + tests/effectname/two.links | 7 + tests/effectname/typenames.links | 12 + tests/effectname/underscore.links | 14 + tests/effectname/zero.links | 6 + tests/headless/.gitignore | 1 - tests/headless/README.md | 22 - tests/headless/browserDrivers.js | 26 - tests/headless/linksServerRunner.js | 73 - tests/headless/linksconfig | 5 - tests/headless/package-lock.json | 3459 ----------------- tests/headless/package.json | 25 - tests/headless/tests/buttons.test.js | 39 - .../tests/examples.dictSuggestUpdate.test.js | 74 - .../headless/tests/examples.factorial.test.js | 57 - tests/headless/tests/progress.test.js | 57 - tests/selenium-tests/selenium-suite.html | 12 - tests/selenium-tests/selenium-tests.html | 74 - 60 files changed, 752 insertions(+), 4174 deletions(-) create mode 100644 tests/effectname.tests create mode 100755 tests/effectname/effect-same-name.links create mode 100755 tests/effectname/handler.links create mode 100755 tests/effectname/mutual.links create mode 100755 tests/effectname/nested-decl.links create mode 100644 tests/effectname/one.links create mode 100755 tests/effectname/recursive.links create mode 100755 tests/effectname/simple-decl.links create mode 100755 tests/effectname/two-nested.links create mode 100755 tests/effectname/two.links create mode 100755 tests/effectname/typenames.links create mode 100755 tests/effectname/underscore.links create mode 100644 tests/effectname/zero.links delete mode 100644 tests/headless/.gitignore delete mode 100644 tests/headless/README.md delete mode 100644 tests/headless/browserDrivers.js delete mode 100644 tests/headless/linksServerRunner.js delete mode 100644 tests/headless/linksconfig delete mode 100644 tests/headless/package-lock.json delete mode 100644 tests/headless/package.json delete mode 100644 tests/headless/tests/buttons.test.js delete mode 100644 tests/headless/tests/examples.dictSuggestUpdate.test.js delete mode 100644 tests/headless/tests/examples.factorial.test.js delete mode 100644 tests/headless/tests/progress.test.js delete mode 100644 tests/selenium-tests/selenium-suite.html delete mode 100644 tests/selenium-tests/selenium-tests.html diff --git a/bin/driver.ml b/bin/driver.ml index f9ef75e1e..6f7c08cc7 100644 --- a/bin/driver.ml +++ b/bin/driver.ml @@ -235,30 +235,35 @@ module Phases = struct if Settings.get Basicsettings.System.link_js_runtime then begin Js_CodeGen.output oc Compiler.primitive_bindings; - let runtime_file = + let runtime_files = match Settings.get Basicsettings.System.custom_js_runtime with - | None -> - begin match Settings.get jslib_dir with - | None | Some "" -> + | [] -> + let file = + begin match Settings.get jslib_dir with + | None | Some "" -> begin Filename.concat (match Utility.getenv "LINKS_LIB" with - | None -> Filename.dirname Sys.executable_name - | Some path -> path) - (Filename.concat "js" "jslib.js") + | None -> Filename.dirname Sys.executable_name + | Some path -> path) + (Filename.concat "js" "jslib.js") end - | Some path -> Filename.concat path "jslib.js" - end - | Some file -> file + | Some path -> Filename.concat path "jslib.js" + end + in [file] + | files -> files in - let ic = - try open_in runtime_file - with Sys_error reason -> raise (Errors.cannot_open_file runtime_file reason) - in - try - Utility.IO.Channel.cat ic oc; - close_in ic - with e -> close_in ic; raise e + List.iter + (fun runtime_file -> + let ic = + try open_in runtime_file + with Sys_error reason -> raise (Errors.cannot_open_file runtime_file reason) + in + try + Utility.IO.Channel.cat ic oc; + close_in ic + with e -> close_in ic; raise e) + runtime_files; end; (* Copy contents of FFI files. *) List.iter diff --git a/core/basicsettings.ml b/core/basicsettings.ml index 95eb60fa2..724285728 100644 --- a/core/basicsettings.ml +++ b/core/basicsettings.ml @@ -116,11 +116,11 @@ module System = struct |> sync) let custom_js_runtime = - Settings.(option "custom_js_runtime" + Settings.(multi_option "custom_js_runtime" |> privilege `User |> synopsis "If link_js_runtime is set to true, then the JS compiler will link the provided file(s) rather than the standard Links JS runtime" - |> to_string from_string_option - |> convert (fun s -> Some s) + |> to_string string_of_paths + |> convert parse_paths |> hidden |> CLI.(add (long "Xcustom-js-runtime")) |> sync) diff --git a/core/defaultAliases.ml b/core/defaultAliases.ml index 54f127035..ab61de7f7 100644 --- a/core/defaultAliases.ml +++ b/core/defaultAliases.ml @@ -15,7 +15,7 @@ let alias_env : Types.tycon_environment = let wq, w = mk_arg () in let nq, n = mk_arg () in let th_alias_type = - `Alias ([rq; wq; nq], Types.make_tablehandle_alias (r, w, n)) + `Alias (pk_type, [rq; wq; nq], Types.make_tablehandle_alias (r, w, n)) in List.fold_left @@ -23,13 +23,13 @@ let alias_env : Types.tycon_environment = AliasEnv.bind name t env) AliasEnv.empty [ (* "String" , `Alias ([], `Application (Types.list, [`Type (`Primitive Primitive.Char)])); *) - "Xml" , `Alias ([], Types.Application (Types.list, [(PrimaryKind.Type, Types.Primitive Primitive.XmlItem)])); + "Xml" , `Alias (pk_type, [], Types.Application (Types.list, [(PrimaryKind.Type, Types.Primitive Primitive.XmlItem)])); "Event" , `Abstract Types.event; "List" , `Abstract Types.list; "Process" , `Abstract Types.process; "DomNode" , `Abstract Types.dom_node; "AP" , `Abstract Types.access_point; - "EndBang" , `Alias ([], Types.make_endbang_type); + "EndBang" , `Alias (pk_type, [], Types.make_endbang_type); "Socket" , `Abstract Types.socket; "ValidTime", `Abstract Types.valid_time_data; "TransactionTime", `Abstract Types.transaction_time_data; diff --git a/core/desugarDatatypes.ml b/core/desugarDatatypes.ml index cc89e2fbd..a3ade2ac6 100644 --- a/core/desugarDatatypes.ml +++ b/core/desugarDatatypes.ml @@ -45,6 +45,10 @@ object (self) (_, None) -> {< all_desugared = false >} | _ -> self + method! row' = function + (_, None) -> {< all_desugared = false >} + | _ -> self + method! type_arg' = function (_, None) -> {< all_desugared = false >} | _ -> self @@ -125,13 +129,9 @@ module Desugar = struct let t_kind = primary_kind_of_type_arg t in if q_kind <> t_kind then raise - (TypeApplicationKindMismatch - { pos; - name = tycon; - tyarg_number = i; - expected = PrimaryKind.to_string q_kind; - provided = PrimaryKind.to_string t_kind - }) + (type_application_kind_mismatch pos tycon i + (PrimaryKind.to_string q_kind) + (PrimaryKind.to_string t_kind)) else t in let type_args qs ts = @@ -149,10 +149,14 @@ module Desugar = struct raise (TypeApplicationArityMismatch { pos; name = tycon; expected = qn; provided = tn }) in begin match SEnv.find_opt tycon alias_env with - | None -> raise (UnboundTyCon (pos, tycon)) - | Some (`Alias (qs, _dt)) -> - let ts = match_quantifiers snd qs in - Instantiate.alias tycon ts alias_env + | None -> raise (unbound_tycon pos tycon) + | Some (`Alias (k, qs, _dt)) -> + if k = pk_type then + let ts = match_quantifiers snd qs in + Instantiate.alias tycon ts alias_env + else + raise (type_application_global_kind_mismatch pos tycon + "Type" (PrimaryKind.to_string k)) | Some (`Abstract abstype) -> let ts = match_quantifiers identity (Abstype.arity abstype) in Application (abstype, ts) @@ -209,6 +213,70 @@ module Desugar = struct let seed = let open Datatype in match rv with + | EffectApplication (name, ts) -> + let match_quantifiers : type a. (a -> Kind.t) -> a list -> Types.type_arg list = fun proj qs -> + let match_kinds i (q, t) = + let primary_kind_of_type_arg : Datatype.type_arg -> PrimaryKind.t = function + | Type _ -> PrimaryKind.Type + | Row _ -> PrimaryKind.Row + | Presence _ -> PrimaryKind.Presence + in + let q_kind, _ = proj q in + let t_kind = primary_kind_of_type_arg t in + if q_kind <> t_kind then + raise + (type_application_kind_mismatch node.pos name i + (PrimaryKind.to_string q_kind) + (PrimaryKind.to_string t_kind)) + else t + in + let type_args qs ts = + List.combine qs ts + |> List.mapi + (fun i (q,t) -> + let t = match_kinds i (q, t) in + type_arg alias_env t node) + in + let qn = List.length qs and tn = List.length ts in + if qn = tn then + type_args qs ts + else + raise (TypeApplicationArityMismatch { pos = node.pos; name = name; expected = qn; provided = tn }) + in + begin match SEnv.find_opt name alias_env with + | None -> raise (unbound_tycon node.pos name) + | Some (`Alias (k, qs, _r)) -> + if k = pk_row then + let ts = match_quantifiers snd qs in + begin match Instantiate.alias name ts alias_env with + | Alias(PrimaryKind.Row, _, body) -> body + | _ -> raise (internal_error "Instantiation failed") + end + else + raise (type_application_global_kind_mismatch node.pos name + "Row" (PrimaryKind.to_string k)) + | Some (`Abstract abstype) -> + let ts = match_quantifiers identity (Abstype.arity abstype) in + Application (abstype, ts) + | Some (`Mutual (qs, tygroup_ref)) -> + (* Check that the quantifiers / kinds match up, then generate + * a `RecursiveApplication. *) + let r_args = match_quantifiers snd qs in + let r_unwind args dual = + let _, body = StringMap.find name !tygroup_ref.type_map in + let body = Instantiate.recursive_application name qs args body in + if dual then dual_type body else body + in + let r_unique_name = name ^ string_of_int !tygroup_ref.id in + let r_linear () = StringMap.lookup name !tygroup_ref.linearity_map in + RecursiveApplication + { r_name = name; + r_dual = false; + r_unique_name; + r_quantifiers = List.map snd qs; + r_args; r_unwind; r_linear + } + end | Closed -> Types.make_empty_closed_row () | Open srv -> let rv = SugarTypeVar.get_resolved_row_exn srv in @@ -236,11 +304,16 @@ module Desugar = struct | Row r -> Row, row alias_env r node | Presence f -> Presence, fieldspec alias_env f node - - let datatype' alias_env ((dt, _) : datatype') = (dt, Some (datatype alias_env dt)) + let row' alias_env ((r, _) :row') = + (r, Some (row alias_env r (WithPos.make (Datatype.Effect r)))) (* should we keep the pos ? have a real node ? *) + + let aliasbody alias_env = function + | Typename dt' -> Typename (datatype' alias_env dt') + | Effectname r' -> Effectname (row' alias_env r') + let type_arg' alias_env ((ta, _) : type_arg') : type_arg' = let unlocated = WithPos.make Datatype.Unit in (ta, Some (type_arg alias_env ta unlocated)) @@ -288,6 +361,8 @@ object (self) method! datatype' node = (self, Desugar.datatype' alias_env node) + method! row' node = (self, Desugar.row' alias_env node) + method! type_arg' node = (self, Desugar.type_arg' alias_env node) method! phrasenode = function @@ -325,7 +400,7 @@ object (self) method! bindingnode = function - | Typenames ts -> + | Aliases ts -> (* Maps syntactic types in the recursive group to semantic types. *) (* This must be empty to start off with, because there's a cycle * in calculating the semantic types: we need the alias environment @@ -340,36 +415,43 @@ object (self) (* Add all type declarations in the group to the alias * environment, as mutuals. Quantifiers need to be desugared. *) - let ((mutual_env : tycon_spec SEnv.t), ts) = - List.fold_left (fun (alias_env, ts) {node=(t, args, (d, _)); pos} -> + let ((mutual_env : Types.tycon_environment), ts) = + List.fold_left (fun (alias_env, ts) {node=(t, args, b); pos} -> let qs = Desugar.desugar_quantifiers args in - let alias_env = SEnv.bind t (`Mutual (qs, tygroup_ref)) alias_env in - (alias_env, WithPos.make ~pos (t, args, (d, None)) :: ts)) + match b with + | Typename (d,_) -> + let alias_env = SEnv.bind t (`Mutual (qs, tygroup_ref)) alias_env in + (alias_env, WithPos.make ~pos (t, args, Typename (d, None)) :: ts) + | Effectname (r,_) -> + let alias_env = SEnv.bind t (`Mutual (qs, tygroup_ref)) alias_env in + (alias_env, WithPos.make ~pos (t, args, Effectname (r, None)) :: ts)) (alias_env, []) ts in (* Desugar all DTs, given the temporary new alias environment. *) let desugared_mutuals = - List.map (fun {node=(name, args, dt); pos} -> + List.map (fun {node=(name, args, b); pos} -> (* Desugar the datatype *) - let dt' = Desugar.datatype' mutual_env dt in (* Check if the datatype has actually been desugared *) - let (t, dt) = - match dt' with - | (t, Some dt) -> (t, dt) - | _ -> assert false in - WithPos.make ~pos (name, args, (t, Some dt)) + let b' = match Desugar.aliasbody mutual_env b with + | Typename (_, Some _) as b' -> b' + | Effectname (_, Some _) as b' -> b' + | _ -> raise (internal_error "Datatype not desugared") + in + WithPos.make ~pos (name, args, b') ) ts in (* Given the desugared datatypes, we now need to handle linearity. First, calculate linearity up to recursive application *) let (linearity_env, dep_graph) = List.fold_left (fun (lin_map, dep_graph) mutual -> - let (name, _, (_, dt)) = SourceCode.WithPos.node mutual in - let dt = OptionUtils.val_of dt in - let lin_map = StringMap.add name (not @@ Unl.type_satisfies dt) lin_map in - let deps = recursive_applications dt in - let dep_graph = (name, deps) :: dep_graph in - (lin_map, dep_graph) + match SourceCode.WithPos.node mutual with + | (name, _, Typename (_, dt)) + | (name, _, Effectname (_, dt)) -> + let dt = OptionUtils.val_of dt in + let lin_map = StringMap.add name (not @@ Unl.type_satisfies dt) lin_map in + let deps = recursive_applications dt in + let dep_graph = (name, deps) :: dep_graph in + (lin_map, dep_graph) ) (StringMap.empty, []) desugared_mutuals in (* Next, use the toposorted dependency graph from above. We need to reverse since we propagate linearity information downwards from the @@ -400,11 +482,13 @@ object (self) (* NB: type aliases are scoped; we allow shadowing. We also allow type aliases to shadow abstract types. *) let alias_env = - List.fold_left (fun alias_env {node=(t, args, (_, dt')); _} -> - let dt = OptionUtils.val_of dt' in + List.fold_left (fun alias_env {node=(t, args, b); _} -> let semantic_qs = List.map SugarQuantifier.get_resolved_exn args in - let alias_env = - SEnv.bind t (`Alias (semantic_qs, dt)) alias_env in + let dt, k = match b with + | Typename (_, dt') -> OptionUtils.val_of dt', pk_type + | Effectname (_, dt') -> OptionUtils.val_of dt', pk_row + in + let alias_env = SEnv.bind t (`Alias (k , semantic_qs, dt)) alias_env in tygroup_ref := { !tygroup_ref with type_map = (StringMap.add t (semantic_qs, dt) !tygroup_ref.type_map); @@ -412,7 +496,8 @@ object (self) alias_env ) alias_env desugared_mutuals in - ({< alias_env = alias_env >}, Typenames desugared_mutuals) + ({< alias_env = alias_env >}, Aliases desugared_mutuals) + | Foreign alien -> let binder, datatype = Alien.declaration alien in let _, binder = self#binder binder in diff --git a/core/desugarEffects.ml b/core/desugarEffects.ml index 063d9e1cc..813abd2b8 100644 --- a/core/desugarEffects.ml +++ b/core/desugarEffects.ml @@ -120,7 +120,7 @@ let simplify_tycon_env (tycon_env : Types.tycon_environment) : simple_tycon_env let simplify_tycon name tycon simpl_env = let param_kinds, internal_type = match tycon with - | `Alias (qs, tp) -> List.map Quantifier.to_kind qs, Some tp + | `Alias (_, qs, tp) -> List.map Quantifier.to_kind qs, Some tp | `Abstract abs -> Types.Abstype.arity abs, None | `Mutual _ -> raise (internal_error "Found `Mutual in global tycon env") in @@ -256,7 +256,7 @@ let may_have_shared_eff (tycon_env : simple_tycon_env) dt = let param_kinds, _has_implicit_effect, _internal_type = try SEnv.find tycon tycon_env - with NotFound _ -> raise (Errors.UnboundTyCon (SourceCode.WithPos.pos dt, tycon)) + with NotFound _ -> raise (Errors.unbound_tycon (SourceCode.WithPos.pos dt) tycon) in match ListUtils.last_opt param_kinds with | Some (PrimaryKind.Row, (_, Restriction.Effect)) -> Some `Alias @@ -322,7 +322,7 @@ let cleanup_effects tycon_env = let tycon_info = try SEnv.find_opt name tycon_env - with NotFound _ -> raise (Errors.UnboundTyCon (pos, name)) + with NotFound _ -> raise (Errors.unbound_tycon pos name) in let rec go = (* We don't know if the arities match up yet (nor the final arities @@ -344,17 +344,20 @@ let cleanup_effects tycon_env = let ts = match tycon_info with | Some (params, _, _) -> go (params, ts) - | None -> raise (Errors.UnboundTyCon (pos, name)) + | None -> raise (Errors.unbound_tycon pos name) in TypeApplication (name, ts) + | Effect e -> + let e = self#effect_row ~allow_shared:`Disallow e in + Effect e | _ -> super#datatypenode t in SourceCode.WithPos.with_node dt res_t - method effect_row ~allow_shared (fields, var) = let open Datatype in - let open SourceCode.WithPos in + let open SourceCode in + let open WithPos in let fields = List.map (function @@ -371,15 +374,17 @@ let cleanup_effects tycon_env = (* might need an extra check on recursive rows *) ( name, Present - (SourceCode.WithPos.make ~pos + (WithPos.make ~pos (Function (domain, ([], Closed), codomain))) ) | _, _ -> raise (unexpected_effects_on_abstract_op pos name) ) - | name, Present node when not (TypeUtils.is_builtin_effect name) -> + | name, Present ({ node ; pos } as node') when not (TypeUtils.is_builtin_effect name) -> (* Elaborates `Op : a' to `Op : () {}-> a' *) + let node = match node with + | Forall (qs, node') -> Forall (qs, WithPos.make ~pos (Function ([], ([], Closed), node'))) + | _ -> Function ([], ([], Closed), node') + in ( name, - Present - (SourceCode.WithPos.make ~pos:node.pos - (Function ([], ([], Closed), node))) ) + Present (WithPos.make ~pos node) ) | x -> x) fields in @@ -482,7 +487,7 @@ let gather_mutual_info (tycon_env : simple_tycon_env) = in poss_with_implicit#with_used_type name | Some _ -> self#with_used_type name - | None -> raise (Errors.UnboundTyCon (pos, name)) ) + | None -> raise (Errors.unbound_tycon pos name) ) | _ -> self end) #datatype @@ -569,7 +574,7 @@ let gather_operation_of_type tp let (o, _) = o#typ r in let (o, _) = o#typ d in (o, tp) - | Alias ((_,kinds,tyargs,_), inner_tp) -> + | Alias (_, (_,kinds,tyargs,_), inner_tp) -> let o = o#alias_recapp kinds tyargs in let (o,_) = o#typ inner_tp in (o, tp) @@ -697,7 +702,7 @@ let gather_operations (tycon_env : simple_tycon_env) allow_fresh dt = hide_ops self in self#with_operations operations - | None -> raise (Errors.UnboundTyCon (pos, name)) ) + | None -> raise (Errors.unbound_tycon pos name) ) | Mu (v, t) -> let mtv = SugarTypeVar.get_resolved_type_exn v in let var, (_, sk) = unpack_var_id (Unionfind.find mtv) in @@ -710,6 +715,46 @@ let gather_operations (tycon_env : simple_tycon_env) allow_fresh dt = method! row_var = let open Datatype in function + | EffectApplication (name, ts) -> + let tycon_info = SEnv.find_opt name tycon_env in + let rec go o = + (* We don't know if the arities match up yet, so we handle + mismatches, assuming spare rows are effects. *) + function + | _, [] -> o + | (PrimaryKind.Row, (_, Restriction.Effect)) :: qs, Row t :: ts -> + go (o#effect_row t) (qs, ts) + | (([] as qs) | _ :: qs), t :: ts -> go (o#type_arg t) (qs, ts) + in + begin match tycon_info with + | Some (params, _has_implict_eff, internal_type) -> + let self = go self (params, ts) in + let ops = match internal_type with + | None -> RowVarMap.empty + | Some internal_type -> + gather_operation_of_type internal_type + in + let operations = + RowVarMap.fold + (fun vid sset acc -> + RowVarMap.update vid + (function + | None -> Some sset + | Some opset -> Some (StringSet.union opset sset)) + acc) + ops self#operations + in + let self = match RowVarMap.find_raw_opt (-1) ops with + | None -> self + | Some hide_ops -> + StringSet.fold + (fun label acc -> + acc#add_hidden_op name label) + hide_ops self + in + self#with_operations operations + | None -> raise (Errors.unbound_tycon SourceCode.Position.dummy name) + end | Closed | Open _ -> self @@ -850,7 +895,7 @@ class main_traversal simple_tycon_env = type applications. This must be done in later passes. *) let pos = SourceCode.Position.dummy in match SEnv.find_opt tycon tycon_env with - | None -> raise (Errors.UnboundTyCon (pos, tycon)) + | None -> raise (Errors.unbound_tycon pos tycon) | Some (params, _has_implicit_eff, _internal_type) -> let qn = List.length params in let tn = List.length ts in @@ -873,14 +918,9 @@ class main_traversal simple_tycon_env = distracting the user from the actual error: the kind missmatch. Hence, we must report a proper error here. *) raise - (Errors.TypeApplicationKindMismatch - { - pos; - name = tycon; - tyarg_number = i; - expected = PrimaryKind.to_string (fst k); - provided = PrimaryKind.to_string pk_row; - }) + (Errors.type_application_kind_mismatch pos tycon i + (PrimaryKind.to_string (fst k)) + (PrimaryKind.to_string pk_row)) | _, ta -> snd (o#type_arg ta) in let rec match_args_to_params index = function @@ -978,6 +1018,7 @@ class main_traversal simple_tycon_env = let module D = Datatype in let o, rv = match rv with + | D.EffectApplication _ -> super#row_var rv (* maybe we should do as for TypeApplication and not just visit the node *) | D.Closed -> (o, rv) | D.Open stv when (not (SugarTypeVar.is_resolved stv)) @@ -1055,6 +1096,17 @@ class main_traversal simple_tycon_env = let o, (fields, rv) = o#row (fields, rv) in (o, (fields, rv)) + method! aliasbody = + let open Sugartypes.Datatype in + let module WP = SourceCode.WithPos in + function + | Typename _ as t -> super#aliasbody t + | Effectname (r, _) -> (* hack to cleanup the row and desugar properly *) + let wp = cleanup_effects tycon_env (WP.dummy (Effect r)) in + match WP.node wp with + | Effect r -> (o, Effectname(r, None)) + | _ -> assert false + method! bindingnode = function | Val (_pat, (_qs, _body), _loc, signature) as b -> @@ -1067,7 +1119,7 @@ class main_traversal simple_tycon_env = let o = o#set_allow_implictly_bound_vars allow_implictly_bound_vars in (o, b) - | Typenames ts -> + | Aliases ts -> let open SourceCode.WithPos in let tycon_env, tycons = List.fold_left @@ -1089,16 +1141,28 @@ class main_traversal simple_tycon_env = (* First determine which types require an implicit effect variable. *) let implicits, dep_graph = List.fold_left - (fun (implicits, dep_graph) { node = t, _, (d, _); _ } -> - let d = cleanup_effects tycon_env d in - let eff = gather_mutual_info tycon_env d in - let has_imp = eff#has_implicit in - let implicits = StringMap.add t has_imp implicits in - let used_mutuals = StringSet.inter eff#used_types tycons in - let dep_graph = - StringMap.add t (StringSet.elements used_mutuals) dep_graph - in - (implicits, dep_graph)) + (fun (implicits, dep_graph) { node = t, _, b; pos ;_ } -> + match b with + | Typename (d,_) -> + let d = cleanup_effects tycon_env d in + let eff = gather_mutual_info tycon_env d in + let has_imp = eff#has_implicit in + let implicits = StringMap.add t has_imp implicits in + let used_mutuals = StringSet.inter eff#used_types tycons in + let dep_graph = + StringMap.add t (StringSet.elements used_mutuals) dep_graph + in + (implicits, dep_graph) + | Effectname (r,_) -> (* is this the right thing to do ? *) + let d = cleanup_effects tycon_env (SourceCode.WithPos.make ~pos (Datatype.Effect r)) in + let eff = gather_mutual_info tycon_env d in + let has_imp = eff#has_implicit in + let implicits = StringMap.add t has_imp implicits in + let used_mutuals = StringSet.inter eff#used_types tycons in + let dep_graph = + StringMap.add t (StringSet.elements used_mutuals) dep_graph + in + (implicits, dep_graph)) (StringMap.empty, StringMap.empty) ts in @@ -1126,7 +1190,7 @@ class main_traversal simple_tycon_env = in (* Now patch up the types to include this effect variable. *) let patch_type_param_list ((tycon_env : simple_tycon_env), shared_var_env, ts) - ({ node = t, args, (d, _); pos } as tn) = + ({ node = t, args, b; pos } as tn) = if StringMap.find t implicits then let var = Types.fresh_raw_variable () in let q = (var, (PrimaryKind.Row, (lin_unl, res_effect))) in @@ -1148,9 +1212,13 @@ class main_traversal simple_tycon_env = let shared_var_env = StringMap.add t (Some shared_effect_var) shared_var_env in + let b' = match b with + | Typename (d,_) -> Typename (d, None) + | Effectname (r,_) -> Effectname (r, None) + in ( tycon_env, shared_var_env, - SourceCode.WithPos.make ~pos (t, args, (d, None)) :: ts ) + SourceCode.WithPos.make ~pos (t, args, b') :: ts ) else (* Note that we initially set the has-implict flag to false, so there is nothing to do here *) @@ -1174,13 +1242,13 @@ class main_traversal simple_tycon_env = in (* TODO: no info to flow back out? *) - let _o, dt' = o#datatype' dt in + let _o, dt' = o#aliasbody dt in SourceCode.WithPos.make ~pos (name, args, dt') in let ts' = List.map traverse_body ts in - ({}, Typenames ts') + ({}, Aliases ts') | b -> super#bindingnode b method super_datatype = super#datatype diff --git a/core/desugarModules.ml b/core/desugarModules.ml index 9cddfdd9f..c2a481ea7 100644 --- a/core/desugarModules.ml +++ b/core/desugarModules.ml @@ -446,7 +446,7 @@ and desugar ?(toplevel=false) (renamer' : Epithet.t) (scope' : Scope.t) = fs' [] in Funs fs'' - | Typenames ts -> + | Aliases ts -> (* Must be processed before any mutual function bindings in the same mutual binding group. *) (* Same procedure as above. *) @@ -459,11 +459,11 @@ and desugar ?(toplevel=false) (renamer' : Epithet.t) (scope' : Scope.t) = let ts'' = List.fold_right (fun (name, tyvars, dt, pos) ts -> - let dt' = self#datatype' dt in + let dt' = self#aliasbody dt in SourceCode.WithPos.make ~pos (name, tyvars, dt') :: ts) ts' [] in - Typenames ts'' + Aliases ts'' | Val (pat, (tvs, body), loc, dt) -> (* It is important to process [body] before [pat] to avoid inadvertently bringing the binder(s) in [pat] into the diff --git a/core/desugarPages.ml b/core/desugarPages.ml index 8ad49c2d4..ad433d5b0 100644 --- a/core/desugarPages.ml +++ b/core/desugarPages.ml @@ -50,7 +50,7 @@ let rec desugar_page (o, page_type) = let formlet_type = Types.concrete_type formlet_type in let a = Types.fresh_type_variable (lin_any, res_any) in let b = Types.fresh_type_variable (lin_any, res_any) in - Unify.datatypes (Types.Alias (("Formlet", [(Type, default_subkind)], [(Type, a)], false), b), formlet_type); + Unify.datatypes (Types.Alias (pk_type, ("Formlet", [(Type, default_subkind)], [(Type, a)], false), b), formlet_type); fn_appl "formP" [(Type, a); (Row, o#lookup_effects)] [formlet; handler; attributes] | PagePlacement (page) -> page | Xml ("#", [], _, children) -> diff --git a/core/desugarTypeVariables.ml b/core/desugarTypeVariables.ml index dc51fb2bb..b6035f01a 100644 --- a/core/desugarTypeVariables.ml +++ b/core/desugarTypeVariables.ml @@ -415,6 +415,8 @@ object (o : 'self) method! row_var = let open Datatype in function + | EffectApplication _ as ea -> + super#row_var ea | Closed -> o, Closed | Open srv as orig when is_anonymous srv -> (* This transformation pass does not check whether anonymous row variables @@ -520,7 +522,7 @@ object (o : 'self) rec_frozen}) - method! typenamenode (name, unresolved_qs, body) = + method! aliasnode (name, unresolved_qs, body) = (* Don't allow unbound named type variables in type definitions. We do allow unbound *anoynmous* variables, because those may be @@ -529,10 +531,10 @@ object (o : 'self) Hence, we must re-check the free variables in the type definiton later on. *) let o = o#set_allow_implictly_bound_vars false in - (* Typenames must never use type variables from an outer scope *) + (* Aliases must never use type variables from an outer scope *) let o = o#reset_vars in - let o, resolved_qs, body = o#quantified ~rigidify:true unresolved_qs (fun o' -> o'#datatype' body) in + let o, resolved_qs, body = o#quantified ~rigidify:true unresolved_qs (fun o' -> o'#aliasbody body) in let o = o#set_allow_implictly_bound_vars allow_implictly_bound_vars in let o = o#set_vars tyvar_map in diff --git a/core/errors.ml b/core/errors.ml index 01c27d1f5..3e8947475 100644 --- a/core/errors.ml +++ b/core/errors.ml @@ -42,11 +42,13 @@ exception UnboundTyCon of (Position.t * string) exception InternalError of { filename: string; message: string } exception TypeApplicationArityMismatch of { pos: Position.t; name: string; expected: int; provided: int} - (* tyarg_number is 1-based index *) exception TypeApplicationKindMismatch of { pos: Position.t; name: string; tyarg_number: int; expected: string; provided: string } +exception TypeApplicationGlobalKindMismatch of + { pos: Position.t; name: string; + expected: string; provided: string } exception SettingsError of string exception DynlinkError of string exception ModuleError of string * Position.t option @@ -131,6 +133,11 @@ let format_exception = pos_prefix ~pos (Printf.sprintf "Kind mismatch: Type argument %d for type constructor %s has kind %s, but an argument of kind %s was expected. \nIn:\n%s\n" tyarg_number name provided expected expr) + | TypeApplicationGlobalKindMismatch { pos; name; expected; provided } -> + let pos, expr = Position.resolve_start_expr pos in + pos_prefix ~pos + (Printf.sprintf "Kind mismatch: Type constructor %s has kind %s, but something of kind %s was expected. \nIn:\n%s\n" + name provided expected expr) | SettingsError message -> pos_prefix (Printf.sprintf "Settings Error: %s" message) | ModuleError (message, pos) -> @@ -246,3 +253,8 @@ let prime_alien pos = PrimeAlien pos let forbidden_client_call fn reason = ForbiddenClientCall (fn, reason) let cannot_open_file filename reason = CannotOpenFile (filename, reason) let object_file_write_error filename reason = ObjectFileWriteError (filename, reason) +let type_application_kind_mismatch pos name tyarg_number expected provided = + TypeApplicationKindMismatch { pos; name; tyarg_number; expected; provided } +let type_application_global_kind_mismatch pos name expected provided = + TypeApplicationGlobalKindMismatch { pos; name; expected; provided } +let unbound_tycon pos message = UnboundTyCon (pos, message) diff --git a/core/errors.mli b/core/errors.mli index 4330b647d..e5e4bc6f0 100644 --- a/core/errors.mli +++ b/core/errors.mli @@ -34,6 +34,9 @@ exception TypeApplicationArityMismatch of exception TypeApplicationKindMismatch of { pos: Position.t; name: string; tyarg_number: int; expected: string; provided: string } +exception TypeApplicationGlobalKindMismatch of + { pos: Position.t; name: string; + expected: string; provided: string } exception SettingsError of string exception DynlinkError of string exception ModuleError of string * Position.t option @@ -63,3 +66,6 @@ val forbidden_client_call : string -> string -> exn val rethrow_errors_if_better_position : Position.t -> ('a -> 'b) -> 'a -> 'b val cannot_open_file : string -> string -> exn val object_file_write_error : string -> string -> exn +val type_application_kind_mismatch : Position.t -> string -> int -> string -> string -> exn +val type_application_global_kind_mismatch : Position.t -> string -> string -> string -> exn +val unbound_tycon : Position.t -> string -> exn diff --git a/core/generalise.ml b/core/generalise.ml index fea2713a5..710854632 100644 --- a/core/generalise.ml +++ b/core/generalise.ml @@ -30,7 +30,7 @@ let rec get_type_args : gen_kind -> TypeVarSet.t -> datatype -> type_arg list = | Not_typed -> raise (internal_error "Not_typed encountered in get_type_args") | (Var _ | Recursive _) -> failwith ("freestanding Var / Recursive not implemented yet (must be inside Meta)") - | Alias ((_, _, ts, _), t) -> + | Alias (_, (_, _, ts, _), t) -> concat_map (get_type_arg_type_args kind bound_vars) ts @ gt t | Application (_, args) -> Utility.concat_map (get_type_arg_type_args kind bound_vars) args diff --git a/core/instantiate.ml b/core/instantiate.ml index c2196b220..a35a82303 100644 --- a/core/instantiate.ml +++ b/core/instantiate.ml @@ -86,8 +86,8 @@ let instantiates : instantiation_maps -> (datatype -> datatype) * (row -> row) * List.fold_left remove_shadowed_quantifier inst_map qs in ForAll (qs, inst_typ updated_inst_map rec_env t) - | Alias ((name, qs, ts, is_dual), d) -> - Alias ((name, qs, List.map instta ts, is_dual), inst d) + | Alias (k, (name, qs, ts, is_dual), d) -> + Alias (k, (name, qs, List.map instta ts, is_dual), inst d) | Application (n, elem_type) -> Application (n, List.map instta elem_type) | RecursiveApplication app -> @@ -169,6 +169,7 @@ let instantiates : instantiation_maps -> (datatype -> datatype) * (row -> row) * match t with | Row _ -> t | Meta row_var -> Row (StringMap.empty, row_var, false) + | Alias (PrimaryKind.Row, _,row) -> row | _ -> assert false in let instr = inst_row inst_map rec_env in let dual_if = if dual then dual_row else fun x -> x in @@ -437,15 +438,15 @@ let alias name tyargs env : Types.typ = | Some (`Abstract _) | Some (`Mutual _) -> raise (internal_error (Printf.sprintf "The type constructor: %s is not an alias" name)) - | Some (`Alias (vars, _)) when List.length vars <> List.length tyargs -> + | Some (`Alias (_, vars, _)) when List.length vars <> List.length tyargs -> raise (internal_error (Printf.sprintf "Type alias %s applied with incorrect arity (%d instead of %d). This should have been checked prior to instantiation." name (List.length tyargs) (List.length vars))) - | Some (`Alias (vars, body)) -> + | Some (`Alias (k, vars, body)) -> let inst_map = populate_instantiation_map ~name vars tyargs in (* instantiate the type variables bound by the alias definition with the type arguments *and* instantiate any top-level quantifiers *) let (_, body) = typ (instantiate_datatype inst_map body) in - Alias ((name, List.map snd vars, tyargs, false), body) + Alias (k, (name, List.map snd vars, tyargs, false), body) diff --git a/core/irCheck.ml b/core/irCheck.ml index 83fc4c725..44313a2be 100644 --- a/core/irCheck.ml +++ b/core/irCheck.ml @@ -180,7 +180,7 @@ let rec is_toplevel_rec_type = function | T.Recursive _ -> true | _ -> false end - | T.Alias (_, t') -> is_toplevel_rec_type t' + | T.Alias (_, _, t') -> is_toplevel_rec_type t' | _ -> false let is_toplevel_rec_row row = @@ -254,7 +254,7 @@ let eq_types occurrence : type_eq_context -> (Types.datatype * Types.datatype) - end | (Var _ | Recursive _ | Closed) -> raise Types.tag_expectation_mismatch - | Alias (_, _) -> assert false + | Alias _ -> assert false | Application (s, ts) -> begin match t2 with | Application (s', ts') -> diff --git a/core/irTraversals.ml b/core/irTraversals.ml index 920f78768..64d4b731b 100644 --- a/core/irTraversals.ml +++ b/core/irTraversals.ml @@ -968,7 +968,7 @@ module ElimTypeAliases = struct inherit Types.Transform.visitor as super method! typ = function - | Types.Alias (_, typ) -> o#typ typ + | Types.Alias (_, _, typ) -> o#typ typ | other -> super#typ other end diff --git a/core/lens_type_conv.ml b/core/lens_type_conv.ml index ba09cd3f7..d971c0fe9 100644 --- a/core/lens_type_conv.ml +++ b/core/lens_type_conv.ml @@ -13,9 +13,9 @@ let to_links_map m = let lookup_alias context ~alias = match Env.String.find_opt alias context with - | Some (`Alias (_, body)) -> + | Some (`Alias (k, _, body)) -> let tycon = (alias, [], [], false) in - T.Alias (tycon, body) + T.Alias (k, tycon, body) | _ -> Errors.MissingBuiltinType alias |> raise let rec type_of_lens_phrase_type ~context t = diff --git a/core/lexer.mll b/core/lexer.mll index 73a15ed8e..dc52081b6 100644 --- a/core/lexer.mll +++ b/core/lexer.mll @@ -72,6 +72,7 @@ let keywords = [ "delete_left", DELETE_LEFT; "determined", DETERMINED; "do" , DOOP; + "effectname", EFFECTNAME; "else" , ELSE; "escape" , ESCAPE; "false" , FALSE; diff --git a/core/lib.ml b/core/lib.ml index 1fdc340a8..f5f9ac2ba 100644 --- a/core/lib.ml +++ b/core/lib.ml @@ -23,10 +23,10 @@ module AliasEnv = Env.String let alias_env : Types.tycon_environment = DefaultAliases.alias_env let alias_env : Types.tycon_environment = - AliasEnv.bind "Repeat" (`Alias ([], (DesugarDatatypes.read ~aliases:alias_env Linksregex.Repeat.datatype))) alias_env + AliasEnv.bind "Repeat" (`Alias (pk_type, [], (DesugarDatatypes.read ~aliases:alias_env Linksregex.Repeat.datatype))) alias_env let alias_env : Types.tycon_environment = - AliasEnv.bind "Regex" (`Alias ([], (DesugarDatatypes.read ~aliases:alias_env Linksregex.Regex.datatype))) alias_env + AliasEnv.bind "Regex" (`Alias (pk_type, [], (DesugarDatatypes.read ~aliases:alias_env Linksregex.Regex.datatype))) alias_env let datatype = DesugarDatatypes.read ~aliases:alias_env diff --git a/core/moduleUtils.ml b/core/moduleUtils.ml index 5098d7365..6ee4597e8 100644 --- a/core/moduleUtils.ml +++ b/core/moduleUtils.ml @@ -210,12 +210,12 @@ let create_module_info_map program = @ get_binding_names bs | _ :: bs -> get_binding_names bs in (* Other binding types are uninteresting for this pass *) - (* Getting type names -- we're interested in typename decls *) + (* Getting type names -- we're interested in typename/effectname decls *) let rec get_type_names = function | [] -> [] | b :: bs -> match node b with - | Typenames ts -> + | Aliases ts -> let ns = ListUtils.concat_map (fun {node=(n, _, _); _} -> [n]) ts in ns @ (get_type_names bs) | _ -> get_type_names bs in diff --git a/core/parser.mly b/core/parser.mly index a42604f2b..5d0a0cd5b 100644 --- a/core/parser.mly +++ b/core/parser.mly @@ -173,6 +173,9 @@ let attach_row_subkind (r, subkind) = | _ -> assert false in attach_subkind_helper update subkind +let alias p name args aliasbody = + with_pos p (Aliases [with_pos p (name, args, aliasbody)]) + let labels xs = fst (List.split xs) let parseRegexFlags f = @@ -220,7 +223,7 @@ let make_effect_var : is_dot:bool -> ParserPosition.t -> Datatype.row_var module MutualBindings = struct type mutual_bindings = - { mut_types: typename list; + { mut_types: alias list; mut_funs: (function_definition * Position.t) list; mut_pos: Position.t } @@ -232,9 +235,9 @@ module MutualBindings = struct match WithPos.node binding with | Fun f -> { block with mut_funs = ((f, pos) :: fs) } - | Typenames [t] -> + | Aliases [t] -> { block with mut_types = (t :: ts) } - | Typenames _ -> assert false + | Aliases _ -> assert false | _ -> raise (ConcreteSyntaxError (pos, "Only `fun` and `typename` bindings are allowed in a `mutual` block.")) @@ -285,7 +288,7 @@ module MutualBindings = struct let type_binding = function | [] -> [] - | ts -> [WithPos.make ~pos:mut_pos (Typenames (List.rev ts))] in + | ts -> [WithPos.make ~pos:mut_pos (Aliases (List.rev ts))] in type_binding mut_types @ fun_binding mut_funs end @@ -344,7 +347,7 @@ let parse_foreign_language pos lang = %token SLASHFLAGS %token UNDERSCORE AS %token FIXITY -%token TYPENAME +%token TYPENAME EFFECTNAME %token TRY OTHERWISE RAISE %token OPERATOR %token USING @@ -413,6 +416,7 @@ arg: | UFLOAT { string_of_float' $1 } | TRUE { "true" } | FALSE { "false" } +| DEFAULT { "default" } var: | VARIABLE { with_pos $loc $1 } @@ -446,7 +450,8 @@ nofun_declaration: let node = Infix { name = WithPos.node $3; precedence; assoc = $1 } in with_pos $loc node } | signature? tlvarbinding SEMICOLON { val_binding' ~ppos:$loc($2) $1 $2 } -| typedecl SEMICOLON | links_module | links_open SEMICOLON { $1 } +| typedecl SEMICOLON { $1 } +| links_module | links_open SEMICOLON { $1 } | pollute = boption(OPEN) IMPORT CONSTRUCTOR SEMICOLON { import ~ppos:$loc($2) ~pollute [$3] } alien_datatype: @@ -505,7 +510,9 @@ signature: | SIG sigop COLON datatype { with_pos $loc ($2, datatype $4) } typedecl: -| TYPENAME CONSTRUCTOR typeargs_opt EQ datatype { with_pos $loc (Typenames [with_pos $loc ($2, $3, datatype $5)]) } +| TYPENAME CONSTRUCTOR typeargs_opt EQ datatype { alias $loc $2 $3 (Typename ( $5 , None)) } +| EFFECTNAME CONSTRUCTOR typeargs_opt EQ LBRACE erow RBRACE { alias $loc $2 $3 (Effectname ( $6 , None)) } +| EFFECTNAME CONSTRUCTOR typeargs_opt EQ effect_app { alias $loc $2 $3 (Effectname (([], $5), None)) } (* Lists of quantifiers in square brackets denote type abstractions *) type_abstracion_vars: @@ -1013,16 +1020,17 @@ datatype: | mu_datatype | straight_arrow | squiggly_arrow { with_pos $loc $1 } arrow_prefix: -| LBRACE RBRACE { ([], Datatype.Closed) } -| LBRACE efields RBRACE { $2 } +| LBRACE erow RBRACE { $2 } straight_arrow_prefix: | hear_arrow_prefix | arrow_prefix { $1 } | MINUS nonrec_row_var | MINUS kinded_nonrec_row_var { ([], $2) } +| MINUS effect_app { ([], $2) } squig_arrow_prefix: | hear_arrow_prefix | arrow_prefix { $1 } | TILDE nonrec_row_var | TILDE kinded_nonrec_row_var { ([], $2) } +| TILDE effect_app { ([], $2) } hear_arrow_prefix: | LBRACE COLON datatype COMMA efields RBRACE { hear_arrow_prefix $3 $5 } @@ -1130,7 +1138,7 @@ type_arg_list: type_arg: | datatype { Datatype.Type $1 } | braced_fieldspec { Datatype.Presence $1 } -| LBRACE row RBRACE { Datatype.Row $2 } +| LBRACE erow RBRACE { Datatype.Row $2 } datatypes: | separated_nonempty_list(COMMA, datatype) { $1 } @@ -1139,6 +1147,10 @@ vrow: | vfields { $1 } | /* empty */ { ([], Datatype.Closed) } +erow: +| efields { $1 } +| /* empty */ { ([], Datatype.Closed) } + row: | fields { $1 } | /* empty */ { ([], Datatype.Closed) } @@ -1190,9 +1202,9 @@ efields: | soption(efield) VBAR DOT { ( $1 , make_effect_var ~is_dot:true $loc) } | soption(efield) VBAR row_var { ( $1 , $3 ) } | soption(efield) VBAR kinded_row_var { ( $1 , $3 ) } +| soption(efield) VBAR effect_app { ( $1 , $3 ) } | efield COMMA efields { ( $1::fst $3, snd $3 ) } - efield: | effect_label fieldspec { ($1, $2) } @@ -1200,6 +1212,10 @@ effect_label: | CONSTRUCTOR { $1 } | VARIABLE { $1 } +effect_app: +| CONSTRUCTOR { Datatype.EffectApplication($1, []) } +| CONSTRUCTOR LPAREN type_arg_list RPAREN { Datatype.EffectApplication($1, $3) } + fieldspec: | braced_fieldspec { $1 } | COLON datatype { Datatype.Present $2 } diff --git a/core/query/query.ml b/core/query/query.ml index 57f65f850..408425660 100644 --- a/core/query/query.ml +++ b/core/query/query.ml @@ -261,13 +261,31 @@ struct (* Temporal projection operations *) | Q.Apply (Q.Primitive "ttData", [x]) | Q.Apply (Q.Primitive "vtData", [x]) -> - Q.Project (x, TemporalField.data_field) + begin + match x with + | Q.Record r -> + StringMap.find TemporalField.data_field r + | _ -> + Q.Project (x, TemporalField.data_field) + end | Q.Apply (Q.Primitive "ttFrom", [x]) | Q.Apply (Q.Primitive "vtFrom", [x]) -> - Q.Project (x, TemporalField.from_field) + begin + match x with + | Q.Record r -> + StringMap.find TemporalField.from_field r + | _ -> + Q.Project (x, TemporalField.from_field) + end | Q.Apply (Q.Primitive "ttTo", [x]) | Q.Apply (Q.Primitive "vtTo", [x]) -> - Q.Project (x, TemporalField.to_field) + begin + match x with + | Q.Record r -> + StringMap.find TemporalField.to_field r + | _ -> + Q.Project (x, TemporalField.to_field) + end | u -> u let rec xlate env : Ir.value -> Q.t = let open Ir in function diff --git a/core/query/temporalQuery.ml b/core/query/temporalQuery.ml index f04081851..913fd2e1b 100644 --- a/core/query/temporalQuery.ml +++ b/core/query/temporalQuery.ml @@ -784,18 +784,23 @@ module TemporalJoin = struct method private set_tables tbls = {< tables = tbls >} + method private project tbl field = + match tbl with + | Q.Record x -> StringMap.find field x + | _ -> Q.Project (tbl, field) + (* Start time: maximum of all start times *) method start_time = let open Q in List.fold_right (fun (tbl_var, start_time, _) expr -> - Apply (Primitive "greatest", [Project (tbl_var, start_time); expr]) + Apply (Primitive "greatest", [o#project tbl_var start_time; expr]) ) tables (Constant Constant.DateTime.beginning_of_time) (* End time: minimum of all end times *) method end_time = let open Q in List.fold_right (fun (tbl_var, _, end_time) expr -> - Apply (Primitive "least", [Project (tbl_var, end_time); expr]) + Apply (Primitive "least", [o#project tbl_var end_time; expr]) ) tables (Q.Constant forever_const) method! query = diff --git a/core/sugarTraversals.ml b/core/sugarTraversals.ml index e806176e0..e15e4af32 100644 --- a/core/sugarTraversals.ml +++ b/core/sugarTraversals.ml @@ -105,6 +105,10 @@ class map = method row_var : Datatype.row_var -> Datatype.row_var = let open Datatype in function + | EffectApplication (_x, _x_i1) -> + let _x = o#name _x in + let _x_i1 = o#list (fun o -> o#type_arg) _x_i1 + in EffectApplication (_x, _x_i1) | Closed -> Closed | Open _x -> let _x = o#type_variable _x in Open _x @@ -166,6 +170,12 @@ class map = let y = o#option (fun o -> o#typ) y in (x,y) + method row' : row' -> row' = + fun (x, y) -> + let x = o#row x in + let y = o#option (fun o -> o#typ) y in + (x,y) + method given_spawn_location : given_spawn_location -> given_spawn_location = function | ExplicitSpawnLocation p -> ExplicitSpawnLocation (o#phrase p) @@ -753,9 +763,9 @@ class map = | Open _xs -> let _xs = o#list (fun o -> o#name) _xs in Open _xs - | Typenames ts -> - let _x = o#list (fun o -> o#typename) ts in - Typenames _x + | Aliases ts -> + let _x = o#list (fun o -> o#alias) ts in + Aliases _x | Infix { name; assoc; precedence } -> Infix { name = o#name name; assoc; precedence } | Exp _x -> let _x = o#phrase _x in Exp _x @@ -779,17 +789,22 @@ class map = fun p -> WithPos.map2 ~f_pos:o#position ~f_node:o#bindingnode p - method typenamenode : typenamenode -> typenamenode = + method aliasnode : aliasnode -> aliasnode = fun (_x, _x_i1, _x_i2) -> let _x = o#name _x in let _x_i1 = o#list (fun o x -> o#quantifier x) _x_i1 in - let _x_i2 = o#datatype' _x_i2 in + let _x_i2 = o#aliasbody _x_i2 in (_x, _x_i1, _x_i2) - method typename : typename -> typename = + method aliasbody : aliasbody -> aliasbody = + function + | Typename _x -> Typename (o#datatype' _x) + | Effectname _x -> Effectname (o#row' _x) + + method alias : alias -> alias = fun p -> - WithPos.map2 ~f_pos:o#position ~f_node:o#typenamenode p + WithPos.map2 ~f_pos:o#position ~f_node:o#aliasnode p method function_definition : function_definition -> function_definition = fun { fun_binder; @@ -937,6 +952,9 @@ class fold = method row_var : Datatype.row_var -> 'self_type = let open Datatype in function + | EffectApplication (_x, _x_i1) -> + let o = o#name _x in + let o = o#list (fun o -> o#type_arg) _x_i1 in o | Closed -> o | Open _x -> let o = o#type_variable _x in o @@ -992,6 +1010,12 @@ class fold = let o = o#unknown y in o + method row' : row' -> 'self_type = + fun (x, y) -> + let o = o#row x in + let o = o#unknown y in + o + method given_spawn_location : given_spawn_location -> 'self_type = function | ExplicitSpawnLocation p -> let o = o#phrase p in o | _ -> o @@ -1510,8 +1534,8 @@ class fold = | Open _xs -> let o = o#list (fun o -> o#name) _xs in o - | Typenames ts -> - let o = o#list (fun o -> o#typename) ts in + | Aliases ts -> + let o = o#list (fun o -> o#alias) ts in o | Infix { name; _ } -> o#name name @@ -1533,7 +1557,7 @@ class fold = ~f_pos:(fun o v -> o#position v) ~f_node:(fun o v -> o#bindingnode v) - method typenamenode : typenamenode -> 'self_type = + method aliasnode : aliasnode -> 'self_type = fun (_x, _x_i1, _x_i2) -> let o = o#name _x in let o = @@ -1541,14 +1565,19 @@ class fold = (fun o _x -> let o = o#quantifier _x in o) _x_i1 in - let o = o#datatype' _x_i2 in + let o = o#aliasbody _x_i2 in o - method typename : typename -> 'self_type = + method aliasbody : aliasbody -> 'self_type = + function + | Typename _x -> o#datatype' _x + | Effectname _x -> o#row' _x + + method alias : alias -> 'self_type = WithPos.traverse ~o ~f_pos:(fun o v -> o#position v) - ~f_node:(fun o v -> o#typenamenode v) + ~f_node:(fun o v -> o#aliasnode v) method function_definition : function_definition -> 'self = fun { fun_binder; @@ -1692,6 +1721,10 @@ class fold_map = method row_var : Datatype.row_var -> ('self_type * Datatype.row_var) = let open Datatype in function + | EffectApplication (_x, _x_i1) -> + let (o, _x) = o#string _x in + let (o, _x_i1) = o#list (fun o -> o#type_arg) _x_i1 + in (o, EffectApplication (_x, _x_i1)) | Closed -> (o, Closed) | Open _x -> let (o, _x) = o#type_variable _x in (o, (Open _x)) @@ -2282,6 +2315,12 @@ class fold_map = let (o, _x_i1) = o#option (fun o -> o#typ) _x_i1 in (o, (_x, _x_i1)) + method row' : row' -> ('self_type * row') = + fun (_x, _x_i1) -> + let (o, _x) = o#row _x in + let (o, _x_i1) = o#option (fun o -> o#typ) _x_i1 + in (o, (_x, _x_i1)) + method datatypenode : Datatype.t -> ('self_type * Datatype.t) = let open Datatype in function @@ -2419,9 +2458,9 @@ class fold_map = | Open _xs -> let (o, _xs) = o#list (fun o n -> o#name n) _xs in (o, Open _xs) - | Typenames ts -> - let (o, _x) = o#list (fun o -> o#typename) ts in - (o, (Typenames _x)) + | Aliases ts -> + let (o, _x) = o#list (fun o -> o#alias) ts in + (o, (Aliases _x)) | Infix { name; assoc; precedence } -> let (o, name) = o#name name in (o, Infix { name; assoc; precedence }) @@ -2448,7 +2487,7 @@ class fold_map = ~f_pos:(fun o v -> o#position v) ~f_node:(fun o v -> o#bindingnode v) - method typenamenode : typenamenode -> ('self_type * typenamenode) = + method aliasnode : aliasnode -> ('self_type * aliasnode) = fun (_x, _x_i1, _x_i2) -> let (o, _x) = o#name _x in let (o, _x_i1) = @@ -2457,14 +2496,19 @@ class fold_map = let (o, _x) = o#quantifier _x in (o, _x)) _x_i1 in - let (o, _x_i2) = o#datatype' _x_i2 + let (o, _x_i2) = o#aliasbody _x_i2 in (o, (_x, _x_i1, _x_i2)) - method typename : typename -> ('self_type * typename) = + method alias : alias -> ('self_type * alias) = WithPos.traverse_map ~o ~f_pos:(fun o v -> o#position v) - ~f_node:(fun o v -> o#typenamenode v) + ~f_node:(fun o v -> o#aliasnode v) + + method aliasbody : aliasbody -> ('self_type * aliasbody) = + function + | Typename _x -> let o, _x = o#datatype' _x in (o, Typename _x) + | Effectname _x -> let o, _x = o#row' _x in (o, Effectname _x) method function_definition : function_definition -> 'self * function_definition = fun { fun_binder; diff --git a/core/sugarTraversals.mli b/core/sugarTraversals.mli index 49e423d41..d3fb2a34d 100644 --- a/core/sugarTraversals.mli +++ b/core/sugarTraversals.mli @@ -63,6 +63,7 @@ class map : method datatype : Datatype.with_pos -> Datatype.with_pos method datatypenode : Datatype.t -> Datatype.t method datatype' : datatype' -> datatype' + method row' : row' -> row' method type_arg : Datatype.type_arg -> Datatype.type_arg method type_arg' : type_arg' -> type_arg' method constant : Constant.t -> Constant.t @@ -70,8 +71,9 @@ class map : method tybinop : tyarg list * BinaryOp.t -> tyarg list * BinaryOp.t method bindingnode : bindingnode -> bindingnode method binding : binding -> binding - method typenamenode : typenamenode -> typenamenode - method typename : typename -> typename + method aliasnode : aliasnode -> aliasnode + method alias : alias -> alias + method aliasbody : aliasbody -> aliasbody method function_definition : function_definition -> function_definition method recursive_function : recursive_function -> recursive_function method recursive_functionnode : recursive_functionnode -> recursive_functionnode @@ -145,6 +147,7 @@ class fold : method datatype : Datatype.with_pos -> 'self method datatypenode : Datatype.t -> 'self method datatype' : datatype' -> 'self + method row' : row' -> 'self method type_arg : Datatype.type_arg -> 'self method type_arg' : type_arg' -> 'self method constant : Constant.t -> 'self @@ -152,8 +155,9 @@ class fold : method tybinop : tyarg list * BinaryOp.t -> 'self method bindingnode : bindingnode -> 'self method binding : binding -> 'self - method typenamenode : typenamenode -> 'self - method typename : typename -> 'self + method aliasnode : aliasnode -> 'self + method alias : alias -> 'self + method aliasbody : aliasbody -> 'self method function_definition : function_definition -> 'self method recursive_function : recursive_function -> 'self method recursive_functionnode : recursive_functionnode -> 'self @@ -177,8 +181,9 @@ object ('self) method binder : Binder.with_pos -> 'self * Binder.with_pos method binding : binding -> 'self * binding method bindingnode : bindingnode -> 'self * bindingnode - method typenamenode : typenamenode -> 'self * typenamenode - method typename : typename -> 'self * typename + method aliasnode : aliasnode -> 'self * aliasnode + method alias : alias -> 'self * alias + method aliasbody : aliasbody -> 'self * aliasbody method binop : BinaryOp.t -> 'self * BinaryOp.t method tybinop : tyarg list * BinaryOp.t -> 'self * (tyarg list * BinaryOp.t) method bool : bool -> 'self * bool @@ -188,6 +193,7 @@ object ('self) method datatype : Datatype.with_pos -> 'self * Datatype.with_pos method datatypenode : Datatype.t -> 'self * Datatype.t method datatype' : datatype' -> 'self * datatype' + method row' : row' -> 'self * row' method type_arg' : type_arg' -> 'self * type_arg' method directive : directive -> 'self * directive method fieldconstraint : fieldconstraint -> 'self * fieldconstraint diff --git a/core/sugartoir.ml b/core/sugartoir.ml index 0f31eaf85..380ec60e3 100644 --- a/core/sugartoir.ml +++ b/core/sugartoir.ml @@ -1317,7 +1317,7 @@ struct let xt = Binder.to_type binder in I.alien (Var.make_info xt x scope, Alien.object_name alien, Alien.language alien, fun v -> eval_bindings scope (extend [x] [(v, xt)] env) bs e) - | Typenames _ + | Aliases _ | Infix _ -> (* Ignore type alias and infix declarations - they shouldn't be needed in the IR *) diff --git a/core/sugartypes.ml b/core/sugartypes.ml index 8a64e764e..b17421516 100644 --- a/core/sugartypes.ml +++ b/core/sugartypes.ml @@ -117,7 +117,7 @@ let get_unresolved_exn = function let get_unresolved_name_exn = get_unresolved_exn ->- fst3 - let get_resolved_type_exn = +let get_resolved_type_exn = function | TResolvedType point -> point | _ -> raise (internal_error "requested kind does not match existing kind info") @@ -209,6 +209,7 @@ module Datatype = struct and with_pos = t WithPos.t and row = (string * fieldspec) list * row_var and row_var = + | EffectApplication of string * type_arg list | Closed | Open of SugarTypeVar.t | Recursive of SugarTypeVar.t * row @@ -227,6 +228,9 @@ end type datatype' = Datatype.with_pos * Types.datatype option [@@deriving show] +type row' = Datatype.row * Types.row option + [@@deriving show] + type type_arg' = Datatype.type_arg * Types.type_arg option [@@deriving show] @@ -520,7 +524,7 @@ and bindingnode = | Foreign of Alien.single Alien.t | Import of { pollute: bool; path : Name.t list } | Open of Name.t list - | Typenames of typename list + | Aliases of alias list | Infix of { assoc: Associativity.t; precedence: int; name: string } @@ -541,8 +545,11 @@ and cp_phrasenode = | CPLink of Binder.with_pos * Binder.with_pos | CPComp of Binder.with_pos * cp_phrase * cp_phrase and cp_phrase = cp_phrasenode WithPos.t -and typenamenode = Name.t * SugarQuantifier.t list * datatype' -and typename = typenamenode WithPos.t +and aliasnode = Name.t * SugarQuantifier.t list * aliasbody +and alias = aliasnode WithPos.t +and aliasbody = + | Typename of datatype' + | Effectname of row' and function_definition = { fun_binder: Binder.with_pos; fun_linearity: DeclaredLinearity.t; @@ -804,7 +811,7 @@ struct names, union_map (fun rhs -> diff (funlit rhs) names) rhss | Import _ | Open _ - | Typenames _ -> empty, empty + | Aliases _ -> empty, empty (* This is technically a declaration, thus the name should probably be treated as bound rather than free. *) | Infix { name; _ } -> empty, singleton name diff --git a/core/transformSugar.ml b/core/transformSugar.ml index 6f06af5cf..0be2a390e 100644 --- a/core/transformSugar.ml +++ b/core/transformSugar.ml @@ -888,16 +888,20 @@ class transform (env : Types.typing_environment) = in let o, language = o#foreign_language (Alien.language alien) in (o, Foreign (Alien.modify ~language ~declarations alien)) - | Typenames ts -> - let (o, _) = listu o (fun o {node=(name, vars, (x, dt')); pos} -> - match dt' with - | Some dt -> + | Aliases ts -> + let (o, _) = listu o (fun o {node=(name, vars, b); pos} -> + match b with + | Typename (x, (Some dt as dt')) -> let o = o#bind_tycon name - (`Alias (List.map (SugarQuantifier.get_resolved_exn) vars, dt)) in - (o, WithPos.make ~pos (name, vars, (x, dt'))) - | None -> raise (internal_error "Unannotated type alias") + (`Alias (pk_type, List.map (SugarQuantifier.get_resolved_exn) vars, dt)) in + (o, WithPos.make ~pos (name, vars, Typename (x, dt'))) + | Effectname (x, (Some r as r')) -> + let o = o#bind_tycon name + (`Alias (pk_row, List.map (SugarQuantifier.get_resolved_exn) vars, r)) in + (o, WithPos.make ~pos (name, vars, Effectname (x, r'))) + | _ -> raise (internal_error "Unannotated type alias") ) ts in - (o, Typenames ts) + (o, Aliases ts) | (Infix _) as node -> (o, node) | Exp e -> let (o, e, _) = o#phrase e in (o, Exp e) diff --git a/core/typeSugar.ml b/core/typeSugar.ml index 5747060ca..08b76aa95 100644 --- a/core/typeSugar.ml +++ b/core/typeSugar.ml @@ -154,7 +154,7 @@ struct | Fun _ | Funs _ | Infix _ - | Typenames _ + | Aliases _ | Foreign _ -> true | Exp p -> is_pure p | Val (pat, (_, rhs), _, _) -> @@ -1666,10 +1666,10 @@ let empty_context eff desugared = effect_row = eff; desugared } -let bind_var context (v, t) = {context with var_env = Env.bind v t context.var_env} -let unbind_var context v = {context with var_env = Env.unbind v context.var_env} -let bind_tycon context (v, t) = {context with tycon_env = Env.bind v t context.tycon_env} -let bind_effects context r = {context with effect_row = r} +let bind_var context (v, t) = {context with var_env = Env.bind v t context.var_env} +let unbind_var context v = {context with var_env = Env.unbind v context.var_env} +let bind_alias context (v, t) = {context with tycon_env = Env.bind v t context.tycon_env} +let bind_effects context r = {context with effect_row = r} (* TODO(dhil): I have extracted the Usage abstraction from my name hygiene/compilation unit patch. The below module is a compatibility @@ -1918,7 +1918,7 @@ let close_pattern_type : Pattern.with_pos list -> Types.datatype -> Types.dataty let open Types in let rec cpt : Pattern.with_pos list -> Types.datatype -> Types.datatype = fun pats t -> match t with - | Alias (alias, t) -> Alias (alias, cpt pats t) + | Alias (k, alias, t) -> Alias (k, alias, cpt pats t) | Record row when Types.is_tuple row-> let fields, row_var, dual = Types.unwrap_row row |> fst |> TypeUtils.extract_row_parts in let rec unwrap_at i p = @@ -4847,14 +4847,16 @@ and type_binding : context -> binding -> binding * context * Usage.t = ( Foreign (Alien.modify ~declarations:[(binder, (dt, Some datatype))] alien) , bind_var empty_context (Binder.to_name binder, datatype) , Usage.empty ) - | Typenames ts -> - let env = List.fold_left (fun env {node=(name, vars, (_, dt')); _} -> - match dt' with - | Some dt -> - bind_tycon env (name, `Alias (List.map (SugarQuantifier.get_resolved_exn) vars, dt)) - | None -> raise (internal_error "typeSugar.ml: unannotated type") + | Aliases ts -> + let env = List.fold_left (fun env {node=(name, vars, b); _} -> + match b with + | Typename (_, Some dt) -> + bind_alias env (name, `Alias (pk_type, List.map (SugarQuantifier.get_resolved_exn) vars, dt)) + | Effectname (_, Some dt) -> + bind_alias env (name, `Alias (pk_row , List.map (SugarQuantifier.get_resolved_exn) vars, dt)) + | _ -> raise (internal_error "typeSugar.ml: unannotated type") ) empty_context ts in - (Typenames ts, env, Usage.empty) + (Aliases ts, env, Usage.empty) | Infix def -> Infix def, empty_context, Usage.empty | Exp e -> let e = tc e in @@ -4940,7 +4942,7 @@ and type_cp (context : context) = fun {node = p; pos} -> CPUnquote (bindings, e), t, usage_builder u | CPGrab ((c, _), None, p) -> let (_, t, _) = type_check context (var c) in - let ctype = T.Alias (("EndQuery", [], [], false), T.Input (Types.unit_type, T.End)) in + let ctype = T.Alias (pk_type, ("EndQuery", [], [], false), T.Input (Types.unit_type, T.End)) in unify ~pos:pos ~handle:(Gripers.cp_grab c) (t, ctype); let (p, pt, u) = type_cp (unbind_var context c) p in CPGrab ((c, Some (ctype, [])), None, p), pt, use c u diff --git a/core/typeUtils.ml b/core/typeUtils.ml index dba381b90..4b09fa890 100644 --- a/core/typeUtils.ml +++ b/core/typeUtils.ml @@ -237,7 +237,7 @@ let rec primary_kind_of_type t = failwith "Top-level Recursive should have been removed by concrete_type call" | Meta p -> primary_kind_of_type (Unionfind.find p) - | Alias (_, d) -> + | Alias (_, _, d) -> primary_kind_of_type d | Primitive _ | Function _ @@ -323,7 +323,7 @@ let check_type_wellformedness primary_kind t : unit = | (Var _ | Recursive _ | Closed) -> (* freestanding Var / Recursive / Closed not implemented yet (must be inside Meta) *) raise tag_expectation_mismatch - | Alias ((_name, qs, ts, _), d) -> + | Alias (_, (_name, qs, ts, _), d) -> List.iter2 (compare_kinds rec_env) qs ts; typ rec_env d | Application (abs_type, args) -> diff --git a/core/types.ml b/core/types.ml index 6c3658633..a06a73712 100644 --- a/core/types.ml +++ b/core/types.ml @@ -138,7 +138,7 @@ and typ = | Not_typed | Var of (tid * Kind.t * Freedom.t) | Recursive of (tid * Kind.t * typ) - | Alias of ((string * Kind.t list * type_arg list * bool) * typ) + | Alias of (PrimaryKind.t * (string * Kind.t list * type_arg list * bool) * typ) | Application of (Abstype.t * type_arg list) | RecursiveApplication of rec_appl | Meta of typ point @@ -188,7 +188,7 @@ let is_present = function | _ -> failwith "Expected presence constructor." -type alias_type = Quantifier.t list * typ [@@deriving show] +type alias_type = PrimaryKind.t * Quantifier.t list * typ [@@deriving show] type tycon_spec = [ | `Alias of alias_type @@ -196,7 +196,6 @@ type tycon_spec = [ | `Mutual of (Quantifier.t list * tygroup ref) (* Type in same recursive group *) ] [@@deriving show] - (* Generation of fresh type variables *) let type_variable_counter = ref 0 let fresh_raw_variable () : int = @@ -329,10 +328,10 @@ struct (o, Not_typed) | (Var _ | Recursive _ | Closed) -> failwith ("[0] freestanding Var / Recursive / Closed not implemented yet (must be inside Meta)") - | Alias ((name, params, args, is_dual), t) -> + | Alias (k, (name, params, args, is_dual), t) -> let (o, args') = o#type_args args in let (o, t') = o#typ t in - (o, Alias ((name, params, args', is_dual), t')) + (o, Alias (k, (name, params, args', is_dual), t')) | Application (con, args) -> let (o, args') = o#type_args args in (o, Application (con, args')) @@ -370,7 +369,12 @@ struct let (o, write') = o#typ write in let (o, needed') = o#typ needed in (o, Table (temporality, read', write', needed')) - | Lens _ -> assert false (* TODO FIXME *) + | Lens t -> + (* Lens types are substantially more complex than allowed for by a + visitor. If this functionality is needed, then the visitor can + be extended and a separate visitor can be written for lens types + separately. *) + (o, Lens t) | ForAll (names, body) -> let (o, names') = o#list (fun o -> o#quantifier) names in let (o, body') = o#typ body in @@ -566,7 +570,7 @@ class virtual type_predicate = object(self) | Not_typed -> assert false | Var _ | Recursive _ | Closed -> failwith ("[1] freestanding Var / Recursive / Closed not implemented yet (must be inside Meta)") - | Alias (_, t) -> self#type_satisfies vars t + | Alias (_, _, t) -> self#type_satisfies vars t | Application (_, ts) -> (* This does assume that all abstract types satisfy the predicate. *) List.for_all (self#type_satisfies_arg vars) ts @@ -638,7 +642,7 @@ class virtual type_iter = object(self) | Not_typed -> assert false | Var _ | Recursive _ | Closed -> failwith ("[2] freestanding Var / Recursive / Closed not implemented yet (must be inside Meta)") - | Alias (_, t) -> self#visit_type vars t + | Alias (_, _, t) -> self#visit_type vars t | Application (_, ts) -> List.iter (self#visit_type_arg vars) ts | RecursiveApplication { r_args; _ } -> List.iter (self#visit_type_arg vars) r_args | Meta point -> self#visit_point self#visit_type vars point @@ -1160,7 +1164,7 @@ let free_type_vars, free_row_type_vars, free_tyarg_vars = S.union_all [free_type_vars' rec_vars r; free_type_vars' rec_vars w; free_type_vars' rec_vars n] | Lens _ -> S.empty - | Alias ((_, _, ts, _), datatype) -> + | Alias (_, (_, _, ts, _), datatype) -> S.union (S.union_all (List.map (free_tyarg_vars' rec_vars) ts)) (free_type_vars' rec_vars datatype) | Application (_, tyargs) -> S.union_all (List.map (free_tyarg_vars' rec_vars) tyargs) | RecursiveApplication { r_args; _ } -> @@ -1321,7 +1325,7 @@ let rec dual_type : var_map -> datatype -> datatype = | RecursiveApplication appl -> RecursiveApplication { appl with r_dual = (not appl.r_dual) } | End -> End - | Alias ((f,ks,args,isdual),t) -> Alias ((f,ks,args,not(isdual)),dt t) + | Alias (k, (f,ks,args,isdual),t) -> Alias (k, (f,ks,args,not(isdual)),dt t) | t -> raise (Invalid_argument ("Attempt to dualise non-session type: " ^ show_datatype @@ DecycleTypes.datatype t)) and dual_row : var_map -> row -> row = fun rec_points row -> @@ -1356,7 +1360,7 @@ and subst_dual_type : var_map -> datatype -> datatype = | Table (t, r, w, n) -> Table (t, sdt r, sdt w, sdt n) | Lens _sort -> t (* TODO: we could do a check to see if we can preserve aliases here *) - | Alias (_, t) -> sdt t + | Alias (_, _, t) -> sdt t | Application (abs, ts) -> Application (abs, List.map (subst_dual_type_arg rec_points) ts) | RecursiveApplication app -> (* I don't think we need to do anything with the dualisation flag @@ -1429,7 +1433,8 @@ and flatten_row : row -> row = fun row -> | Row _ -> row (* HACK: this probably shouldn't happen! *) | Meta row_var -> Row (StringMap.empty, row_var, false) - | _ -> assert false in + | _ -> raise (internal_error "attempt to flatten, row expected") + in let dual_if = match row with | Row (_, _, dual) -> @@ -1559,8 +1564,8 @@ and normalise_datatype rec_names t = | Effect row -> Effect (nr row) | Table (t, r, w, n) -> Table (t, nt r, nt w, nt n) | Lens sort -> Lens sort - | Alias ((name, qs, ts, is_dual), datatype) -> - Alias ((name, qs, ts, is_dual), nt datatype) + | Alias (k, (name, qs, ts, is_dual), datatype) -> + Alias (k, (name, qs, ts, is_dual), nt datatype) | Application (abs, tyargs) -> Application (abs, List.map (normalise_type_arg rec_names) tyargs) | RecursiveApplication app -> @@ -1671,7 +1676,7 @@ let bool_type = Primitive Primitive.Bool let int_type = Primitive Primitive.Int let float_type = Primitive Primitive.Float let datetime_type = Primitive Primitive.DateTime -let xml_type = Alias (("Xml", [], [], false), Application (list, [(PrimaryKind.Type, Primitive Primitive.XmlItem)])) +let xml_type = Alias (pk_type, ("Xml", [], [], false), Application (list, [(PrimaryKind.Type, Primitive Primitive.XmlItem)])) let database_type = Primitive Primitive.DB (* Empty type, used for exceptions *) let empty_type = Variant (make_empty_closed_row ()) @@ -1732,7 +1737,7 @@ exception TypeDestructionError of string let concrete_type' t = let rec ct rec_names t : datatype = match t with - | Alias (_, t) -> ct rec_names t + | Alias (_, _, t) -> ct rec_names t | Meta point -> begin match Unionfind.find point with @@ -1825,7 +1830,7 @@ struct | Not_typed -> [] | Var _ | Recursive _ | Closed -> failwith ("[10] freestanding Var / Recursive / Closed not implemented yet (must be inside Meta)") - | Alias ((_, _, ts, _), _) -> + | Alias (_, (_, _, ts, _), _) -> concat_map (free_bound_tyarg_vars bound_vars) ts | Application (_, tyargs) -> List.concat (List.map (free_bound_tyarg_vars bound_vars) tyargs) @@ -1908,7 +1913,7 @@ struct (TypeVarSet.add var bound_vars, (var, spec)::vars)) (bound_vars, []) tyvars in (bound_vars, List.rev vars) in match tycon_spec with - | `Alias (tyvars, body) -> + | `Alias (_, tyvars, body) -> let (bound_vars, vars) = split_vars tyvars in vars @ (free_bound_type_vars bound_vars body) | `Mutual (tyvars, _) -> snd (split_vars tyvars) @@ -2280,7 +2285,7 @@ struct (** If this type may contain a shared effect. *) let maybe_shared_effect = function | Function _ | Lolli _ -> true - | Alias ((_, qs, _, _), _) | RecursiveApplication { r_quantifiers = qs; _ } -> + | Alias (_, (_, qs, _, _), _) | RecursiveApplication { r_quantifiers = qs; _ } -> begin match ListUtils.last_opt qs with | Some (PrimaryKind.Row, (_, Restriction.Effect)) -> true | _ -> false @@ -2304,7 +2309,7 @@ struct match t with | Function (_, _, r) | Lolli (_, _, r) when maybe_shared_effect r -> find_shared_var r | Function (_, e, _) | Lolli (_, e, _) -> find_row_var e - | Alias ((_, _, ts, _), _) | RecursiveApplication { r_args = ts; _ } when maybe_shared_effect t -> + | Alias (_, (_, _, ts, _), _) | RecursiveApplication { r_args = ts; _ } when maybe_shared_effect t -> begin match ListUtils.last ts with | (PrimaryKind.Row, (Row _ as r)) -> find_row_var r | _ -> None @@ -2509,7 +2514,7 @@ struct | Not_typed -> "not typed" | Var _ | Recursive _ | Closed -> failwith ("[11] freestanding Var / Recursive / Closed not implemented yet (must be inside Meta)") - | Alias ((s, _, ts, is_dual), _) | RecursiveApplication { r_name = s; r_args = ts; r_dual = is_dual; _ } -> + | Alias (_, (s, _, ts, is_dual), _) | RecursiveApplication { r_name = s; r_args = ts; r_dual = is_dual; _ } -> let ts = match ListUtils.unsnoc_opt ts, context.shared_effect with | Some (ts, (PrimaryKind.Row, (Row r as r'))), Some v when maybe_shared_effect t && is_row_var v r -> @@ -2719,7 +2724,7 @@ struct TypeVarSet.add (Quantifier.to_var tyvar) bound_vars) bound_vars tyvars in function - | `Alias (tyvars, body) -> + | `Alias (_, tyvars, body) -> let ctx = { context with bound_vars = bound_vars tyvars } in begin match tyvars with @@ -2916,7 +2921,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct need those to share an effect variable, we only need to look at the surface (here the kinds of type arguments), because if this has a shared effect, it must be visible in type arguments *) - | Alias ((_, kinds, _, _), _) + | Alias (_, (_, kinds, _, _), _) | RecursiveApplication { r_quantifiers = kinds; _ } -> begin (* by convention, if the alias has an argument containing shared effect, it @@ -2959,7 +2964,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct (* alternatively, this is the rightmost alias, which can also have a shared effect - this is by convention the last argument *) - | Alias ((_,_,type_args,_), _) + | Alias (_, (_,_,type_args,_), _) | RecursiveApplication { r_args = type_args ; _ } when implicit_allowed_in tp -> begin @@ -3069,7 +3074,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct let (o, _) = o#effect_row e in let (o, _) = o#typ r in (o, tp) - | Alias ((_,kinds,tyargs,_), _) + | Alias (_, (_,kinds,tyargs,_), _) | RecursiveApplication { r_quantifiers = kinds; r_args = tyargs ; _ } -> (o#alias_recapp kinds tyargs, tp) | _ -> super#typ tp @@ -3246,7 +3251,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct (** Deconstruct Alias, let tyarg_list handle it *) method alias : typ -> 'self_type * typ = fun al -> - let ((name, kinds, tyargs, dual), tp) = match al with + let (k, (name, kinds, tyargs, dual), tp) = match al with | Alias a -> a | _ -> assert false in @@ -3256,7 +3261,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct else o#tyarg_list kinds tyargs in (* let (o, tp) = o#typ tp in *) - let al = Alias ((name, kinds, tyargs, dual), tp) in + let al = Alias (k, (name, kinds, tyargs, dual), tp) in (o, al) (** Deconstruct Rec.App., let tyarg_list handle it *) @@ -4008,7 +4013,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct | Var (vid, knd, _) -> with_value var (vid, knd) | Recursive v -> with_value recursive v | Application a -> with_value application a - | Alias ((name, arg_kinds, arg_types, is_dual), _) + | Alias (_, (name, arg_kinds, arg_types, is_dual), _) | RecursiveApplication { r_name = name; r_quantifiers = arg_kinds ; r_args = arg_types; r_dual = is_dual; _ } -> with_value alias_recapp (name, arg_kinds, arg_types, is_dual) @@ -4087,7 +4092,7 @@ module RoundtripPrinter : PRETTY_PRINTER = struct = let open Printer in Printer (fun ctx v buf -> match v with - | `Alias (tyvars, body) -> + | `Alias (_, tyvars, body) -> let ctx = Context.bind_tyvars (List.map Quantifier.to_var tyvars) ctx in begin match tyvars with @@ -4130,7 +4135,7 @@ module DerivedPrinter : PRETTY_PRINTER = struct let string_of_tycon_spec : Policy.t -> names -> tycon_spec -> string = fun _policy _names tycon -> let decycle_tycon_spec = function - | `Alias (qlist, ty) -> `Alias (List.map DecycleTypes.quantifier qlist, DecycleTypes.datatype ty) + | `Alias (k, qlist, ty) -> `Alias (k, List.map DecycleTypes.quantifier qlist, DecycleTypes.datatype ty) | other -> other in show_tycon_spec (decycle_tycon_spec tycon) @@ -4187,7 +4192,7 @@ See Note [Variable names in error messages]. type environment = datatype Env.t [@@deriving show] -type tycon_environment = tycon_spec Env.t +type tycon_environment = tycon_spec Env.t [@@deriving show] type typing_environment = { var_env : environment ; rec_vars : StringSet.t ; @@ -4196,11 +4201,11 @@ type typing_environment = { var_env : environment ; desugared : bool } [@@deriving show] -let empty_typing_environment = { var_env = Env.empty; - rec_vars = StringSet.empty; - tycon_env = Env.empty; +let empty_typing_environment = { var_env = Env.empty; + rec_vars = StringSet.empty; + tycon_env = Env.empty; effect_row = make_empty_closed_row (); - desugared = false } + desugared = false } (* Which printer to use *) type pretty_printer_engine = Old | Roundtrip | Derived @@ -4357,7 +4362,7 @@ let make_fresh_envs : datatype -> datatype IntMap.t * row IntMap.t * field_spec | Effect row | Record row | Variant row -> make_env boundvars row | Table (_, r, w, n) -> union [make_env boundvars r; make_env boundvars w; make_env boundvars n] | Lens _ -> empties - | Alias ((_, _, ts, _), d) -> union (List.map (make_env_ta boundvars) ts @ [make_env boundvars d]) + | Alias (_, (_, _, ts, _), d) -> union (List.map (make_env_ta boundvars) ts @ [make_env boundvars d]) | Application (_, ds) -> union (List.map (make_env_ta boundvars) ds) | RecursiveApplication { r_args ; _ } -> union (List.map (make_env_ta boundvars) r_args) | ForAll (qs, t) -> @@ -4488,10 +4493,10 @@ let is_sub_type, is_sub_row = | Recursive _ -> false | t' -> is_sub_type rec_vars (t, t') end - | Alias ((name, [], [], is_dual), _), Alias ((name', [], [], is_dual'), _) - when name=name' && is_dual=is_dual' -> true - | (Alias (_, t)), t' - | t, (Alias (_, t')) -> is_sub_type rec_vars (t, t') + | Alias (k, (name, [], [], is_dual), _), Alias (k', (name', [], [], is_dual'), _) + when k=k' && name=name' && is_dual=is_dual' -> true + | (Alias (_, _, t)), t' + | t, (Alias (_, _, t')) -> is_sub_type rec_vars (t, t') | ForAll _, ForAll _ -> raise (internal_error "not implemented subtyping on forall types yet") | _, _ -> false @@ -4650,10 +4655,10 @@ let make_tablehandle_alias (r, w, n) = let kind = (PrimaryKind.Type, (lin_unl, res_any)) in let kinds = List.init 3 (fun _ -> kind) in let tyargs = List.map (fun x -> (PrimaryKind.Type, x)) [r; w; n] in - Alias (("TableHandle", kinds, tyargs, false), + Alias (pk_type, ("TableHandle", kinds, tyargs, false), Table (Temporality.current, r, w, n)) -let make_endbang_type : datatype = Alias (("EndBang", [], [], false), Output (unit_type, End)) +let make_endbang_type : datatype = Alias (pk_type, ("EndBang", [], [], false), Output (unit_type, End)) let make_function_type : ?linear:bool -> datatype list -> row -> datatype -> datatype = fun ?(linear=false) args effs range -> @@ -4714,7 +4719,7 @@ let pp_type_arg : Format.formatter -> type_arg -> unit = fun fmt t -> let pp_tycon_spec : Format.formatter -> tycon_spec -> unit = fun fmt t -> let decycle_tycon_spec = function - | `Alias (qlist, ty) -> `Alias (List.map DecycleTypes.quantifier qlist, DecycleTypes.datatype ty) + | `Alias (k, qlist, ty) -> `Alias (k, List.map DecycleTypes.quantifier qlist, DecycleTypes.datatype ty) | other -> other in if Settings.get print_types_pretty then diff --git a/core/types.mli b/core/types.mli index c92fa77ec..ccf5e2f42 100644 --- a/core/types.mli +++ b/core/types.mli @@ -129,7 +129,7 @@ and typ = | Not_typed | Var of (tid * Kind.t * Freedom.t) | Recursive of (tid * Kind.t * typ) - | Alias of ((string * Kind.t list * type_arg list * bool) * typ) + | Alias of (PrimaryKind.t * (string * Kind.t list * type_arg list * bool) * typ) | Application of (Abstype.t * type_arg list) | RecursiveApplication of rec_appl | Meta of typ point @@ -206,7 +206,7 @@ val get_restriction_constraint : Restriction.t -> (module Constraint) option val dual_row : row -> row val dual_type : datatype -> datatype -type alias_type = Quantifier.t list * typ [@@deriving show] +type alias_type = PrimaryKind.t * Quantifier.t list * typ [@@deriving show] type tycon_spec = [ | `Alias of alias_type @@ -445,6 +445,7 @@ val pp_row : Format.formatter -> row -> unit val pp_row' : Format.formatter -> row' -> unit val pp_type_arg : Format.formatter -> type_arg -> unit val pp_tycon_spec: Format.formatter -> tycon_spec -> unit +val pp_field_spec: Format.formatter -> field_spec -> unit (* Recursive type applications *) val recursive_applications : datatype -> string list diff --git a/core/typevarcheck.ml b/core/typevarcheck.ml index 214befbb4..7d33b5c1e 100644 --- a/core/typevarcheck.ml +++ b/core/typevarcheck.ml @@ -33,7 +33,7 @@ let rec is_guarded : TypeVarSet.t -> StringSet.t -> int -> datatype -> bool = | Not_typed -> true | (Var _ | Recursive _) -> failwith ("freestanding Var / Recursive not implemented yet (must be inside Meta)") - | Alias (_, t) -> isg t + | Alias (_, _, t) -> isg t | Application (_, ts) -> (* don't treat abstract type constructors as guards *) List.for_all (is_guarded_type_arg bound_vars expanded_apps var) ts @@ -138,7 +138,7 @@ let rec is_negative : TypeVarSet.t -> StringSet.t -> int -> datatype -> bool = | Not_typed -> false | (Var _ | Recursive _) -> failwith ("freestanding Var / Recursive not implemented yet (must be inside Meta)") - | Alias (_, t) -> isn t + | Alias (_, _, t) -> isn t | Application (_, ts) -> List.exists (is_negative_type_arg bound_vars expanded_apps var) ts | RecursiveApplication { r_unique_name; r_args; r_unwind; r_dual; _ } -> @@ -225,7 +225,7 @@ and is_positive : TypeVarSet.t -> StringSet.t -> int -> datatype -> bool = | Not_typed -> false | (Var _ | Recursive _) -> failwith ("freestanding Var / Recursive not implemented yet (must be inside Meta)") - | Alias (_, t) -> isp t + | Alias (_, _, t) -> isp t | Application (_, ts) -> List.exists (is_positive_type_arg bound_vars expanded_apps var) ts | RecursiveApplication { r_unique_name; r_args; r_unwind; r_dual; _ } -> diff --git a/core/unify.ml b/core/unify.ml index 0d28bec09..f36cc0bf1 100644 --- a/core/unify.ml +++ b/core/unify.ml @@ -82,7 +82,7 @@ inside points *) let rec eq_types : (datatype * datatype) -> bool = fun (t1, t2) -> let rec unalias = function - | Alias (_, x) -> unalias x + | Alias (_, _, x) -> unalias x | x -> x in match unalias t1 with | Not_typed -> @@ -591,7 +591,7 @@ let rec unify' : unify_env -> (datatype * datatype) -> unit = Unionfind.change point t; *) | t' -> ut (t, t') end - | Alias (_, t1), t2 | t1, Alias (_, t2) -> ut (t1, t2) + | Alias (_, _, t1), t2 | t1, Alias (_, _, t2) -> ut (t1, t2) | Application (l, _), Application (r, _) when l <> r -> raise (Failure (`Msg ("Cannot unify abstract type '"^string_of_datatype t1^ diff --git a/core/webif.ml b/core/webif.ml index 5186261f8..30a26a880 100644 --- a/core/webif.ml +++ b/core/webif.ml @@ -41,13 +41,23 @@ struct have to do something about it in order for attempts to remotely call primitive functions to work properly. *) - let func = - match fvs with - | `Record [] -> let i_fname = int_of_string fname in - if Lib.is_primitive_var i_fname - then `PrimitiveFunction (Lib.primitive_name i_fname, Some i_fname) - else `FunctionPtr (int_of_string fname, None) - | _ -> `FunctionPtr (int_of_string fname, Some fvs) + let i_fname = int_of_string fname in + let func,args = + match Lib.is_primitive_var i_fname, fvs with + | true, `Record [] -> `PrimitiveFunction (Lib.primitive_name i_fname, Some i_fname), args + | false, `Record [] -> + (* Should ideally handle failure to find function gracefully here. *) + let (_finfo, (_xs, _body), z, _location) = + Tables.find Tables.fun_defs i_fname in + (* This is a workaround for the fact that client-side code passes + the environment back as an ordinary (first) argument, while + the environment is expected as the second argument to the + FunctionPtr constructor. *) + begin match z with + None -> `FunctionPtr (i_fname, None), args + | Some _ -> `FunctionPtr (i_fname, Some (List.hd args)), List.tl args + end + | _ -> `FunctionPtr (i_fname, Some fvs), args in RemoteCall (func, valenv, args) diff --git a/links-mode.el b/links-mode.el index 5087e9726..1fcec5287 100644 --- a/links-mode.el +++ b/links-mode.el @@ -62,6 +62,7 @@ "do" "else" "escape" + "effectname" "false" "for" "forall" diff --git a/tests/effectname.tests b/tests/effectname.tests new file mode 100644 index 000000000..765aff62f --- /dev/null +++ b/tests/effectname.tests @@ -0,0 +1,62 @@ +Simple effectname declarations +./tests/effectname/simple-decl.links +filemode : true +stdout : () : () + +Declaration and instanciation [1] +./tests/effectname/zero.links +filemode : true +stdout : fun : () {}-> () + +Declaration and instanciation [2] +./tests/effectname/one.links +filemode : true +stdout : fun : () {E:() {}-> ()}-> () + +Declaration and instanciation [3] +./tests/effectname/two.links +filemode : true +stdout : fun : () {E:() {}-> ()}-> () + +Twice the same effectname in one row +./tests/effectname/two-nested.links +filemode : true +stdout : fun : () {E:() {}-> ()}-> () + +Mixed typename and effectname aliases +./tests/effectname/typenames.links +filemode : true +stdout : fun : T' (Bool,Int,{}) + +Nested declaration and instanciation +./tests/effectname/nested-decl.links +filemode : true +stdout : fun : () {E:() {}-> Int,E':(Int) {}-> ()}-> () + +Recursive alias +./tests/effectname/recursive.links +filemode : true +stderr : @.* +exit : 1 + +Effectname aliases in handlers signatures +./tests/effectname/handler.links +filemode : true +args : --enable-handlers +stdout : (((), 42), (0, 42), (0, 42)) : (((), Int), (Int, Int), (Int, Int)) + +Twice the same effect label in the row +./tests/effectname/effect-same-name.links +filemode : true +stdout : fun : () {E:() {}-> Int}-> Int + +Mutual declaration +./tests/effectname/mutual.links +filemode : true +stdout : () : () + +Underscore in effect alias application +./tests/effectname/underscore.links +filemode : true +args : --enable-handlers +stdout : true : Bool diff --git a/tests/effectname/effect-same-name.links b/tests/effectname/effect-same-name.links new file mode 100755 index 000000000..dcdbbe2d4 --- /dev/null +++ b/tests/effectname/effect-same-name.links @@ -0,0 +1,8 @@ +effectname A(a,b,e::Eff) = { E: () {}-> a, E: () {}-> b | e } ; + +sig f : () -A(Int, Bool, {})-> Int +fun f () { + do E() +} + +f diff --git a/tests/effectname/handler.links b/tests/effectname/handler.links new file mode 100755 index 000000000..fd5bad41c --- /dev/null +++ b/tests/effectname/handler.links @@ -0,0 +1,38 @@ +effectname State(a,e::Eff) = { Get:() {}-> a, Put:(a) {}-> () | e } ; + +sig hstate : (() ~State(a,{ |e})~> b) -> () {Get{_}, Put{_} | e}~> (a) ~e~> (b,a) +fun hstate (m)() { + handle (m()) { + case Return(x) -> fun (s) { (x,s) } + case Get(k) -> fun (s) { k(s)(s) } + case Put(s',k) -> fun (s) { k(())(s') } + } +} + + +sig f : () ~State(Int,{})~> () +fun f () { + var x = do Get() ; + do Put(2*x) ; + () +} + +effectname Reader(a,e::Eff) = {Ask:() {}-> a | e } ; + +sig hreader : (() ~Reader(Int,{ |e})~> a) -> () {Ask{_}|e}~> a +fun hreader (m)() { + handle (m()) { + case Return(x) -> x + case Ask(k) -> k (-42) + } +} + +sig g : () ~State(Int,{ |Reader(Int,{})})~> Int +fun g () { + var x = do Get() ; + var y = do Ask() ; + do Put(2*x) ; + y + do Get() +} + +( hstate(f)()(21) , hstate(hreader(g))()(21) , hreader(fun () { hstate(g)()(21) })() ) diff --git a/tests/effectname/mutual.links b/tests/effectname/mutual.links new file mode 100755 index 000000000..20dde2793 --- /dev/null +++ b/tests/effectname/mutual.links @@ -0,0 +1,7 @@ +mutual { + effectname A = B ; + effectname B = {} ; +} + +# sig f : () -A-> () +# fun f () {} diff --git a/tests/effectname/nested-decl.links b/tests/effectname/nested-decl.links new file mode 100755 index 000000000..dab7e7f87 --- /dev/null +++ b/tests/effectname/nested-decl.links @@ -0,0 +1,8 @@ +effectname A = {} ; +effectname B(a,e::Eff) = { E: () -e-> a | A } ; +effectname C = { E': (Int) -> () | B(Int, { | A }) } ; + +sig f : () -C-> () +fun f () { do E'(do E()) } + +f diff --git a/tests/effectname/one.links b/tests/effectname/one.links new file mode 100644 index 000000000..9f90c70b8 --- /dev/null +++ b/tests/effectname/one.links @@ -0,0 +1,6 @@ +effectname A = {E: () {}-> ()} ; + +sig f : () -A-> () +fun f () { do E() } + +f diff --git a/tests/effectname/recursive.links b/tests/effectname/recursive.links new file mode 100755 index 000000000..f30d8b627 --- /dev/null +++ b/tests/effectname/recursive.links @@ -0,0 +1,10 @@ +effectname A = { E: ( () -A-> () ) {}-> () } ; + +sig f : () -A-> () +fun f () {} + +sig g : () -A-> () +fun g () { do E(f) } + +sig h : () -A-> () +fun h () { do E(g) } diff --git a/tests/effectname/simple-decl.links b/tests/effectname/simple-decl.links new file mode 100755 index 000000000..7f5370ab2 --- /dev/null +++ b/tests/effectname/simple-decl.links @@ -0,0 +1,16 @@ +effectname Void = {} ; +effectname Box(e::Eff) = { | e } ; +effectname OneEffect(a,e::Eff) = { E:a | e } ; +effectname JustOneEffect(a,e::Eff) = { E:a } ; # aka Joe +effectname W(e::Eff) = { wild:() | e } ; +effectname Wild = { wild:() } ; +effectname TwoEffects(a,e::Eff) = { E1:a, E2:a | e } ; + +typename BoxIsCompletlyUseless(e::Eff) = () -Box({ |e })-> () ; + +typename Fun(a,b,e::Eff) = (a) -e-> b ; +typename SquigglyFun(a,b,e::Eff) = (a) -W({ |e})-> b ; # as (a) ~e~> b +typename SimpleSquigglyFunInfix(a,b) = (a) -Wild-> b ; # as (a) ~> b +typename SimpleSquigglyFunPrefix(a,b) = (a) { | Wild }-> b ; +typename SimpleSquigglyFunPrefix2(a,b) = (a) { wild:() }-> b ; +typename SimpleSquigglyFunBoxWVoid(a,b) = (a) -Box({ |W({ |Void})})-> b ; diff --git a/tests/effectname/two-nested.links b/tests/effectname/two-nested.links new file mode 100755 index 000000000..95e3c6a96 --- /dev/null +++ b/tests/effectname/two-nested.links @@ -0,0 +1,9 @@ +effectname A(e::Eff) = { E: () {}-> () | e } ; +# effectname B = A({ | A({}) }) ; + +sig f : () -A({}) -> () +fun f () { + do E() +} + +f diff --git a/tests/effectname/two.links b/tests/effectname/two.links new file mode 100755 index 000000000..a1f92fc3a --- /dev/null +++ b/tests/effectname/two.links @@ -0,0 +1,7 @@ +effectname A = {} ; +effectname B(a,e::Eff) = { E: () {}-> a | e } ; + +sig f : () -B((),{ |A})-> () +fun f () { do E() } + +f diff --git a/tests/effectname/typenames.links b/tests/effectname/typenames.links new file mode 100755 index 000000000..85d1a5304 --- /dev/null +++ b/tests/effectname/typenames.links @@ -0,0 +1,12 @@ +typename T = forall e::Eff. (Int) -e-> Int ; + +effectname A(a,e::Eff) = { E1: T, E2: (Int) {}-> a | e } ; + +typename T'(a,b,e::Eff) = (a) { E: (a) {}-> Int | A(b,{ |e}) }-> b ; + +sig f : T'(Bool, Int, {}) +fun f (x) { + do E2( (do E1 ()) (do E(x)) ) +} + +f diff --git a/tests/effectname/underscore.links b/tests/effectname/underscore.links new file mode 100755 index 000000000..06da26428 --- /dev/null +++ b/tests/effectname/underscore.links @@ -0,0 +1,14 @@ +effectname A(e::Eff) = { FEct : () {}-> Bool | e } ; + +sig callF : () -A({ |_})-> Bool # with _ => error, with e => no error +fun callF () { do FEct } + +sig handlerA : ( () ~A({ |b})~> c ) {FEct{_}|b}~> c +fun handlerA (h) { + handle (h()) { + case Return(x) -> x + case FEct(k) -> k(true) + } +} + +handlerA( callF ) diff --git a/tests/effectname/zero.links b/tests/effectname/zero.links new file mode 100644 index 000000000..59ed3fe7c --- /dev/null +++ b/tests/effectname/zero.links @@ -0,0 +1,6 @@ +effectname A = {} ; + +sig f : () -A-> () +fun f () {} + +f diff --git a/tests/headless/.gitignore b/tests/headless/.gitignore deleted file mode 100644 index 40b878db5..000000000 --- a/tests/headless/.gitignore +++ /dev/null @@ -1 +0,0 @@ -node_modules/ \ No newline at end of file diff --git a/tests/headless/README.md b/tests/headless/README.md deleted file mode 100644 index 89d0d0969..000000000 --- a/tests/headless/README.md +++ /dev/null @@ -1,22 +0,0 @@ -# End-to-end Testing -Automated browser testing to test Links. -Designed to run as part of the GitHub Actions pipeline for Links. - -## How to run locally -1. Build Links in the root of the repository. -2. Run `npm install` in the current repository -3. (Optional) Set env variable `LINKS_BROWSER` to be either `chrome` (default) or `firefox` -4. (Optional) Modify `linksconfig` file to set the port, hostname, and the database config. -5. Run `npm test` - -## Troubleshooting -- To test Links server with database, make sure the database is set up as expected -- The server will fail to start if the port is used by some other process. Some useful shell commands: - - To check the port `8080`: - ``` - lsof -l 8080 - ``` - - To kill an existing Links process: - ``` - killall links.exe - ``` \ No newline at end of file diff --git a/tests/headless/browserDrivers.js b/tests/headless/browserDrivers.js deleted file mode 100644 index 0679cce56..000000000 --- a/tests/headless/browserDrivers.js +++ /dev/null @@ -1,26 +0,0 @@ -const BROWSER = process.env.LINKS_BROWSER || 'chrome'; -const { Builder } = require('selenium-webdriver'); - -let Options; - -module.exports = { - loadBrowser: () => { - switch (BROWSER) { - case 'firefox': - Options = require(`selenium-webdriver/firefox`).Options; - require('geckodriver'); // Load Firefox engine - return new Builder() - .forBrowser(BROWSER) - .setFirefoxOptions(new Options().headless()) - .build(); - case 'chrome': - Options = require(`selenium-webdriver/chrome`).Options; - return new Builder() - .forBrowser(BROWSER) - .setChromeOptions(new Options().headless()) - .build(); - default: - throw new Error(`Browser name ${BROWSER} not recognised`); - } - } -}; \ No newline at end of file diff --git a/tests/headless/linksServerRunner.js b/tests/headless/linksServerRunner.js deleted file mode 100644 index d0698555a..000000000 --- a/tests/headless/linksServerRunner.js +++ /dev/null @@ -1,73 +0,0 @@ -const fetch = require('node-fetch'); -const LINKS_ROOT_DIR = __dirname + '/../..'; -const LINKS_EXEC = `${LINKS_ROOT_DIR}/links`; - -// Load Links config as environment variables -require('dotenv').config({ path: './linksconfig' }); - -const HOSTNAME = process.env.host; -const PORT = process.env.port; -const DEFAULT_BASE_URL = `http://${HOSTNAME}:${PORT}`; - -// Delay function -async function sleep(sec) { - await new Promise(resolve => { - setTimeout(resolve, sec); - }); -} - -module.exports = { - startServer: async (linksScriptPath, linksModulePath = '') => { - linksServer = require('child_process') - .spawn(`${LINKS_EXEC} ${linksScriptPath}`, - [ - "--debug", - "--config='linksconfig'", - linksModulePath ? `--path=${linksModulePath}` : '' - ], - { - detached: true, - // stdio: 'inherit', // Print the Links stdout into the Node stdout - stdio: 'ignore', // Do not print the Links log - shell: true - }); - linksServer.unref(); - - return new Promise(async (resolve, reject) => { - - linksServer.on('exit', (code) => { - reject(`Links server exited with Code ${code}. Is the given Links script working?`); - return; - }); - - // Sleep to detect exit - await sleep(2000); - - linksServer.unref(); - - const TRIAL_COUNT = 10; - for (var i = 1; i <= TRIAL_COUNT; i++) { - // Some delay - await sleep(2000); - - console.log(`(${i + 1}) request ${DEFAULT_BASE_URL} `); - - try { - let response = await fetch(DEFAULT_BASE_URL); - if (response.ok) { - console.log(`Request ${i} successful.`); - resolve(linksServer); - return; - } - } catch (e) { /* Ignore error and try again */ } - - } - - // else: - reject(`Server not responded`); - - }); - }, - DEFAULT_BASE_URL: DEFAULT_BASE_URL, - LINKS_ROOT: LINKS_ROOT_DIR -}; \ No newline at end of file diff --git a/tests/headless/linksconfig b/tests/headless/linksconfig deleted file mode 100644 index de4287c13..000000000 --- a/tests/headless/linksconfig +++ /dev/null @@ -1,5 +0,0 @@ -# hostname and port to host Links server -port=8080 -host=0.0.0.0 -database_driver=postgresql -database_args=localhost:5432:links:links \ No newline at end of file diff --git a/tests/headless/package-lock.json b/tests/headless/package-lock.json deleted file mode 100644 index a9d047c3f..000000000 --- a/tests/headless/package-lock.json +++ /dev/null @@ -1,3459 +0,0 @@ -{ - "name": "links-end-to-end", - "requires": true, - "lockfileVersion": 1, - "dependencies": { - "@babel/code-frame": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/code-frame/-/code-frame-7.14.5.tgz", - "integrity": "sha512-9pzDqyc6OLDaqe+zbACgFkb6fKMNG6CObKpnYXChRsvYGyEdc7CA2BaqeOM+vOtCS5ndmJicPJhKAwYRI6UfFw==", - "requires": { - "@babel/highlight": "^7.14.5" - } - }, - "@babel/compat-data": { - "version": "7.14.7", - "resolved": "https://registry.npmjs.org/@babel/compat-data/-/compat-data-7.14.7.tgz", - "integrity": "sha512-nS6dZaISCXJ3+518CWiBfEr//gHyMO02uDxBkXTKZDN5POruCnOZ1N4YBRZDCabwF8nZMWBpRxIicmXtBs+fvw==" - }, - "@babel/core": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/core/-/core-7.14.8.tgz", - "integrity": "sha512-/AtaeEhT6ErpDhInbXmjHcUQXH0L0TEgscfcxk1qbOvLuKCa5aZT0SOOtDKFY96/CLROwbLSKyFor6idgNaU4Q==", - "requires": { - "@babel/code-frame": "^7.14.5", - "@babel/generator": "^7.14.8", - "@babel/helper-compilation-targets": "^7.14.5", - "@babel/helper-module-transforms": "^7.14.8", - "@babel/helpers": "^7.14.8", - "@babel/parser": "^7.14.8", - "@babel/template": "^7.14.5", - "@babel/traverse": "^7.14.8", - "@babel/types": "^7.14.8", - "convert-source-map": "^1.7.0", - "debug": "^4.1.0", - "gensync": "^1.0.0-beta.2", - "json5": "^2.1.2", - "semver": "^6.3.0", - "source-map": "^0.5.0" - }, - "dependencies": { - "source-map": { - "version": "0.5.7", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.5.7.tgz", - "integrity": "sha1-igOdLRAh0i0eoUyA2OpGi6LvP8w=" - } - } - }, - "@babel/generator": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/generator/-/generator-7.14.8.tgz", - "integrity": "sha512-cYDUpvIzhBVnMzRoY1fkSEhK/HmwEVwlyULYgn/tMQYd6Obag3ylCjONle3gdErfXBW61SVTlR9QR7uWlgeIkg==", - "requires": { - "@babel/types": "^7.14.8", - "jsesc": "^2.5.1", - "source-map": "^0.5.0" - }, - "dependencies": { - "source-map": { - "version": "0.5.7", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.5.7.tgz", - "integrity": "sha1-igOdLRAh0i0eoUyA2OpGi6LvP8w=" - } - } - }, - "@babel/helper-compilation-targets": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-compilation-targets/-/helper-compilation-targets-7.14.5.tgz", - "integrity": "sha512-v+QtZqXEiOnpO6EYvlImB6zCD2Lel06RzOPzmkz/D/XgQiUu3C/Jb1LOqSt/AIA34TYi/Q+KlT8vTQrgdxkbLw==", - "requires": { - "@babel/compat-data": "^7.14.5", - "@babel/helper-validator-option": "^7.14.5", - "browserslist": "^4.16.6", - "semver": "^6.3.0" - } - }, - "@babel/helper-function-name": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-function-name/-/helper-function-name-7.14.5.tgz", - "integrity": "sha512-Gjna0AsXWfFvrAuX+VKcN/aNNWonizBj39yGwUzVDVTlMYJMK2Wp6xdpy72mfArFq5uK+NOuexfzZlzI1z9+AQ==", - "requires": { - "@babel/helper-get-function-arity": "^7.14.5", - "@babel/template": "^7.14.5", - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-get-function-arity": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-get-function-arity/-/helper-get-function-arity-7.14.5.tgz", - "integrity": "sha512-I1Db4Shst5lewOM4V+ZKJzQ0JGGaZ6VY1jYvMghRjqs6DWgxLCIyFt30GlnKkfUeFLpJt2vzbMVEXVSXlIFYUg==", - "requires": { - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-hoist-variables": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-hoist-variables/-/helper-hoist-variables-7.14.5.tgz", - "integrity": "sha512-R1PXiz31Uc0Vxy4OEOm07x0oSjKAdPPCh3tPivn/Eo8cvz6gveAeuyUUPB21Hoiif0uoPQSSdhIPS3352nvdyQ==", - "requires": { - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-member-expression-to-functions": { - "version": "7.14.7", - "resolved": "https://registry.npmjs.org/@babel/helper-member-expression-to-functions/-/helper-member-expression-to-functions-7.14.7.tgz", - "integrity": "sha512-TMUt4xKxJn6ccjcOW7c4hlwyJArizskAhoSTOCkA0uZ+KghIaci0Qg9R043kUMWI9mtQfgny+NQ5QATnZ+paaA==", - "requires": { - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-module-imports": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-module-imports/-/helper-module-imports-7.14.5.tgz", - "integrity": "sha512-SwrNHu5QWS84XlHwGYPDtCxcA0hrSlL2yhWYLgeOc0w7ccOl2qv4s/nARI0aYZW+bSwAL5CukeXA47B/1NKcnQ==", - "requires": { - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-module-transforms": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/helper-module-transforms/-/helper-module-transforms-7.14.8.tgz", - "integrity": "sha512-RyE+NFOjXn5A9YU1dkpeBaduagTlZ0+fccnIcAGbv1KGUlReBj7utF7oEth8IdIBQPcux0DDgW5MFBH2xu9KcA==", - "requires": { - "@babel/helper-module-imports": "^7.14.5", - "@babel/helper-replace-supers": "^7.14.5", - "@babel/helper-simple-access": "^7.14.8", - "@babel/helper-split-export-declaration": "^7.14.5", - "@babel/helper-validator-identifier": "^7.14.8", - "@babel/template": "^7.14.5", - "@babel/traverse": "^7.14.8", - "@babel/types": "^7.14.8" - } - }, - "@babel/helper-optimise-call-expression": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-optimise-call-expression/-/helper-optimise-call-expression-7.14.5.tgz", - "integrity": "sha512-IqiLIrODUOdnPU9/F8ib1Fx2ohlgDhxnIDU7OEVi+kAbEZcyiF7BLU8W6PfvPi9LzztjS7kcbzbmL7oG8kD6VA==", - "requires": { - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-plugin-utils": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-plugin-utils/-/helper-plugin-utils-7.14.5.tgz", - "integrity": "sha512-/37qQCE3K0vvZKwoK4XU/irIJQdIfCJuhU5eKnNxpFDsOkgFaUAwbv+RYw6eYgsC0E4hS7r5KqGULUogqui0fQ==" - }, - "@babel/helper-replace-supers": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-replace-supers/-/helper-replace-supers-7.14.5.tgz", - "integrity": "sha512-3i1Qe9/8x/hCHINujn+iuHy+mMRLoc77b2nI9TB0zjH1hvn9qGlXjWlggdwUcju36PkPCy/lpM7LLUdcTyH4Ow==", - "requires": { - "@babel/helper-member-expression-to-functions": "^7.14.5", - "@babel/helper-optimise-call-expression": "^7.14.5", - "@babel/traverse": "^7.14.5", - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-simple-access": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/helper-simple-access/-/helper-simple-access-7.14.8.tgz", - "integrity": "sha512-TrFN4RHh9gnWEU+s7JloIho2T76GPwRHhdzOWLqTrMnlas8T9O7ec+oEDNsRXndOmru9ymH9DFrEOxpzPoSbdg==", - "requires": { - "@babel/types": "^7.14.8" - } - }, - "@babel/helper-split-export-declaration": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-split-export-declaration/-/helper-split-export-declaration-7.14.5.tgz", - "integrity": "sha512-hprxVPu6e5Kdp2puZUmvOGjaLv9TCe58E/Fl6hRq4YiVQxIcNvuq6uTM2r1mT/oPskuS9CgR+I94sqAYv0NGKA==", - "requires": { - "@babel/types": "^7.14.5" - } - }, - "@babel/helper-validator-identifier": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/helper-validator-identifier/-/helper-validator-identifier-7.14.8.tgz", - "integrity": "sha512-ZGy6/XQjllhYQrNw/3zfWRwZCTVSiBLZ9DHVZxn9n2gip/7ab8mv2TWlKPIBk26RwedCBoWdjLmn+t9na2Gcow==" - }, - "@babel/helper-validator-option": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/helper-validator-option/-/helper-validator-option-7.14.5.tgz", - "integrity": "sha512-OX8D5eeX4XwcroVW45NMvoYaIuFI+GQpA2a8Gi+X/U/cDUIRsV37qQfF905F0htTRCREQIB4KqPeaveRJUl3Ow==" - }, - "@babel/helpers": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/helpers/-/helpers-7.14.8.tgz", - "integrity": "sha512-ZRDmI56pnV+p1dH6d+UN6GINGz7Krps3+270qqI9UJ4wxYThfAIcI5i7j5vXC4FJ3Wap+S9qcebxeYiqn87DZw==", - "requires": { - "@babel/template": "^7.14.5", - "@babel/traverse": "^7.14.8", - "@babel/types": "^7.14.8" - } - }, - "@babel/highlight": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/highlight/-/highlight-7.14.5.tgz", - "integrity": "sha512-qf9u2WFWVV0MppaL877j2dBtQIDgmidgjGk5VIMw3OadXvYaXn66U1BFlH2t4+t3i+8PhedppRv+i40ABzd+gg==", - "requires": { - "@babel/helper-validator-identifier": "^7.14.5", - "chalk": "^2.0.0", - "js-tokens": "^4.0.0" - }, - "dependencies": { - "ansi-styles": { - "version": "3.2.1", - "resolved": "https://registry.npmjs.org/ansi-styles/-/ansi-styles-3.2.1.tgz", - "integrity": "sha512-VT0ZI6kZRdTh8YyJw3SMbYm/u+NqfsAxEpWO0Pf9sq8/e94WxxOpPKx9FR1FlyCtOVDNOQ+8ntlqFxiRc+r5qA==", - "requires": { - "color-convert": "^1.9.0" - } - }, - "chalk": { - "version": "2.4.2", - "resolved": "https://registry.npmjs.org/chalk/-/chalk-2.4.2.tgz", - "integrity": "sha512-Mti+f9lpJNcwF4tWV8/OrTTtF1gZi+f8FqlyAdouralcFWFQWF2+NgCHShjkCb+IFBLq9buZwE1xckQU4peSuQ==", - "requires": { - "ansi-styles": "^3.2.1", - "escape-string-regexp": "^1.0.5", - "supports-color": "^5.3.0" - } - }, - "color-convert": { - "version": "1.9.3", - "resolved": "https://registry.npmjs.org/color-convert/-/color-convert-1.9.3.tgz", - "integrity": "sha512-QfAUtd+vFdAtFQcC8CCyYt1fYWxSqAiK2cSD6zDB8N3cpsEBAvRxp9zOGg6G/SHHJYAT88/az/IuDGALsNVbGg==", - "requires": { - "color-name": "1.1.3" - } - }, - "color-name": { - "version": "1.1.3", - "resolved": "https://registry.npmjs.org/color-name/-/color-name-1.1.3.tgz", - "integrity": "sha1-p9BVi9icQveV3UIyj3QIMcpTvCU=" - }, - "escape-string-regexp": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/escape-string-regexp/-/escape-string-regexp-1.0.5.tgz", - "integrity": "sha1-G2HAViGQqN/2rjuyzwIAyhMLhtQ=" - }, - "has-flag": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-3.0.0.tgz", - "integrity": "sha1-tdRU3CGZriJWmfNGfloH87lVuv0=" - }, - "supports-color": { - "version": "5.5.0", - "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-5.5.0.tgz", - "integrity": "sha512-QjVjwdXIt408MIiAqCX4oUKsgU2EqAGzs2Ppkm4aQYbjm+ZEWEcW4SfFNTr4uMNZma0ey4f5lgLrkB0aX0QMow==", - "requires": { - "has-flag": "^3.0.0" - } - } - } - }, - "@babel/parser": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/parser/-/parser-7.14.8.tgz", - "integrity": "sha512-syoCQFOoo/fzkWDeM0dLEZi5xqurb5vuyzwIMNZRNun+N/9A4cUZeQaE7dTrB8jGaKuJRBtEOajtnmw0I5hvvA==" - }, - "@babel/plugin-syntax-async-generators": { - "version": "7.8.4", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-async-generators/-/plugin-syntax-async-generators-7.8.4.tgz", - "integrity": "sha512-tycmZxkGfZaxhMRbXlPXuVFpdWlXpir2W4AMhSJgRKzk/eDlIXOhb2LHWoLpDF7TEHylV5zNhykX6KAgHJmTNw==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-bigint": { - "version": "7.8.3", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-bigint/-/plugin-syntax-bigint-7.8.3.tgz", - "integrity": "sha512-wnTnFlG+YxQm3vDxpGE57Pj0srRU4sHE/mDkt1qv2YJJSeUAec2ma4WLUnUPeKjyrfntVwe/N6dCXpU+zL3Npg==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-class-properties": { - "version": "7.12.13", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-class-properties/-/plugin-syntax-class-properties-7.12.13.tgz", - "integrity": "sha512-fm4idjKla0YahUNgFNLCB0qySdsoPiZP3iQE3rky0mBUtMZ23yDJ9SJdg6dXTSDnulOVqiF3Hgr9nbXvXTQZYA==", - "requires": { - "@babel/helper-plugin-utils": "^7.12.13" - } - }, - "@babel/plugin-syntax-import-meta": { - "version": "7.10.4", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-import-meta/-/plugin-syntax-import-meta-7.10.4.tgz", - "integrity": "sha512-Yqfm+XDx0+Prh3VSeEQCPU81yC+JWZ2pDPFSS4ZdpfZhp4MkFMaDC1UqseovEKwSUpnIL7+vK+Clp7bfh0iD7g==", - "requires": { - "@babel/helper-plugin-utils": "^7.10.4" - } - }, - "@babel/plugin-syntax-json-strings": { - "version": "7.8.3", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-json-strings/-/plugin-syntax-json-strings-7.8.3.tgz", - "integrity": "sha512-lY6kdGpWHvjoe2vk4WrAapEuBR69EMxZl+RoGRhrFGNYVK8mOPAW8VfbT/ZgrFbXlDNiiaxQnAtgVCZ6jv30EA==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-logical-assignment-operators": { - "version": "7.10.4", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-logical-assignment-operators/-/plugin-syntax-logical-assignment-operators-7.10.4.tgz", - "integrity": "sha512-d8waShlpFDinQ5MtvGU9xDAOzKH47+FFoney2baFIoMr952hKOLp1HR7VszoZvOsV/4+RRszNY7D17ba0te0ig==", - "requires": { - "@babel/helper-plugin-utils": "^7.10.4" - } - }, - "@babel/plugin-syntax-nullish-coalescing-operator": { - "version": "7.8.3", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-nullish-coalescing-operator/-/plugin-syntax-nullish-coalescing-operator-7.8.3.tgz", - "integrity": "sha512-aSff4zPII1u2QD7y+F8oDsz19ew4IGEJg9SVW+bqwpwtfFleiQDMdzA/R+UlWDzfnHFCxxleFT0PMIrR36XLNQ==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-numeric-separator": { - "version": "7.10.4", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-numeric-separator/-/plugin-syntax-numeric-separator-7.10.4.tgz", - "integrity": "sha512-9H6YdfkcK/uOnY/K7/aA2xpzaAgkQn37yzWUMRK7OaPOqOpGS1+n0H5hxT9AUw9EsSjPW8SVyMJwYRtWs3X3ug==", - "requires": { - "@babel/helper-plugin-utils": "^7.10.4" - } - }, - "@babel/plugin-syntax-object-rest-spread": { - "version": "7.8.3", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-object-rest-spread/-/plugin-syntax-object-rest-spread-7.8.3.tgz", - "integrity": "sha512-XoqMijGZb9y3y2XskN+P1wUGiVwWZ5JmoDRwx5+3GmEplNyVM2s2Dg8ILFQm8rWM48orGy5YpI5Bl8U1y7ydlA==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-optional-catch-binding": { - "version": "7.8.3", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-optional-catch-binding/-/plugin-syntax-optional-catch-binding-7.8.3.tgz", - "integrity": "sha512-6VPD0Pc1lpTqw0aKoeRTMiB+kWhAoT24PA+ksWSBrFtl5SIRVpZlwN3NNPQjehA2E/91FV3RjLWoVTglWcSV3Q==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-optional-chaining": { - "version": "7.8.3", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-optional-chaining/-/plugin-syntax-optional-chaining-7.8.3.tgz", - "integrity": "sha512-KoK9ErH1MBlCPxV0VANkXW2/dw4vlbGDrFgz8bmUsBGYkFRcbRwMh6cIJubdPrkxRwuGdtCk0v/wPTKbQgBjkg==", - "requires": { - "@babel/helper-plugin-utils": "^7.8.0" - } - }, - "@babel/plugin-syntax-top-level-await": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-top-level-await/-/plugin-syntax-top-level-await-7.14.5.tgz", - "integrity": "sha512-hx++upLv5U1rgYfwe1xBQUhRmU41NEvpUvrp8jkrSCdvGSnM5/qdRMtylJ6PG5OFkBaHkbTAKTnd3/YyESRHFw==", - "requires": { - "@babel/helper-plugin-utils": "^7.14.5" - } - }, - "@babel/plugin-syntax-typescript": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/plugin-syntax-typescript/-/plugin-syntax-typescript-7.14.5.tgz", - "integrity": "sha512-u6OXzDaIXjEstBRRoBCQ/uKQKlbuaeE5in0RvWdA4pN6AhqxTIwUsnHPU1CFZA/amYObMsuWhYfRl3Ch90HD0Q==", - "requires": { - "@babel/helper-plugin-utils": "^7.14.5" - } - }, - "@babel/template": { - "version": "7.14.5", - "resolved": "https://registry.npmjs.org/@babel/template/-/template-7.14.5.tgz", - "integrity": "sha512-6Z3Po85sfxRGachLULUhOmvAaOo7xCvqGQtxINai2mEGPFm6pQ4z5QInFnUrRpfoSV60BnjyF5F3c+15fxFV1g==", - "requires": { - "@babel/code-frame": "^7.14.5", - "@babel/parser": "^7.14.5", - "@babel/types": "^7.14.5" - } - }, - "@babel/traverse": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/traverse/-/traverse-7.14.8.tgz", - "integrity": "sha512-kexHhzCljJcFNn1KYAQ6A5wxMRzq9ebYpEDV4+WdNyr3i7O44tanbDOR/xjiG2F3sllan+LgwK+7OMk0EmydHg==", - "requires": { - "@babel/code-frame": "^7.14.5", - "@babel/generator": "^7.14.8", - "@babel/helper-function-name": "^7.14.5", - "@babel/helper-hoist-variables": "^7.14.5", - "@babel/helper-split-export-declaration": "^7.14.5", - "@babel/parser": "^7.14.8", - "@babel/types": "^7.14.8", - "debug": "^4.1.0", - "globals": "^11.1.0" - } - }, - "@babel/types": { - "version": "7.14.8", - "resolved": "https://registry.npmjs.org/@babel/types/-/types-7.14.8.tgz", - "integrity": "sha512-iob4soQa7dZw8nodR/KlOQkPh9S4I8RwCxwRIFuiMRYjOzH/KJzdUfDgz6cGi5dDaclXF4P2PAhCdrBJNIg68Q==", - "requires": { - "@babel/helper-validator-identifier": "^7.14.8", - "to-fast-properties": "^2.0.0" - } - }, - "@bcoe/v8-coverage": { - "version": "0.2.3", - "resolved": "https://registry.npmjs.org/@bcoe/v8-coverage/-/v8-coverage-0.2.3.tgz", - "integrity": "sha512-0hYQ8SB4Db5zvZB4axdMHGwEaQjkZzFjQiN9LVYvIFB2nSUHW9tYpxWriPrWDASIxiaXax83REcLxuSdnGPZtw==" - }, - "@istanbuljs/load-nyc-config": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/@istanbuljs/load-nyc-config/-/load-nyc-config-1.1.0.tgz", - "integrity": "sha512-VjeHSlIzpv/NyD3N0YuHfXOPDIixcA1q2ZV98wsMqcYlPmv2n3Yb2lYP9XMElnaFVXg5A7YLTeLu6V84uQDjmQ==", - "requires": { - "camelcase": "^5.3.1", - "find-up": "^4.1.0", - "get-package-type": "^0.1.0", - "js-yaml": "^3.13.1", - "resolve-from": "^5.0.0" - } - }, - "@istanbuljs/schema": { - "version": "0.1.3", - "resolved": "https://registry.npmjs.org/@istanbuljs/schema/-/schema-0.1.3.tgz", - "integrity": "sha512-ZXRY4jNvVgSVQ8DL3LTcakaAtXwTVUxE81hslsyD2AtoXW/wVob10HkOJ1X/pAlcI7D+2YoZKg5do8G/w6RYgA==" - }, - "@jest/console": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/console/-/console-27.0.6.tgz", - "integrity": "sha512-fMlIBocSHPZ3JxgWiDNW/KPj6s+YRd0hicb33IrmelCcjXo/pXPwvuiKFmZz+XuqI/1u7nbUK10zSsWL/1aegg==", - "requires": { - "@jest/types": "^27.0.6", - "@types/node": "*", - "chalk": "^4.0.0", - "jest-message-util": "^27.0.6", - "jest-util": "^27.0.6", - "slash": "^3.0.0" - } - }, - "@jest/core": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/core/-/core-27.0.6.tgz", - "integrity": "sha512-SsYBm3yhqOn5ZLJCtccaBcvD/ccTLCeuDv8U41WJH/V1MW5eKUkeMHT9U+Pw/v1m1AIWlnIW/eM2XzQr0rEmow==", - "requires": { - "@jest/console": "^27.0.6", - "@jest/reporters": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/transform": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "ansi-escapes": "^4.2.1", - "chalk": "^4.0.0", - "emittery": "^0.8.1", - "exit": "^0.1.2", - "graceful-fs": "^4.2.4", - "jest-changed-files": "^27.0.6", - "jest-config": "^27.0.6", - "jest-haste-map": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-regex-util": "^27.0.6", - "jest-resolve": "^27.0.6", - "jest-resolve-dependencies": "^27.0.6", - "jest-runner": "^27.0.6", - "jest-runtime": "^27.0.6", - "jest-snapshot": "^27.0.6", - "jest-util": "^27.0.6", - "jest-validate": "^27.0.6", - "jest-watcher": "^27.0.6", - "micromatch": "^4.0.4", - "p-each-series": "^2.1.0", - "rimraf": "^3.0.0", - "slash": "^3.0.0", - "strip-ansi": "^6.0.0" - } - }, - "@jest/environment": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/environment/-/environment-27.0.6.tgz", - "integrity": "sha512-4XywtdhwZwCpPJ/qfAkqExRsERW+UaoSRStSHCCiQTUpoYdLukj+YJbQSFrZjhlUDRZeNiU9SFH0u7iNimdiIg==", - "requires": { - "@jest/fake-timers": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "jest-mock": "^27.0.6" - } - }, - "@jest/fake-timers": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/fake-timers/-/fake-timers-27.0.6.tgz", - "integrity": "sha512-sqd+xTWtZ94l3yWDKnRTdvTeZ+A/V7SSKrxsrOKSqdyddb9CeNRF8fbhAU0D7ZJBpTTW2nbp6MftmKJDZfW2LQ==", - "requires": { - "@jest/types": "^27.0.6", - "@sinonjs/fake-timers": "^7.0.2", - "@types/node": "*", - "jest-message-util": "^27.0.6", - "jest-mock": "^27.0.6", - "jest-util": "^27.0.6" - } - }, - "@jest/globals": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/globals/-/globals-27.0.6.tgz", - "integrity": "sha512-DdTGCP606rh9bjkdQ7VvChV18iS7q0IMJVP1piwTWyWskol4iqcVwthZmoJEf7obE1nc34OpIyoVGPeqLC+ryw==", - "requires": { - "@jest/environment": "^27.0.6", - "@jest/types": "^27.0.6", - "expect": "^27.0.6" - } - }, - "@jest/reporters": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/reporters/-/reporters-27.0.6.tgz", - "integrity": "sha512-TIkBt09Cb2gptji3yJXb3EE+eVltW6BjO7frO7NEfjI9vSIYoISi5R3aI3KpEDXlB1xwB+97NXIqz84qYeYsfA==", - "requires": { - "@bcoe/v8-coverage": "^0.2.3", - "@jest/console": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/transform": "^27.0.6", - "@jest/types": "^27.0.6", - "chalk": "^4.0.0", - "collect-v8-coverage": "^1.0.0", - "exit": "^0.1.2", - "glob": "^7.1.2", - "graceful-fs": "^4.2.4", - "istanbul-lib-coverage": "^3.0.0", - "istanbul-lib-instrument": "^4.0.3", - "istanbul-lib-report": "^3.0.0", - "istanbul-lib-source-maps": "^4.0.0", - "istanbul-reports": "^3.0.2", - "jest-haste-map": "^27.0.6", - "jest-resolve": "^27.0.6", - "jest-util": "^27.0.6", - "jest-worker": "^27.0.6", - "slash": "^3.0.0", - "source-map": "^0.6.0", - "string-length": "^4.0.1", - "terminal-link": "^2.0.0", - "v8-to-istanbul": "^8.0.0" - } - }, - "@jest/source-map": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/source-map/-/source-map-27.0.6.tgz", - "integrity": "sha512-Fek4mi5KQrqmlY07T23JRi0e7Z9bXTOOD86V/uS0EIW4PClvPDqZOyFlLpNJheS6QI0FNX1CgmPjtJ4EA/2M+g==", - "requires": { - "callsites": "^3.0.0", - "graceful-fs": "^4.2.4", - "source-map": "^0.6.0" - } - }, - "@jest/test-result": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/test-result/-/test-result-27.0.6.tgz", - "integrity": "sha512-ja/pBOMTufjX4JLEauLxE3LQBPaI2YjGFtXexRAjt1I/MbfNlMx0sytSX3tn5hSLzQsR3Qy2rd0hc1BWojtj9w==", - "requires": { - "@jest/console": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/istanbul-lib-coverage": "^2.0.0", - "collect-v8-coverage": "^1.0.0" - } - }, - "@jest/test-sequencer": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/test-sequencer/-/test-sequencer-27.0.6.tgz", - "integrity": "sha512-bISzNIApazYOlTHDum9PwW22NOyDa6VI31n6JucpjTVM0jD6JDgqEZ9+yn575nDdPF0+4csYDxNNW13NvFQGZA==", - "requires": { - "@jest/test-result": "^27.0.6", - "graceful-fs": "^4.2.4", - "jest-haste-map": "^27.0.6", - "jest-runtime": "^27.0.6" - } - }, - "@jest/transform": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/transform/-/transform-27.0.6.tgz", - "integrity": "sha512-rj5Dw+mtIcntAUnMlW/Vju5mr73u8yg+irnHwzgtgoeI6cCPOvUwQ0D1uQtc/APmWgvRweEb1g05pkUpxH3iCA==", - "requires": { - "@babel/core": "^7.1.0", - "@jest/types": "^27.0.6", - "babel-plugin-istanbul": "^6.0.0", - "chalk": "^4.0.0", - "convert-source-map": "^1.4.0", - "fast-json-stable-stringify": "^2.0.0", - "graceful-fs": "^4.2.4", - "jest-haste-map": "^27.0.6", - "jest-regex-util": "^27.0.6", - "jest-util": "^27.0.6", - "micromatch": "^4.0.4", - "pirates": "^4.0.1", - "slash": "^3.0.0", - "source-map": "^0.6.1", - "write-file-atomic": "^3.0.0" - } - }, - "@jest/types": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/@jest/types/-/types-27.0.6.tgz", - "integrity": "sha512-aSquT1qa9Pik26JK5/3rvnYb4bGtm1VFNesHKmNTwmPIgOrixvhL2ghIvFRNEpzy3gU+rUgjIF/KodbkFAl++g==", - "requires": { - "@types/istanbul-lib-coverage": "^2.0.0", - "@types/istanbul-reports": "^3.0.0", - "@types/node": "*", - "@types/yargs": "^16.0.0", - "chalk": "^4.0.0" - } - }, - "@nodelib/fs.scandir": { - "version": "2.1.5", - "resolved": "https://registry.npmjs.org/@nodelib/fs.scandir/-/fs.scandir-2.1.5.tgz", - "integrity": "sha512-vq24Bq3ym5HEQm2NKCr3yXDwjc7vTsEThRDnkp2DK9p1uqLR+DHurm/NOTo0KG7HYHU7eppKZj3MyqYuMBf62g==", - "requires": { - "@nodelib/fs.stat": "2.0.5", - "run-parallel": "^1.1.9" - } - }, - "@nodelib/fs.stat": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/@nodelib/fs.stat/-/fs.stat-2.0.5.tgz", - "integrity": "sha512-RkhPPp2zrqDAQA/2jNhnztcPAlv64XdhIp7a7454A5ovI7Bukxgt7MX7udwAu3zg1DcpPU0rz3VV1SeaqvY4+A==" - }, - "@nodelib/fs.walk": { - "version": "1.2.8", - "resolved": "https://registry.npmjs.org/@nodelib/fs.walk/-/fs.walk-1.2.8.tgz", - "integrity": "sha512-oGB+UxlgWcgQkgwo8GcEGwemoTFt3FIO9ababBmaGwXIoBKZ+GTy0pP185beGg7Llih/NSHSV2XAs1lnznocSg==", - "requires": { - "@nodelib/fs.scandir": "2.1.5", - "fastq": "^1.6.0" - } - }, - "@sindresorhus/is": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/@sindresorhus/is/-/is-4.1.0.tgz", - "integrity": "sha512-Cgva8HxclecUCmAImsWsbZGUh6p5DSzQ8l2Uzxuj9ANiD7LVhLM1UJ2hX/R2Y+ILpvqgW9QjmTCaBkXtj8+UOg==" - }, - "@sinonjs/commons": { - "version": "1.8.3", - "resolved": "https://registry.npmjs.org/@sinonjs/commons/-/commons-1.8.3.tgz", - "integrity": "sha512-xkNcLAn/wZaX14RPlwizcKicDk9G3F8m2nU3L7Ukm5zBgTwiT0wsoFAHx9Jq56fJA1z/7uKGtCRu16sOUCLIHQ==", - "requires": { - "type-detect": "4.0.8" - } - }, - "@sinonjs/fake-timers": { - "version": "7.1.2", - "resolved": "https://registry.npmjs.org/@sinonjs/fake-timers/-/fake-timers-7.1.2.tgz", - "integrity": "sha512-iQADsW4LBMISqZ6Ci1dupJL9pprqwcVFTcOsEmQOEhW+KLCVn/Y4Jrvg2k19fIHCp+iFprriYPTdRcQR8NbUPg==", - "requires": { - "@sinonjs/commons": "^1.7.0" - } - }, - "@szmarczak/http-timer": { - "version": "4.0.6", - "resolved": "https://registry.npmjs.org/@szmarczak/http-timer/-/http-timer-4.0.6.tgz", - "integrity": "sha512-4BAffykYOgO+5nzBWYwE3W90sBgLJoUPRWWcL8wlyiM8IB8ipJz3UMJ9KXQd1RKQXpKp8Tutn80HZtWsu2u76w==", - "requires": { - "defer-to-connect": "^2.0.0" - } - }, - "@testim/chrome-version": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/@testim/chrome-version/-/chrome-version-1.0.7.tgz", - "integrity": "sha512-8UT/J+xqCYfn3fKtOznAibsHpiuDshCb0fwgWxRazTT19Igp9ovoXMPhXyLD6m3CKQGTMHgqoxaFfMWaL40Rnw==" - }, - "@tootallnate/once": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/@tootallnate/once/-/once-1.1.2.tgz", - "integrity": "sha512-RbzJvlNzmRq5c3O09UipeuXno4tA1FE6ikOjxZK0tuxVv3412l64l5t1W5pj4+rJq9vpkm/kwiR07aZXnsKPxw==" - }, - "@types/babel__core": { - "version": "7.1.15", - "resolved": "https://registry.npmjs.org/@types/babel__core/-/babel__core-7.1.15.tgz", - "integrity": "sha512-bxlMKPDbY8x5h6HBwVzEOk2C8fb6SLfYQ5Jw3uBYuYF1lfWk/kbLd81la82vrIkBb0l+JdmrZaDikPrNxpS/Ew==", - "requires": { - "@babel/parser": "^7.1.0", - "@babel/types": "^7.0.0", - "@types/babel__generator": "*", - "@types/babel__template": "*", - "@types/babel__traverse": "*" - } - }, - "@types/babel__generator": { - "version": "7.6.3", - "resolved": "https://registry.npmjs.org/@types/babel__generator/-/babel__generator-7.6.3.tgz", - "integrity": "sha512-/GWCmzJWqV7diQW54smJZzWbSFf4QYtF71WCKhcx6Ru/tFyQIY2eiiITcCAeuPbNSvT9YCGkVMqqvSk2Z0mXiA==", - "requires": { - "@babel/types": "^7.0.0" - } - }, - "@types/babel__template": { - "version": "7.4.1", - "resolved": "https://registry.npmjs.org/@types/babel__template/-/babel__template-7.4.1.tgz", - "integrity": "sha512-azBFKemX6kMg5Io+/rdGT0dkGreboUVR0Cdm3fz9QJWpaQGJRQXl7C+6hOTCZcMll7KFyEQpgbYI2lHdsS4U7g==", - "requires": { - "@babel/parser": "^7.1.0", - "@babel/types": "^7.0.0" - } - }, - "@types/babel__traverse": { - "version": "7.14.2", - "resolved": "https://registry.npmjs.org/@types/babel__traverse/-/babel__traverse-7.14.2.tgz", - "integrity": "sha512-K2waXdXBi2302XUdcHcR1jCeU0LL4TD9HRs/gk0N2Xvrht+G/BfJa4QObBQZfhMdxiCpV3COl5Nfq4uKTeTnJA==", - "requires": { - "@babel/types": "^7.3.0" - } - }, - "@types/cacheable-request": { - "version": "6.0.2", - "resolved": "https://registry.npmjs.org/@types/cacheable-request/-/cacheable-request-6.0.2.tgz", - "integrity": "sha512-B3xVo+dlKM6nnKTcmm5ZtY/OL8bOAOd2Olee9M1zft65ox50OzjEHW91sDiU9j6cvW8Ejg1/Qkf4xd2kugApUA==", - "requires": { - "@types/http-cache-semantics": "*", - "@types/keyv": "*", - "@types/node": "*", - "@types/responselike": "*" - } - }, - "@types/graceful-fs": { - "version": "4.1.5", - "resolved": "https://registry.npmjs.org/@types/graceful-fs/-/graceful-fs-4.1.5.tgz", - "integrity": "sha512-anKkLmZZ+xm4p8JWBf4hElkM4XR+EZeA2M9BAkkTldmcyDY4mbdIJnRghDJH3Ov5ooY7/UAoENtmdMSkaAd7Cw==", - "requires": { - "@types/node": "*" - } - }, - "@types/http-cache-semantics": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/@types/http-cache-semantics/-/http-cache-semantics-4.0.1.tgz", - "integrity": "sha512-SZs7ekbP8CN0txVG2xVRH6EgKmEm31BOxA07vkFaETzZz1xh+cbt8BcI0slpymvwhx5dlFnQG2rTlPVQn+iRPQ==" - }, - "@types/istanbul-lib-coverage": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/@types/istanbul-lib-coverage/-/istanbul-lib-coverage-2.0.3.tgz", - "integrity": "sha512-sz7iLqvVUg1gIedBOvlkxPlc8/uVzyS5OwGz1cKjXzkl3FpL3al0crU8YGU1WoHkxn0Wxbw5tyi6hvzJKNzFsw==" - }, - "@types/istanbul-lib-report": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/@types/istanbul-lib-report/-/istanbul-lib-report-3.0.0.tgz", - "integrity": "sha512-plGgXAPfVKFoYfa9NpYDAkseG+g6Jr294RqeqcqDixSbU34MZVJRi/P+7Y8GDpzkEwLaGZZOpKIEmeVZNtKsrg==", - "requires": { - "@types/istanbul-lib-coverage": "*" - } - }, - "@types/istanbul-reports": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/@types/istanbul-reports/-/istanbul-reports-3.0.1.tgz", - "integrity": "sha512-c3mAZEuK0lvBp8tmuL74XRKn1+y2dcwOUpH7x4WrF6gk1GIgiluDRgMYQtw2OFcBvAJWlt6ASU3tSqxp0Uu0Aw==", - "requires": { - "@types/istanbul-lib-report": "*" - } - }, - "@types/keyv": { - "version": "3.1.3", - "resolved": "https://registry.npmjs.org/@types/keyv/-/keyv-3.1.3.tgz", - "integrity": "sha512-FXCJgyyN3ivVgRoml4h94G/p3kY+u/B86La+QptcqJaWtBWtmc6TtkNfS40n9bIvyLteHh7zXOtgbobORKPbDg==", - "requires": { - "@types/node": "*" - } - }, - "@types/node": { - "version": "16.4.3", - "resolved": "https://registry.npmjs.org/@types/node/-/node-16.4.3.tgz", - "integrity": "sha512-GKM4FLMkWDc0sfx7tXqPWkM6NBow1kge0fgQh0bOnlqo4iT1kvTvMEKE0c1RtUGnbLlGRXiAA8SumE//90uKAg==" - }, - "@types/prettier": { - "version": "2.3.2", - "resolved": "https://registry.npmjs.org/@types/prettier/-/prettier-2.3.2.tgz", - "integrity": "sha512-eI5Yrz3Qv4KPUa/nSIAi0h+qX0XyewOliug5F2QAtuRg6Kjg6jfmxe1GIwoIRhZspD1A0RP8ANrPwvEXXtRFog==" - }, - "@types/responselike": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/@types/responselike/-/responselike-1.0.0.tgz", - "integrity": "sha512-85Y2BjiufFzaMIlvJDvTTB8Fxl2xfLo4HgmHzVBz08w4wDePCTjYw66PdrolO0kzli3yam/YCgRufyo1DdQVTA==", - "requires": { - "@types/node": "*" - } - }, - "@types/stack-utils": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/@types/stack-utils/-/stack-utils-2.0.1.tgz", - "integrity": "sha512-Hl219/BT5fLAaz6NDkSuhzasy49dwQS/DSdu4MdggFB8zcXv7vflBI3xp7FEmkmdDkBUI2bPUNeMttp2knYdxw==" - }, - "@types/yargs": { - "version": "16.0.4", - "resolved": "https://registry.npmjs.org/@types/yargs/-/yargs-16.0.4.tgz", - "integrity": "sha512-T8Yc9wt/5LbJyCaLiHPReJa0kApcIgJ7Bn735GjItUfh08Z1pJvu8QZqb9s+mMvKV6WUQRV7K2R46YbjMXTTJw==", - "requires": { - "@types/yargs-parser": "*" - } - }, - "@types/yargs-parser": { - "version": "20.2.1", - "resolved": "https://registry.npmjs.org/@types/yargs-parser/-/yargs-parser-20.2.1.tgz", - "integrity": "sha512-7tFImggNeNBVMsn0vLrpn1H1uPrUBdnARPTpZoitY37ZrdJREzf7I16tMrlK3hen349gr1NYh8CmZQa7CTG6Aw==" - }, - "@types/yauzl": { - "version": "2.9.2", - "resolved": "https://registry.npmjs.org/@types/yauzl/-/yauzl-2.9.2.tgz", - "integrity": "sha512-8uALY5LTvSuHgloDVUvWP3pIauILm+8/0pDMokuDYIoNsOkSwd5AiHBTSEJjKTDcZr5z8UpgOWZkxBF4iJftoA==", - "optional": true, - "requires": { - "@types/node": "*" - } - }, - "abab": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/abab/-/abab-2.0.5.tgz", - "integrity": "sha512-9IK9EadsbHo6jLWIpxpR6pL0sazTXV6+SQv25ZB+F7Bj9mJNaOc4nCRabwd5M/JwmUa8idz6Eci6eKfJryPs6Q==" - }, - "acorn": { - "version": "8.4.1", - "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.4.1.tgz", - "integrity": "sha512-asabaBSkEKosYKMITunzX177CXxQ4Q8BSSzMTKD+FefUhipQC70gfW5SiUDhYQ3vk8G+81HqQk7Fv9OXwwn9KA==" - }, - "acorn-globals": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/acorn-globals/-/acorn-globals-6.0.0.tgz", - "integrity": "sha512-ZQl7LOWaF5ePqqcX4hLuv/bLXYQNfNWw2c0/yX/TsPRKamzHcTGQnlCjHT3TsmkOUVEPS3crCxiPfdzE/Trlhg==", - "requires": { - "acorn": "^7.1.1", - "acorn-walk": "^7.1.1" - }, - "dependencies": { - "acorn": { - "version": "7.4.1", - "resolved": "https://registry.npmjs.org/acorn/-/acorn-7.4.1.tgz", - "integrity": "sha512-nQyp0o1/mNdbTO1PO6kHkwSrmgZ0MT/jCCpNiwbUjGoRN4dlBhqJtoQuCnEOKzgTVwg0ZWiCoQy6SxMebQVh8A==" - } - } - }, - "acorn-walk": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/acorn-walk/-/acorn-walk-7.2.0.tgz", - "integrity": "sha512-OPdCF6GsMIP+Az+aWfAAOEt2/+iVDKE7oy6lJ098aoe59oAmK76qV6Gw60SbZ8jHuG2wH058GF4pLFbYamYrVA==" - }, - "adm-zip": { - "version": "0.5.5", - "resolved": "https://registry.npmjs.org/adm-zip/-/adm-zip-0.5.5.tgz", - "integrity": "sha512-IWwXKnCbirdbyXSfUDvCCrmYrOHANRZcc8NcRrvTlIApdl7PwE9oGcsYvNeJPAVY1M+70b4PxXGKIf8AEuiQ6w==" - }, - "agent-base": { - "version": "6.0.2", - "resolved": "https://registry.npmjs.org/agent-base/-/agent-base-6.0.2.tgz", - "integrity": "sha512-RZNwNclF7+MS/8bDg70amg32dyeZGZxiDuQmZxKLAlQjr3jGyLx+4Kkk58UO7D2QdgFIQCovuSuZESne6RG6XQ==", - "requires": { - "debug": "4" - } - }, - "aggregate-error": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/aggregate-error/-/aggregate-error-3.1.0.tgz", - "integrity": "sha512-4I7Td01quW/RpocfNayFdFVk1qSuoh0E7JrbRJ16nH01HhKFQ88INq9Sd+nd72zqRySlr9BmDA8xlEJ6vJMrYA==", - "requires": { - "clean-stack": "^2.0.0", - "indent-string": "^4.0.0" - } - }, - "ansi-escapes": { - "version": "4.3.2", - "resolved": "https://registry.npmjs.org/ansi-escapes/-/ansi-escapes-4.3.2.tgz", - "integrity": "sha512-gKXj5ALrKWQLsYG9jlTRmR/xKluxHV+Z9QEwNIgCfM1/uwPMCuzVVnh5mwTd+OuBZcwSIMbqssNWRm1lE51QaQ==", - "requires": { - "type-fest": "^0.21.3" - } - }, - "ansi-regex": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-6.0.1.tgz", - "integrity": "sha512-n5M855fKb2SsfMIiFFoVrABHJC8QtHwVx+mHWP3QcEqBHYienj5dHSgjbxtC0WEZXYt4wcD6zrQElDPhFuZgfA==" - }, - "ansi-styles": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/ansi-styles/-/ansi-styles-4.3.0.tgz", - "integrity": "sha512-zbB9rCJAT1rbjiVDb2hqKFHNYLxgtk8NURxZ3IZwD3F6NtxbXZQCnnSi1Lkx+IDohdPlFp222wVALIheZJQSEg==", - "requires": { - "color-convert": "^2.0.1" - } - }, - "anymatch": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/anymatch/-/anymatch-3.1.2.tgz", - "integrity": "sha512-P43ePfOAIupkguHUycrc4qJ9kz8ZiuOUijaETwX7THt0Y/GNK7v0aa8rY816xWjZ7rJdA5XdMcpVFTKMq+RvWg==", - "requires": { - "normalize-path": "^3.0.0", - "picomatch": "^2.0.4" - } - }, - "argparse": { - "version": "1.0.10", - "resolved": "https://registry.npmjs.org/argparse/-/argparse-1.0.10.tgz", - "integrity": "sha512-o5Roy6tNG4SL/FOkCAN6RzjiakZS25RLYFrcMttJqbdd8BWrnA+fGz57iN5Pb06pvBGvl5gQ0B48dJlslXvoTg==", - "requires": { - "sprintf-js": "~1.0.2" - } - }, - "array-union": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/array-union/-/array-union-2.1.0.tgz", - "integrity": "sha512-HGyxoOTYUyCM6stUe6EJgnd4EoewAI7zMdfqO+kGjnlZmBDz/cR5pf8r/cR4Wq60sL/p0IkcjUEEPwS3GFrIyw==" - }, - "asynckit": { - "version": "0.4.0", - "resolved": "https://registry.npmjs.org/asynckit/-/asynckit-0.4.0.tgz", - "integrity": "sha1-x57Zf380y48robyXkLzDZkdLS3k=" - }, - "axios": { - "version": "0.21.4", - "resolved": "https://registry.npmjs.org/axios/-/axios-0.21.4.tgz", - "integrity": "sha512-ut5vewkiu8jjGBdqpM44XxjuCjq9LAKeHVmoVfHVzy8eHgxxq8SbAVQNovDA8mVi05kP0Ea/n/UzcSHcTJQfNg==", - "requires": { - "follow-redirects": "^1.14.0" - } - }, - "babel-jest": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/babel-jest/-/babel-jest-27.0.6.tgz", - "integrity": "sha512-iTJyYLNc4wRofASmofpOc5NK9QunwMk+TLFgGXsTFS8uEqmd8wdI7sga0FPe2oVH3b5Agt/EAK1QjPEuKL8VfA==", - "requires": { - "@jest/transform": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/babel__core": "^7.1.14", - "babel-plugin-istanbul": "^6.0.0", - "babel-preset-jest": "^27.0.6", - "chalk": "^4.0.0", - "graceful-fs": "^4.2.4", - "slash": "^3.0.0" - } - }, - "babel-plugin-istanbul": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/babel-plugin-istanbul/-/babel-plugin-istanbul-6.0.0.tgz", - "integrity": "sha512-AF55rZXpe7trmEylbaE1Gv54wn6rwU03aptvRoVIGP8YykoSxqdVLV1TfwflBCE/QtHmqtP8SWlTENqbK8GCSQ==", - "requires": { - "@babel/helper-plugin-utils": "^7.0.0", - "@istanbuljs/load-nyc-config": "^1.0.0", - "@istanbuljs/schema": "^0.1.2", - "istanbul-lib-instrument": "^4.0.0", - "test-exclude": "^6.0.0" - } - }, - "babel-plugin-jest-hoist": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/babel-plugin-jest-hoist/-/babel-plugin-jest-hoist-27.0.6.tgz", - "integrity": "sha512-CewFeM9Vv2gM7Yr9n5eyyLVPRSiBnk6lKZRjgwYnGKSl9M14TMn2vkN02wTF04OGuSDLEzlWiMzvjXuW9mB6Gw==", - "requires": { - "@babel/template": "^7.3.3", - "@babel/types": "^7.3.3", - "@types/babel__core": "^7.0.0", - "@types/babel__traverse": "^7.0.6" - } - }, - "babel-preset-current-node-syntax": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/babel-preset-current-node-syntax/-/babel-preset-current-node-syntax-1.0.1.tgz", - "integrity": "sha512-M7LQ0bxarkxQoN+vz5aJPsLBn77n8QgTFmo8WK0/44auK2xlCXrYcUxHFxgU7qW5Yzw/CjmLRK2uJzaCd7LvqQ==", - "requires": { - "@babel/plugin-syntax-async-generators": "^7.8.4", - "@babel/plugin-syntax-bigint": "^7.8.3", - "@babel/plugin-syntax-class-properties": "^7.8.3", - "@babel/plugin-syntax-import-meta": "^7.8.3", - "@babel/plugin-syntax-json-strings": "^7.8.3", - "@babel/plugin-syntax-logical-assignment-operators": "^7.8.3", - "@babel/plugin-syntax-nullish-coalescing-operator": "^7.8.3", - "@babel/plugin-syntax-numeric-separator": "^7.8.3", - "@babel/plugin-syntax-object-rest-spread": "^7.8.3", - "@babel/plugin-syntax-optional-catch-binding": "^7.8.3", - "@babel/plugin-syntax-optional-chaining": "^7.8.3", - "@babel/plugin-syntax-top-level-await": "^7.8.3" - } - }, - "babel-preset-jest": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/babel-preset-jest/-/babel-preset-jest-27.0.6.tgz", - "integrity": "sha512-WObA0/Biw2LrVVwZkF/2GqbOdzhKD6Fkdwhoy9ASIrOWr/zodcSpQh72JOkEn6NWyjmnPDjNSqaGN4KnpKzhXw==", - "requires": { - "babel-plugin-jest-hoist": "^27.0.6", - "babel-preset-current-node-syntax": "^1.0.0" - } - }, - "balanced-match": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.2.tgz", - "integrity": "sha512-3oSeUO0TMV67hN1AmbXsK4yaqU7tjiHlbxRDZOpH0KW9+CeX4bRAaX0Anxt0tx2MrpRpWwQaPwIlISEJhYU5Pw==" - }, - "bluebird": { - "version": "3.7.2", - "resolved": "https://registry.npmjs.org/bluebird/-/bluebird-3.7.2.tgz", - "integrity": "sha512-XpNj6GDQzdfW+r2Wnn7xiSAd7TM3jzkxGXBGTtWKuSXv1xUV+azxAm8jdWZN06QTQk+2N2XB9jRDkvbmQmcRtg==" - }, - "brace-expansion": { - "version": "1.1.11", - "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.11.tgz", - "integrity": "sha512-iCuPHDFgrHX7H2vEI/5xpz07zSHB00TpugqhmYtVmMO6518mCuRMoOYFldEBl0g187ufozdaHgWKcYFb61qGiA==", - "requires": { - "balanced-match": "^1.0.0", - "concat-map": "0.0.1" - } - }, - "braces": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/braces/-/braces-3.0.2.tgz", - "integrity": "sha512-b8um+L1RzM3WDSzvhm6gIz1yfTbBt6YTlcEKAvsmqCZZFw46z626lVj9j1yEPW33H5H+lBQpZMP1k8l+78Ha0A==", - "requires": { - "fill-range": "^7.0.1" - } - }, - "browser-process-hrtime": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/browser-process-hrtime/-/browser-process-hrtime-1.0.0.tgz", - "integrity": "sha512-9o5UecI3GhkpM6DrXr69PblIuWxPKk9Y0jHBRhdocZ2y7YECBFCsHm79Pr3OyR2AvjhDkabFJaDJMYRazHgsow==" - }, - "browserslist": { - "version": "4.16.6", - "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.16.6.tgz", - "integrity": "sha512-Wspk/PqO+4W9qp5iUTJsa1B/QrYn1keNCcEP5OvP7WBwT4KaDly0uONYmC6Xa3Z5IqnUgS0KcgLYu1l74x0ZXQ==", - "requires": { - "caniuse-lite": "^1.0.30001219", - "colorette": "^1.2.2", - "electron-to-chromium": "^1.3.723", - "escalade": "^3.1.1", - "node-releases": "^1.1.71" - } - }, - "bser": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/bser/-/bser-2.1.1.tgz", - "integrity": "sha512-gQxTNE/GAfIIrmHLUE3oJyp5FO6HRBfhjnw4/wMmA63ZGDJnWBmgY/lyQBpnDUkGmAhbSe39tx2d/iTOAfglwQ==", - "requires": { - "node-int64": "^0.4.0" - } - }, - "buffer-crc32": { - "version": "0.2.13", - "resolved": "https://registry.npmjs.org/buffer-crc32/-/buffer-crc32-0.2.13.tgz", - "integrity": "sha1-DTM+PwDqxQqhRUq9MO+MKl2ackI=" - }, - "buffer-from": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.1.tgz", - "integrity": "sha512-MQcXEUbCKtEo7bhqEs6560Hyd4XaovZlO/k9V3hjVUF/zwW7KBVdSK4gIt/bzwS9MbR5qob+F5jusZsb0YQK2A==" - }, - "cacheable-lookup": { - "version": "5.0.4", - "resolved": "https://registry.npmjs.org/cacheable-lookup/-/cacheable-lookup-5.0.4.tgz", - "integrity": "sha512-2/kNscPhpcxrOigMZzbiWF7dz8ilhb/nIHU3EyZiXWXpeq/au8qJ8VhdftMkty3n7Gj6HIGalQG8oiBNB3AJgA==" - }, - "cacheable-request": { - "version": "7.0.2", - "resolved": "https://registry.npmjs.org/cacheable-request/-/cacheable-request-7.0.2.tgz", - "integrity": "sha512-pouW8/FmiPQbuGpkXQ9BAPv/Mo5xDGANgSNXzTzJ8DrKGuXOssM4wIQRjfanNRh3Yu5cfYPvcorqbhg2KIJtew==", - "requires": { - "clone-response": "^1.0.2", - "get-stream": "^5.1.0", - "http-cache-semantics": "^4.0.0", - "keyv": "^4.0.0", - "lowercase-keys": "^2.0.0", - "normalize-url": "^6.0.1", - "responselike": "^2.0.0" - } - }, - "callsites": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/callsites/-/callsites-3.1.0.tgz", - "integrity": "sha512-P8BjAsXvZS+VIDUI11hHCQEv74YT67YUi5JJFNWIqL235sBmjX4+qx9Muvls5ivyNENctx46xQLQ3aTuE7ssaQ==" - }, - "camelcase": { - "version": "5.3.1", - "resolved": "https://registry.npmjs.org/camelcase/-/camelcase-5.3.1.tgz", - "integrity": "sha512-L28STB170nwWS63UjtlEOE3dldQApaJXZkOI1uMFfzf3rRuPegHaHesyee+YxQ+W6SvRDQV6UrdOdRiR153wJg==" - }, - "caniuse-lite": { - "version": "1.0.30001247", - "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001247.tgz", - "integrity": "sha512-4rS7co+7+AoOSPRPOPUt5/GdaqZc0EsUpWk66ofE3HJTAajUK2Ss2VwoNzVN69ghg8lYYlh0an0Iy4LIHHo9UQ==" - }, - "chalk": { - "version": "4.1.1", - "resolved": "https://registry.npmjs.org/chalk/-/chalk-4.1.1.tgz", - "integrity": "sha512-diHzdDKxcU+bAsUboHLPEDQiw0qEe0qd7SYUn3HgcFlWgbDcfLGswOHYeGrHKzG9z6UYf01d9VFMfZxPM1xZSg==", - "requires": { - "ansi-styles": "^4.1.0", - "supports-color": "^7.1.0" - } - }, - "char-regex": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/char-regex/-/char-regex-1.0.2.tgz", - "integrity": "sha512-kWWXztvZ5SBQV+eRgKFeh8q5sLuZY2+8WUIzlxWVTg+oGwY14qylx1KbKzHd8P6ZYkAg0xyIDU9JMHhyJMZ1jw==" - }, - "chownr": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/chownr/-/chownr-2.0.0.tgz", - "integrity": "sha512-bIomtDF5KGpdogkLd9VspvFzk9KfpyyGlS8YFVZl7TGPBHL5snIOnxeshwVgPteQ9b4Eydl+pVbIyE1DcvCWgQ==" - }, - "chromedriver": { - "version": "92.0.1", - "resolved": "https://registry.npmjs.org/chromedriver/-/chromedriver-92.0.1.tgz", - "integrity": "sha512-LptlDVCs1GgyFNVbRoHzzy948JDVzTgGiVPXjNj385qXKQP3hjAVBIgyvb/Hco0xSEW8fjwJfsm1eQRmu6t4pQ==", - "requires": { - "@testim/chrome-version": "^1.0.7", - "axios": "^0.21.1", - "del": "^6.0.0", - "extract-zip": "^2.0.1", - "https-proxy-agent": "^5.0.0", - "proxy-from-env": "^1.1.0", - "tcp-port-used": "^1.0.1" - } - }, - "ci-info": { - "version": "3.2.0", - "resolved": "https://registry.npmjs.org/ci-info/-/ci-info-3.2.0.tgz", - "integrity": "sha512-dVqRX7fLUm8J6FgHJ418XuIgDLZDkYcDFTeL6TA2gt5WlIZUQrrH6EZrNClwT/H0FateUsZkGIOPRrLbP+PR9A==" - }, - "cjs-module-lexer": { - "version": "1.2.2", - "resolved": "https://registry.npmjs.org/cjs-module-lexer/-/cjs-module-lexer-1.2.2.tgz", - "integrity": "sha512-cOU9usZw8/dXIXKtwa8pM0OTJQuJkxMN6w30csNRUerHfeQ5R6U3kkU/FtJeIf3M202OHfY2U8ccInBG7/xogA==" - }, - "clean-stack": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/clean-stack/-/clean-stack-2.2.0.tgz", - "integrity": "sha512-4diC9HaTE+KRAMWhDhrGOECgWZxoevMc5TlkObMqNSsVU62PYzXZ/SMTjzyGAFF1YusgxGcSWTEXBhp0CPwQ1A==" - }, - "cliui": { - "version": "7.0.4", - "resolved": "https://registry.npmjs.org/cliui/-/cliui-7.0.4.tgz", - "integrity": "sha512-OcRE68cOsVMXp1Yvonl/fzkQOyjLSu/8bhPDfQt0e0/Eb283TKP20Fs2MqoPsr9SwA595rRCA+QMzYc9nBP+JQ==", - "requires": { - "string-width": "^4.2.0", - "strip-ansi": "^6.0.0", - "wrap-ansi": "^7.0.0" - } - }, - "clone-response": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/clone-response/-/clone-response-1.0.2.tgz", - "integrity": "sha1-0dyXOSAxTfZ/vrlCI7TuNQI56Ws=", - "requires": { - "mimic-response": "^1.0.0" - } - }, - "co": { - "version": "4.6.0", - "resolved": "https://registry.npmjs.org/co/-/co-4.6.0.tgz", - "integrity": "sha1-bqa989hTrlTMuOR7+gvz+QMfsYQ=" - }, - "collect-v8-coverage": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/collect-v8-coverage/-/collect-v8-coverage-1.0.1.tgz", - "integrity": "sha512-iBPtljfCNcTKNAto0KEtDfZ3qzjJvqE3aTGZsbhjSBlorqpXJlaWWtPO35D+ZImoC3KWejX64o+yPGxhWSTzfg==" - }, - "color-convert": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/color-convert/-/color-convert-2.0.1.tgz", - "integrity": "sha512-RRECPsj7iu/xb5oKYcsFHSppFNnsj/52OVTRKb4zP5onXwVF3zVmmToNcOfGC+CRDpfK/U584fMg38ZHCaElKQ==", - "requires": { - "color-name": "~1.1.4" - } - }, - "color-name": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/color-name/-/color-name-1.1.4.tgz", - "integrity": "sha512-dOy+3AuW3a2wNbZHIuMZpTcgjGuLU/uBL/ubcZF9OXbDo8ff4O8yVp5Bf0efS8uEoYo5q4Fx7dY9OgQGXgAsQA==" - }, - "colorette": { - "version": "1.2.2", - "resolved": "https://registry.npmjs.org/colorette/-/colorette-1.2.2.tgz", - "integrity": "sha512-MKGMzyfeuutC/ZJ1cba9NqcNpfeqMUcYmyF1ZFY6/Cn7CNSAKx6a+s48sqLqyAiZuaP2TcqMhoo+dlwFnVxT9w==" - }, - "combined-stream": { - "version": "1.0.8", - "resolved": "https://registry.npmjs.org/combined-stream/-/combined-stream-1.0.8.tgz", - "integrity": "sha512-FQN4MRfuJeHf7cBbBMJFXhKSDq+2kAArBlmRBvcvFE5BB1HZKXtSFASDhdlz9zOYwxh8lDdnvmMOe/+5cdoEdg==", - "requires": { - "delayed-stream": "~1.0.0" - } - }, - "concat-map": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", - "integrity": "sha1-2Klr13/Wjfd5OnMDajug1UBdR3s=" - }, - "convert-source-map": { - "version": "1.8.0", - "resolved": "https://registry.npmjs.org/convert-source-map/-/convert-source-map-1.8.0.tgz", - "integrity": "sha512-+OQdjP49zViI/6i7nIJpA8rAl4sV/JdPfU9nZs3VqOwGIgizICvuN2ru6fMd+4llL0tar18UYJXfZ/TWtmhUjA==", - "requires": { - "safe-buffer": "~5.1.1" - } - }, - "core-util-is": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.2.tgz", - "integrity": "sha1-tf1UIgqivFq1eqtxQMlAdUUDwac=" - }, - "cross-spawn": { - "version": "7.0.3", - "resolved": "https://registry.npmjs.org/cross-spawn/-/cross-spawn-7.0.3.tgz", - "integrity": "sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==", - "requires": { - "path-key": "^3.1.0", - "shebang-command": "^2.0.0", - "which": "^2.0.1" - } - }, - "cssom": { - "version": "0.4.4", - "resolved": "https://registry.npmjs.org/cssom/-/cssom-0.4.4.tgz", - "integrity": "sha512-p3pvU7r1MyyqbTk+WbNJIgJjG2VmTIaB10rI93LzVPrmDJKkzKYMtxxyAvQXR/NS6otuzveI7+7BBq3SjBS2mw==" - }, - "cssstyle": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/cssstyle/-/cssstyle-2.3.0.tgz", - "integrity": "sha512-AZL67abkUzIuvcHqk7c09cezpGNcxUxU4Ioi/05xHk4DQeTkWmGYftIE6ctU6AEt+Gn4n1lDStOtj7FKycP71A==", - "requires": { - "cssom": "~0.3.6" - }, - "dependencies": { - "cssom": { - "version": "0.3.8", - "resolved": "https://registry.npmjs.org/cssom/-/cssom-0.3.8.tgz", - "integrity": "sha512-b0tGHbfegbhPJpxpiBPU2sCkigAqtM9O121le6bbOlgyV+NyGyCmVfJ6QW9eRjz8CpNfWEOYBIMIGRYkLwsIYg==" - } - } - }, - "data-uri-to-buffer": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/data-uri-to-buffer/-/data-uri-to-buffer-4.0.0.tgz", - "integrity": "sha512-Vr3mLBA8qWmcuschSLAOogKgQ/Jwxulv3RNE4FXnYWRGujzrRWQI4m12fQqRkwX06C0KanhLr4hK+GydchZsaA==" - }, - "data-urls": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/data-urls/-/data-urls-2.0.0.tgz", - "integrity": "sha512-X5eWTSXO/BJmpdIKCRuKUgSCgAN0OwliVK3yPKbwIWU1Tdw5BRajxlzMidvh+gwko9AfQ9zIj52pzF91Q3YAvQ==", - "requires": { - "abab": "^2.0.3", - "whatwg-mimetype": "^2.3.0", - "whatwg-url": "^8.0.0" - } - }, - "debug": { - "version": "4.3.2", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.2.tgz", - "integrity": "sha512-mOp8wKcvj7XxC78zLgw/ZA+6TSgkoE2C/ienthhRD298T7UNwAg9diBpLRxC0mOezLl4B0xV7M0cCO6P/O0Xhw==", - "requires": { - "ms": "2.1.2" - } - }, - "decimal.js": { - "version": "10.3.1", - "resolved": "https://registry.npmjs.org/decimal.js/-/decimal.js-10.3.1.tgz", - "integrity": "sha512-V0pfhfr8suzyPGOx3nmq4aHqabehUZn6Ch9kyFpV79TGDTWFmHqUqXdabR7QHqxzrYolF4+tVmJhUG4OURg5dQ==" - }, - "decompress-response": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/decompress-response/-/decompress-response-6.0.0.tgz", - "integrity": "sha512-aW35yZM6Bb/4oJlZncMH2LCoZtJXTRxES17vE3hoRiowU2kWHaJKFkSBDnDR+cm9J+9QhXmREyIfv0pji9ejCQ==", - "requires": { - "mimic-response": "^3.1.0" - }, - "dependencies": { - "mimic-response": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/mimic-response/-/mimic-response-3.1.0.tgz", - "integrity": "sha512-z0yWI+4FDrrweS8Zmt4Ej5HdJmky15+L2e6Wgn3+iK5fWzb6T3fhNFq2+MeTRb064c6Wr4N/wv0DzQTjNzHNGQ==" - } - } - }, - "dedent": { - "version": "0.7.0", - "resolved": "https://registry.npmjs.org/dedent/-/dedent-0.7.0.tgz", - "integrity": "sha1-JJXduvbrh0q7Dhvp3yLS5aVEMmw=" - }, - "deep-is": { - "version": "0.1.3", - "resolved": "https://registry.npmjs.org/deep-is/-/deep-is-0.1.3.tgz", - "integrity": "sha1-s2nW+128E+7PUk+RsHD+7cNXzzQ=" - }, - "deepmerge": { - "version": "4.2.2", - "resolved": "https://registry.npmjs.org/deepmerge/-/deepmerge-4.2.2.tgz", - "integrity": "sha512-FJ3UgI4gIl+PHZm53knsuSFpE+nESMr7M4v9QcgB7S63Kj/6WqMiFQJpBBYz1Pt+66bZpP3Q7Lye0Oo9MPKEdg==" - }, - "defer-to-connect": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/defer-to-connect/-/defer-to-connect-2.0.1.tgz", - "integrity": "sha512-4tvttepXG1VaYGrRibk5EwJd1t4udunSOVMdLSAL6mId1ix438oPwPZMALY41FCijukO1L0twNcGsdzS7dHgDg==" - }, - "del": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/del/-/del-6.0.0.tgz", - "integrity": "sha512-1shh9DQ23L16oXSZKB2JxpL7iMy2E0S9d517ptA1P8iw0alkPtQcrKH7ru31rYtKwF499HkTu+DRzq3TCKDFRQ==", - "requires": { - "globby": "^11.0.1", - "graceful-fs": "^4.2.4", - "is-glob": "^4.0.1", - "is-path-cwd": "^2.2.0", - "is-path-inside": "^3.0.2", - "p-map": "^4.0.0", - "rimraf": "^3.0.2", - "slash": "^3.0.0" - } - }, - "delayed-stream": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/delayed-stream/-/delayed-stream-1.0.0.tgz", - "integrity": "sha1-3zrhmayt+31ECqrgsp4icrJOxhk=" - }, - "detect-newline": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/detect-newline/-/detect-newline-3.1.0.tgz", - "integrity": "sha512-TLz+x/vEXm/Y7P7wn1EJFNLxYpUD4TgMosxY6fAVJUnJMbupHBOncxyWUG9OpTaH9EBD7uFI5LfEgmMOc54DsA==" - }, - "diff-sequences": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/diff-sequences/-/diff-sequences-27.0.6.tgz", - "integrity": "sha512-ag6wfpBFyNXZ0p8pcuIDS//D8H062ZQJ3fzYxjpmeKjnz8W4pekL3AI8VohmyZmsWW2PWaHgjsmqR6L13101VQ==" - }, - "dir-glob": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/dir-glob/-/dir-glob-3.0.1.tgz", - "integrity": "sha512-WkrWp9GR4KXfKGYzOLmTuGVi1UWFfws377n9cc55/tb6DuqyF6pcQ5AbiHEshaDpY9v6oaSr2XCDidGmMwdzIA==", - "requires": { - "path-type": "^4.0.0" - } - }, - "domexception": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/domexception/-/domexception-2.0.1.tgz", - "integrity": "sha512-yxJ2mFy/sibVQlu5qHjOkf9J3K6zgmCxgJ94u2EdvDOV09H+32LtRswEcUsmUWN72pVLOEnTSRaIVVzVQgS0dg==", - "requires": { - "webidl-conversions": "^5.0.0" - }, - "dependencies": { - "webidl-conversions": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-5.0.0.tgz", - "integrity": "sha512-VlZwKPCkYKxQgeSbH5EyngOmRp7Ww7I9rQLERETtf5ofd9pGeswWiOtogpEO850jziPRarreGxn5QIiTqpb2wA==" - } - } - }, - "dotenv": { - "version": "10.0.0", - "resolved": "https://registry.npmjs.org/dotenv/-/dotenv-10.0.0.tgz", - "integrity": "sha512-rlBi9d8jpv9Sf1klPjNfFAuWDjKLwTIJJ/VxtoTwIR6hnZxcEOQCZg2oIL3MWBYw5GpUDKOEnND7LXTbIpQ03Q==" - }, - "electron-to-chromium": { - "version": "1.3.788", - "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.3.788.tgz", - "integrity": "sha512-dbMIpX4E4/Gk4gzOh1GYS7ls1vGsByWKpIqLviJi1mSmSt5BvrWLLtSqpFE5BaC7Ef4NnI0GMaiddNX2Brw6zA==" - }, - "emittery": { - "version": "0.8.1", - "resolved": "https://registry.npmjs.org/emittery/-/emittery-0.8.1.tgz", - "integrity": "sha512-uDfvUjVrfGJJhymx/kz6prltenw1u7WrCg1oa94zYY8xxVpLLUu045LAT0dhDZdXG58/EpPL/5kA180fQ/qudg==" - }, - "emoji-regex": { - "version": "8.0.0", - "resolved": "https://registry.npmjs.org/emoji-regex/-/emoji-regex-8.0.0.tgz", - "integrity": "sha512-MSjYzcWNOA0ewAHpz0MxpYFvwg6yjy1NG3xteoqz644VCo/RPgnr1/GGt+ic3iJTzQ8Eu3TdM14SawnVUmGE6A==" - }, - "end-of-stream": { - "version": "1.4.4", - "resolved": "https://registry.npmjs.org/end-of-stream/-/end-of-stream-1.4.4.tgz", - "integrity": "sha512-+uw1inIHVPQoaVuHzRyXd21icM+cnt4CzD5rW+NC1wjOUSTOs+Te7FOv7AhN7vS9x/oIyhLP5PR1H+phQAHu5Q==", - "requires": { - "once": "^1.4.0" - } - }, - "escalade": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", - "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==" - }, - "escape-string-regexp": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/escape-string-regexp/-/escape-string-regexp-2.0.0.tgz", - "integrity": "sha512-UpzcLCXolUWcNu5HtVMHYdXJjArjsF9C0aNnquZYY4uW/Vu0miy5YoWvbV345HauVvcAUnpRuhMMcqTcGOY2+w==" - }, - "escodegen": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/escodegen/-/escodegen-2.0.0.tgz", - "integrity": "sha512-mmHKys/C8BFUGI+MAWNcSYoORYLMdPzjrknd2Vc+bUsjN5bXcr8EhrNB+UTqfL1y3I9c4fw2ihgtMPQLBRiQxw==", - "requires": { - "esprima": "^4.0.1", - "estraverse": "^5.2.0", - "esutils": "^2.0.2", - "optionator": "^0.8.1", - "source-map": "~0.6.1" - } - }, - "esprima": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/esprima/-/esprima-4.0.1.tgz", - "integrity": "sha512-eGuFFw7Upda+g4p+QHvnW0RyTX/SVeJBDM/gCtMARO0cLuT2HcEKnTPvhjV6aGeqrCB/sbNop0Kszm0jsaWU4A==" - }, - "estraverse": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.2.0.tgz", - "integrity": "sha512-BxbNGGNm0RyRYvUdHpIwv9IWzeM9XClbOxwoATuFdOE7ZE6wHL+HQ5T8hoPM+zHvmKzzsEqhgy0GrQ5X13afiQ==" - }, - "esutils": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/esutils/-/esutils-2.0.3.tgz", - "integrity": "sha512-kVscqXk4OCp68SZ0dkgEKVi6/8ij300KBWTJq32P/dYeWTSwK41WyTxalN1eRmA5Z9UU/LX9D7FWSmV9SAYx6g==" - }, - "execa": { - "version": "5.1.1", - "resolved": "https://registry.npmjs.org/execa/-/execa-5.1.1.tgz", - "integrity": "sha512-8uSpZZocAZRBAPIEINJj3Lo9HyGitllczc27Eh5YYojjMFMn8yHMDMaUHE2Jqfq05D/wucwI4JGURyXt1vchyg==", - "requires": { - "cross-spawn": "^7.0.3", - "get-stream": "^6.0.0", - "human-signals": "^2.1.0", - "is-stream": "^2.0.0", - "merge-stream": "^2.0.0", - "npm-run-path": "^4.0.1", - "onetime": "^5.1.2", - "signal-exit": "^3.0.3", - "strip-final-newline": "^2.0.0" - }, - "dependencies": { - "get-stream": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-6.0.1.tgz", - "integrity": "sha512-ts6Wi+2j3jQjqi70w5AlN8DFnkSwC+MqmxEzdEALB2qXZYV3X/b1CTfgPLGJNMeAWxdPfU8FO1ms3NUfaHCPYg==" - } - } - }, - "exit": { - "version": "0.1.2", - "resolved": "https://registry.npmjs.org/exit/-/exit-0.1.2.tgz", - "integrity": "sha1-BjJjj42HfMghB9MKD/8aF8uhzQw=" - }, - "expect": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/expect/-/expect-27.0.6.tgz", - "integrity": "sha512-psNLt8j2kwg42jGBDSfAlU49CEZxejN1f1PlANWDZqIhBOVU/c2Pm888FcjWJzFewhIsNWfZJeLjUjtKGiPuSw==", - "requires": { - "@jest/types": "^27.0.6", - "ansi-styles": "^5.0.0", - "jest-get-type": "^27.0.6", - "jest-matcher-utils": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-regex-util": "^27.0.6" - }, - "dependencies": { - "ansi-styles": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/ansi-styles/-/ansi-styles-5.2.0.tgz", - "integrity": "sha512-Cxwpt2SfTzTtXcfOlzGEee8O+c+MmUgGrNiBcXnuWxuFJHe6a5Hz7qwhwe5OgaSYI0IJvkLqWX1ASG+cJOkEiA==" - } - } - }, - "extract-zip": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/extract-zip/-/extract-zip-2.0.1.tgz", - "integrity": "sha512-GDhU9ntwuKyGXdZBUgTIe+vXnWj0fppUEtMDL0+idd5Sta8TGpHssn/eusA9mrPr9qNDym6SxAYZjNvCn/9RBg==", - "requires": { - "@types/yauzl": "^2.9.1", - "debug": "^4.1.1", - "get-stream": "^5.1.0", - "yauzl": "^2.10.0" - } - }, - "fast-glob": { - "version": "3.2.7", - "resolved": "https://registry.npmjs.org/fast-glob/-/fast-glob-3.2.7.tgz", - "integrity": "sha512-rYGMRwip6lUMvYD3BTScMwT1HtAs2d71SMv66Vrxs0IekGZEjhM0pcMfjQPnknBt2zeCwQMEupiN02ZP4DiT1Q==", - "requires": { - "@nodelib/fs.stat": "^2.0.2", - "@nodelib/fs.walk": "^1.2.3", - "glob-parent": "^5.1.2", - "merge2": "^1.3.0", - "micromatch": "^4.0.4" - } - }, - "fast-json-stable-stringify": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", - "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" - }, - "fast-levenshtein": { - "version": "2.0.6", - "resolved": "https://registry.npmjs.org/fast-levenshtein/-/fast-levenshtein-2.0.6.tgz", - "integrity": "sha1-PYpcZog6FqMMqGQ+hR8Zuqd5eRc=" - }, - "fastq": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/fastq/-/fastq-1.11.1.tgz", - "integrity": "sha512-HOnr8Mc60eNYl1gzwp6r5RoUyAn5/glBolUzP/Ez6IFVPMPirxn/9phgL6zhOtaTy7ISwPvQ+wT+hfcRZh/bzw==", - "requires": { - "reusify": "^1.0.4" - } - }, - "fb-watchman": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/fb-watchman/-/fb-watchman-2.0.1.tgz", - "integrity": "sha512-DkPJKQeY6kKwmuMretBhr7G6Vodr7bFwDYTXIkfG1gjvNpaxBTQV3PbXg6bR1c1UP4jPOX0jHUbbHANL9vRjVg==", - "requires": { - "bser": "2.1.1" - } - }, - "fd-slicer": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/fd-slicer/-/fd-slicer-1.1.0.tgz", - "integrity": "sha1-JcfInLH5B3+IkbvmHY85Dq4lbx4=", - "requires": { - "pend": "~1.2.0" - } - }, - "fetch-blob": { - "version": "3.1.4", - "resolved": "https://registry.npmjs.org/fetch-blob/-/fetch-blob-3.1.4.tgz", - "integrity": "sha512-Eq5Xv5+VlSrYWEqKrusxY1C3Hm/hjeAsCGVG3ft7pZahlUAChpGZT/Ms1WmSLnEAisEXszjzu/s+ce6HZB2VHA==", - "requires": { - "node-domexception": "^1.0.0", - "web-streams-polyfill": "^3.0.3" - } - }, - "fill-range": { - "version": "7.0.1", - "resolved": "https://registry.npmjs.org/fill-range/-/fill-range-7.0.1.tgz", - "integrity": "sha512-qOo9F+dMUmC2Lcb4BbVvnKJxTPjCm+RRpe4gDuGrzkL7mEVl/djYSu2OdQ2Pa302N4oqkSg9ir6jaLWJ2USVpQ==", - "requires": { - "to-regex-range": "^5.0.1" - } - }, - "find-up": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/find-up/-/find-up-4.1.0.tgz", - "integrity": "sha512-PpOwAdQ/YlXQ2vj8a3h8IipDuYRi3wceVQQGYWxNINccq40Anw7BlsEXCMbt1Zt+OLA6Fq9suIpIWD0OsnISlw==", - "requires": { - "locate-path": "^5.0.0", - "path-exists": "^4.0.0" - } - }, - "follow-redirects": { - "version": "1.14.8", - "resolved": "https://registry.npmjs.org/follow-redirects/-/follow-redirects-1.14.8.tgz", - "integrity": "sha512-1x0S9UVJHsQprFcEC/qnNzBLcIxsjAV905f/UkQxbclCsoTWlacCNOpQa/anodLl2uaEKFhfWOvM2Qg77+15zA==" - }, - "form-data": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/form-data/-/form-data-3.0.1.tgz", - "integrity": "sha512-RHkBKtLWUVwd7SqRIvCZMEvAMoGUp0XU+seQiZejj0COz3RI3hWP4sCv3gZWWLjJTd7rGwcsF5eKZGii0r/hbg==", - "requires": { - "asynckit": "^0.4.0", - "combined-stream": "^1.0.8", - "mime-types": "^2.1.12" - } - }, - "formdata-polyfill": { - "version": "4.0.10", - "resolved": "https://registry.npmjs.org/formdata-polyfill/-/formdata-polyfill-4.0.10.tgz", - "integrity": "sha512-buewHzMvYL29jdeQTVILecSaZKnt/RJWjoZCF5OW60Z67/GmSLBkOFM7qh1PI3zFNtJbaZL5eQu1vLfazOwj4g==", - "requires": { - "fetch-blob": "^3.1.2" - } - }, - "fs-minipass": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/fs-minipass/-/fs-minipass-2.1.0.tgz", - "integrity": "sha512-V/JgOLFCS+R6Vcq0slCuaeWEdNC3ouDlJMNIsacH2VtALiu9mV4LPrHc5cDl8k5aw6J8jwgWWpiTo5RYhmIzvg==", - "requires": { - "minipass": "^3.0.0" - } - }, - "fs.realpath": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", - "integrity": "sha1-FQStJSMVjKpA20onh8sBQRmU6k8=" - }, - "fsevents": { - "version": "2.3.2", - "resolved": "https://registry.npmjs.org/fsevents/-/fsevents-2.3.2.tgz", - "integrity": "sha512-xiqMQR4xAeHTuB9uWm+fFRcIOgKBMiOBP+eXiyT7jsgVCq1bkVygt00oASowB7EdtpOHaaPgKt812P9ab+DDKA==", - "optional": true - }, - "function-bind": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/function-bind/-/function-bind-1.1.1.tgz", - "integrity": "sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==" - }, - "geckodriver": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/geckodriver/-/geckodriver-2.0.4.tgz", - "integrity": "sha512-3Fu75v6Ov8h5Vt25+djJU56MJA2gRctgjhvG5xGzLFTQjltPz7nojQdBHbmgWznUt3CHl8VaiDn8MaepY7B0dA==", - "requires": { - "adm-zip": "0.5.5", - "bluebird": "3.7.2", - "got": "11.8.2", - "https-proxy-agent": "5.0.0", - "tar": "6.1.9" - }, - "dependencies": { - "tar": { - "version": "6.1.9", - "resolved": "https://registry.npmjs.org/tar/-/tar-6.1.9.tgz", - "integrity": "sha512-XjLaMNl76o07zqZC/aW4lwegdY07baOH1T8w3AEfrHAdyg/oYO4ctjzEBq9Gy9fEP9oHqLIgvx6zuGDGe+bc8Q==", - "requires": { - "chownr": "^2.0.0", - "fs-minipass": "^2.0.0", - "minipass": "^3.0.0", - "minizlib": "^2.1.1", - "mkdirp": "^1.0.3", - "yallist": "^4.0.0" - } - } - } - }, - "gensync": { - "version": "1.0.0-beta.2", - "resolved": "https://registry.npmjs.org/gensync/-/gensync-1.0.0-beta.2.tgz", - "integrity": "sha512-3hN7NaskYvMDLQY55gnW3NQ+mesEAepTqlg+VEbj7zzqEMBVNhzcGYYeqFo/TlYz6eQiFcp1HcsCZO+nGgS8zg==" - }, - "get-caller-file": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/get-caller-file/-/get-caller-file-2.0.5.tgz", - "integrity": "sha512-DyFP3BM/3YHTQOCUL/w0OZHR0lpKeGrxotcHWcqNEdnltqFwXVfhEBQ94eIo34AfQpo0rGki4cyIiftY06h2Fg==" - }, - "get-package-type": { - "version": "0.1.0", - "resolved": "https://registry.npmjs.org/get-package-type/-/get-package-type-0.1.0.tgz", - "integrity": "sha512-pjzuKtY64GYfWizNAJ0fr9VqttZkNiK2iS430LtIHzjBEr6bX8Am2zm4sW4Ro5wjWW5cAlRL1qAMTcXbjNAO2Q==" - }, - "get-stream": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-5.2.0.tgz", - "integrity": "sha512-nBF+F1rAZVCu/p7rjzgA+Yb4lfYXrpl7a6VmJrU8wF9I1CKvP/QwPNZHnOlwbTkY6dvtFIzFMSyQXbLoTQPRpA==", - "requires": { - "pump": "^3.0.0" - } - }, - "glob": { - "version": "7.1.7", - "resolved": "https://registry.npmjs.org/glob/-/glob-7.1.7.tgz", - "integrity": "sha512-OvD9ENzPLbegENnYP5UUfJIirTg4+XwMWGaQfQTY0JenxNvvIKP3U3/tAQSPIu/lHxXYSZmpXlUHeqAIdKzBLQ==", - "requires": { - "fs.realpath": "^1.0.0", - "inflight": "^1.0.4", - "inherits": "2", - "minimatch": "^3.0.4", - "once": "^1.3.0", - "path-is-absolute": "^1.0.0" - } - }, - "glob-parent": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/glob-parent/-/glob-parent-5.1.2.tgz", - "integrity": "sha512-AOIgSQCepiJYwP3ARnGx+5VnTu2HBYdzbGP45eLw1vr3zB3vZLeyed1sC9hnbcOc9/SrMyM5RPQrkGz4aS9Zow==", - "requires": { - "is-glob": "^4.0.1" - } - }, - "globals": { - "version": "11.12.0", - "resolved": "https://registry.npmjs.org/globals/-/globals-11.12.0.tgz", - "integrity": "sha512-WOBp/EEGUiIsJSp7wcv/y6MO+lV9UoncWqxuFfm8eBwzWNgyfBd6Gz+IeKQ9jCmyhoH99g15M3T+QaVHFjizVA==" - }, - "globby": { - "version": "11.0.4", - "resolved": "https://registry.npmjs.org/globby/-/globby-11.0.4.tgz", - "integrity": "sha512-9O4MVG9ioZJ08ffbcyVYyLOJLk5JQ688pJ4eMGLpdWLHq/Wr1D9BlriLQyL0E+jbkuePVZXYFj47QM/v093wHg==", - "requires": { - "array-union": "^2.1.0", - "dir-glob": "^3.0.1", - "fast-glob": "^3.1.1", - "ignore": "^5.1.4", - "merge2": "^1.3.0", - "slash": "^3.0.0" - } - }, - "got": { - "version": "11.8.2", - "resolved": "https://registry.npmjs.org/got/-/got-11.8.2.tgz", - "integrity": "sha512-D0QywKgIe30ODs+fm8wMZiAcZjypcCodPNuMz5H9Mny7RJ+IjJ10BdmGW7OM7fHXP+O7r6ZwapQ/YQmMSvB0UQ==", - "requires": { - "@sindresorhus/is": "^4.0.0", - "@szmarczak/http-timer": "^4.0.5", - "@types/cacheable-request": "^6.0.1", - "@types/responselike": "^1.0.0", - "cacheable-lookup": "^5.0.3", - "cacheable-request": "^7.0.1", - "decompress-response": "^6.0.0", - "http2-wrapper": "^1.0.0-beta.5.2", - "lowercase-keys": "^2.0.0", - "p-cancelable": "^2.0.0", - "responselike": "^2.0.0" - } - }, - "graceful-fs": { - "version": "4.2.6", - "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.6.tgz", - "integrity": "sha512-nTnJ528pbqxYanhpDYsi4Rd8MAeaBA67+RZ10CM1m3bTAVFEDcd5AuA4a6W5YkGZ1iNXHzZz8T6TBKLeBuNriQ==" - }, - "has": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/has/-/has-1.0.3.tgz", - "integrity": "sha512-f2dvO0VU6Oej7RkWJGrehjbzMAjFp5/VKPp5tTpWIV4JHHZK1/BxbFRtf/siA2SWTe09caDmVtYYzWEIbBS4zw==", - "requires": { - "function-bind": "^1.1.1" - } - }, - "has-flag": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", - "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==" - }, - "html-encoding-sniffer": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/html-encoding-sniffer/-/html-encoding-sniffer-2.0.1.tgz", - "integrity": "sha512-D5JbOMBIR/TVZkubHT+OyT2705QvogUW4IBn6nHd756OwieSF9aDYFj4dv6HHEVGYbHaLETa3WggZYWWMyy3ZQ==", - "requires": { - "whatwg-encoding": "^1.0.5" - } - }, - "html-escaper": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/html-escaper/-/html-escaper-2.0.2.tgz", - "integrity": "sha512-H2iMtd0I4Mt5eYiapRdIDjp+XzelXQ0tFE4JS7YFwFevXXMmOp9myNrUvCg0D6ws8iqkRPBfKHgbwig1SmlLfg==" - }, - "http-cache-semantics": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/http-cache-semantics/-/http-cache-semantics-4.1.0.tgz", - "integrity": "sha512-carPklcUh7ROWRK7Cv27RPtdhYhUsela/ue5/jKzjegVvXDqM2ILE9Q2BGn9JZJh1g87cp56su/FgQSzcWS8cQ==" - }, - "http-proxy-agent": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/http-proxy-agent/-/http-proxy-agent-4.0.1.tgz", - "integrity": "sha512-k0zdNgqWTGA6aeIRVpvfVob4fL52dTfaehylg0Y4UvSySvOq/Y+BOyPrgpUrA7HylqvU8vIZGsRuXmspskV0Tg==", - "requires": { - "@tootallnate/once": "1", - "agent-base": "6", - "debug": "4" - } - }, - "http2-wrapper": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/http2-wrapper/-/http2-wrapper-1.0.3.tgz", - "integrity": "sha512-V+23sDMr12Wnz7iTcDeJr3O6AIxlnvT/bmaAAAP/Xda35C90p9599p0F1eHR/N1KILWSoWVAiOMFjBBXaXSMxg==", - "requires": { - "quick-lru": "^5.1.1", - "resolve-alpn": "^1.0.0" - } - }, - "https-proxy-agent": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/https-proxy-agent/-/https-proxy-agent-5.0.0.tgz", - "integrity": "sha512-EkYm5BcKUGiduxzSt3Eppko+PiNWNEpa4ySk9vTC6wDsQJW9rHSa+UhGNJoRYp7bz6Ht1eaRIa6QaJqO5rCFbA==", - "requires": { - "agent-base": "6", - "debug": "4" - } - }, - "human-signals": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/human-signals/-/human-signals-2.1.0.tgz", - "integrity": "sha512-B4FFZ6q/T2jhhksgkbEW3HBvWIfDW85snkQgawt07S7J5QXTk6BkNV+0yAeZrM5QpMAdYlocGoljn0sJ/WQkFw==" - }, - "iconv-lite": { - "version": "0.4.24", - "resolved": "https://registry.npmjs.org/iconv-lite/-/iconv-lite-0.4.24.tgz", - "integrity": "sha512-v3MXnZAcvnywkTUEZomIActle7RXXeedOR31wwl7VlyoXO4Qi9arvSenNQWne1TcRwhCL1HwLI21bEqdpj8/rA==", - "requires": { - "safer-buffer": ">= 2.1.2 < 3" - } - }, - "ignore": { - "version": "5.1.8", - "resolved": "https://registry.npmjs.org/ignore/-/ignore-5.1.8.tgz", - "integrity": "sha512-BMpfD7PpiETpBl/A6S498BaIJ6Y/ABT93ETbby2fP00v4EbvPBXWEoaR1UBPKs3iR53pJY7EtZk5KACI57i1Uw==" - }, - "immediate": { - "version": "3.0.6", - "resolved": "https://registry.npmjs.org/immediate/-/immediate-3.0.6.tgz", - "integrity": "sha1-nbHb0Pr43m++D13V5Wu2BigN5ps=" - }, - "import-local": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/import-local/-/import-local-3.0.2.tgz", - "integrity": "sha512-vjL3+w0oulAVZ0hBHnxa/Nm5TAurf9YLQJDhqRZyqb+VKGOB6LU8t9H1Nr5CIo16vh9XfJTOoHwU0B71S557gA==", - "requires": { - "pkg-dir": "^4.2.0", - "resolve-cwd": "^3.0.0" - } - }, - "imurmurhash": { - "version": "0.1.4", - "resolved": "https://registry.npmjs.org/imurmurhash/-/imurmurhash-0.1.4.tgz", - "integrity": "sha1-khi5srkoojixPcT7a21XbyMUU+o=" - }, - "indent-string": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/indent-string/-/indent-string-4.0.0.tgz", - "integrity": "sha512-EdDDZu4A2OyIK7Lr/2zG+w5jmbuk1DVBnEwREQvBzspBJkCEbRa8GxU1lghYcaGJCnRWibjDXlq779X1/y5xwg==" - }, - "inflight": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", - "integrity": "sha1-Sb1jMdfQLQwJvJEKEHW6gWW1bfk=", - "requires": { - "once": "^1.3.0", - "wrappy": "1" - } - }, - "inherits": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.4.tgz", - "integrity": "sha512-k/vGaX4/Yla3WzyMCvTQOXYeIHvqOKtnqBduzTHpzpQZzAskKMhZ2K+EnBiSM9zGSoIFeMpXKxa4dYeZIQqewQ==" - }, - "ip-regex": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/ip-regex/-/ip-regex-4.3.0.tgz", - "integrity": "sha512-B9ZWJxHHOHUhUjCPrMpLD4xEq35bUTClHM1S6CBU5ixQnkZmwipwgc96vAd7AAGM9TGHvJR+Uss+/Ak6UphK+Q==" - }, - "is-ci": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/is-ci/-/is-ci-3.0.0.tgz", - "integrity": "sha512-kDXyttuLeslKAHYL/K28F2YkM3x5jvFPEw3yXbRptXydjD9rpLEz+C5K5iutY9ZiUu6AP41JdvRQwF4Iqs4ZCQ==", - "requires": { - "ci-info": "^3.1.1" - } - }, - "is-core-module": { - "version": "2.5.0", - "resolved": "https://registry.npmjs.org/is-core-module/-/is-core-module-2.5.0.tgz", - "integrity": "sha512-TXCMSDsEHMEEZ6eCA8rwRDbLu55MRGmrctljsBX/2v1d9/GzqHOxW5c5oPSgrUt2vBFXebu9rGqckXGPWOlYpg==", - "requires": { - "has": "^1.0.3" - } - }, - "is-extglob": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/is-extglob/-/is-extglob-2.1.1.tgz", - "integrity": "sha1-qIwCU1eR8C7TfHahueqXc8gz+MI=" - }, - "is-fullwidth-code-point": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/is-fullwidth-code-point/-/is-fullwidth-code-point-3.0.0.tgz", - "integrity": "sha512-zymm5+u+sCsSWyD9qNaejV3DFvhCKclKdizYaJUuHA83RLjb7nSuGnddCHGv0hk+KY7BMAlsWeK4Ueg6EV6XQg==" - }, - "is-generator-fn": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/is-generator-fn/-/is-generator-fn-2.1.0.tgz", - "integrity": "sha512-cTIB4yPYL/Grw0EaSzASzg6bBy9gqCofvWN8okThAYIxKJZC+udlRAmGbM0XLeniEJSs8uEgHPGuHSe1XsOLSQ==" - }, - "is-glob": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-4.0.1.tgz", - "integrity": "sha512-5G0tKtBTFImOqDnLB2hG6Bp2qcKEFduo4tZu9MT/H6NQv/ghhy30o55ufafxJ/LdH79LLs2Kfrn85TLKyA7BUg==", - "requires": { - "is-extglob": "^2.1.1" - } - }, - "is-number": { - "version": "7.0.0", - "resolved": "https://registry.npmjs.org/is-number/-/is-number-7.0.0.tgz", - "integrity": "sha512-41Cifkg6e8TylSpdtTpeLVMqvSBEVzTttHvERD741+pnZ8ANv0004MRL43QKPDlK9cGvNp6NZWZUBlbGXYxxng==" - }, - "is-path-cwd": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/is-path-cwd/-/is-path-cwd-2.2.0.tgz", - "integrity": "sha512-w942bTcih8fdJPJmQHFzkS76NEP8Kzzvmw92cXsazb8intwLqPibPPdXf4ANdKV3rYMuuQYGIWtvz9JilB3NFQ==" - }, - "is-path-inside": { - "version": "3.0.3", - "resolved": "https://registry.npmjs.org/is-path-inside/-/is-path-inside-3.0.3.tgz", - "integrity": "sha512-Fd4gABb+ycGAmKou8eMftCupSir5lRxqf4aD/vd0cD2qc4HL07OjCeuHMr8Ro4CoMaeCKDB0/ECBOVWjTwUvPQ==" - }, - "is-potential-custom-element-name": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/is-potential-custom-element-name/-/is-potential-custom-element-name-1.0.1.tgz", - "integrity": "sha512-bCYeRA2rVibKZd+s2625gGnGF/t7DSqDs4dP7CrLA1m7jKWz6pps0LpYLJN8Q64HtmPKJ1hrN3nzPNKFEKOUiQ==" - }, - "is-stream": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/is-stream/-/is-stream-2.0.1.tgz", - "integrity": "sha512-hFoiJiTl63nn+kstHGBtewWSKnQLpyb155KHheA1l39uvtO9nWIop1p3udqPcUd/xbF1VLMO4n7OI6p7RbngDg==" - }, - "is-typedarray": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/is-typedarray/-/is-typedarray-1.0.0.tgz", - "integrity": "sha1-5HnICFjfDBsR3dppQPlgEfzaSpo=" - }, - "is-url": { - "version": "1.2.4", - "resolved": "https://registry.npmjs.org/is-url/-/is-url-1.2.4.tgz", - "integrity": "sha512-ITvGim8FhRiYe4IQ5uHSkj7pVaPDrCTkNd3yq3cV7iZAcJdHTUMPMEHcqSOy9xZ9qFenQCvi+2wjH9a1nXqHww==" - }, - "is2": { - "version": "2.0.7", - "resolved": "https://registry.npmjs.org/is2/-/is2-2.0.7.tgz", - "integrity": "sha512-4vBQoURAXC6hnLFxD4VW7uc04XiwTTl/8ydYJxKvPwkWQrSjInkuM5VZVg6BGr1/natq69zDuvO9lGpLClJqvA==", - "requires": { - "deep-is": "^0.1.3", - "ip-regex": "^4.1.0", - "is-url": "^1.2.4" - } - }, - "isarray": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", - "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=" - }, - "isexe": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/isexe/-/isexe-2.0.0.tgz", - "integrity": "sha1-6PvzdNxVb/iUehDcsFctYz8s+hA=" - }, - "istanbul-lib-coverage": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/istanbul-lib-coverage/-/istanbul-lib-coverage-3.0.0.tgz", - "integrity": "sha512-UiUIqxMgRDET6eR+o5HbfRYP1l0hqkWOs7vNxC/mggutCMUIhWMm8gAHb8tHlyfD3/l6rlgNA5cKdDzEAf6hEg==" - }, - "istanbul-lib-instrument": { - "version": "4.0.3", - "resolved": "https://registry.npmjs.org/istanbul-lib-instrument/-/istanbul-lib-instrument-4.0.3.tgz", - "integrity": "sha512-BXgQl9kf4WTCPCCpmFGoJkz/+uhvm7h7PFKUYxh7qarQd3ER33vHG//qaE8eN25l07YqZPpHXU9I09l/RD5aGQ==", - "requires": { - "@babel/core": "^7.7.5", - "@istanbuljs/schema": "^0.1.2", - "istanbul-lib-coverage": "^3.0.0", - "semver": "^6.3.0" - } - }, - "istanbul-lib-report": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/istanbul-lib-report/-/istanbul-lib-report-3.0.0.tgz", - "integrity": "sha512-wcdi+uAKzfiGT2abPpKZ0hSU1rGQjUQnLvtY5MpQ7QCTahD3VODhcu4wcfY1YtkGaDD5yuydOLINXsfbus9ROw==", - "requires": { - "istanbul-lib-coverage": "^3.0.0", - "make-dir": "^3.0.0", - "supports-color": "^7.1.0" - } - }, - "istanbul-lib-source-maps": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/istanbul-lib-source-maps/-/istanbul-lib-source-maps-4.0.0.tgz", - "integrity": "sha512-c16LpFRkR8vQXyHZ5nLpY35JZtzj1PQY1iZmesUbf1FZHbIupcWfjgOXBY9YHkLEQ6puz1u4Dgj6qmU/DisrZg==", - "requires": { - "debug": "^4.1.1", - "istanbul-lib-coverage": "^3.0.0", - "source-map": "^0.6.1" - } - }, - "istanbul-reports": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/istanbul-reports/-/istanbul-reports-3.0.2.tgz", - "integrity": "sha512-9tZvz7AiR3PEDNGiV9vIouQ/EAcqMXFmkcA1CDFTwOB98OZVDL0PH9glHotf5Ugp6GCOTypfzGWI/OqjWNCRUw==", - "requires": { - "html-escaper": "^2.0.0", - "istanbul-lib-report": "^3.0.0" - } - }, - "jest": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest/-/jest-27.0.6.tgz", - "integrity": "sha512-EjV8aETrsD0wHl7CKMibKwQNQc3gIRBXlTikBmmHUeVMKaPFxdcUIBfoDqTSXDoGJIivAYGqCWVlzCSaVjPQsA==", - "requires": { - "@jest/core": "^27.0.6", - "import-local": "^3.0.2", - "jest-cli": "^27.0.6" - } - }, - "jest-changed-files": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-changed-files/-/jest-changed-files-27.0.6.tgz", - "integrity": "sha512-BuL/ZDauaq5dumYh5y20sn4IISnf1P9A0TDswTxUi84ORGtVa86ApuBHqICL0vepqAnZiY6a7xeSPWv2/yy4eA==", - "requires": { - "@jest/types": "^27.0.6", - "execa": "^5.0.0", - "throat": "^6.0.1" - } - }, - "jest-circus": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-circus/-/jest-circus-27.0.6.tgz", - "integrity": "sha512-OJlsz6BBeX9qR+7O9lXefWoc2m9ZqcZ5Ohlzz0pTEAG4xMiZUJoacY8f4YDHxgk0oKYxj277AfOk9w6hZYvi1Q==", - "requires": { - "@jest/environment": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "chalk": "^4.0.0", - "co": "^4.6.0", - "dedent": "^0.7.0", - "expect": "^27.0.6", - "is-generator-fn": "^2.0.0", - "jest-each": "^27.0.6", - "jest-matcher-utils": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-runtime": "^27.0.6", - "jest-snapshot": "^27.0.6", - "jest-util": "^27.0.6", - "pretty-format": "^27.0.6", - "slash": "^3.0.0", - "stack-utils": "^2.0.3", - "throat": "^6.0.1" - } - }, - "jest-cli": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-cli/-/jest-cli-27.0.6.tgz", - "integrity": "sha512-qUUVlGb9fdKir3RDE+B10ULI+LQrz+MCflEH2UJyoUjoHHCbxDrMxSzjQAPUMsic4SncI62ofYCcAvW6+6rhhg==", - "requires": { - "@jest/core": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/types": "^27.0.6", - "chalk": "^4.0.0", - "exit": "^0.1.2", - "graceful-fs": "^4.2.4", - "import-local": "^3.0.2", - "jest-config": "^27.0.6", - "jest-util": "^27.0.6", - "jest-validate": "^27.0.6", - "prompts": "^2.0.1", - "yargs": "^16.0.3" - } - }, - "jest-config": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-config/-/jest-config-27.0.6.tgz", - "integrity": "sha512-JZRR3I1Plr2YxPBhgqRspDE2S5zprbga3swYNrvY3HfQGu7p/GjyLOqwrYad97tX3U3mzT53TPHVmozacfP/3w==", - "requires": { - "@babel/core": "^7.1.0", - "@jest/test-sequencer": "^27.0.6", - "@jest/types": "^27.0.6", - "babel-jest": "^27.0.6", - "chalk": "^4.0.0", - "deepmerge": "^4.2.2", - "glob": "^7.1.1", - "graceful-fs": "^4.2.4", - "is-ci": "^3.0.0", - "jest-circus": "^27.0.6", - "jest-environment-jsdom": "^27.0.6", - "jest-environment-node": "^27.0.6", - "jest-get-type": "^27.0.6", - "jest-jasmine2": "^27.0.6", - "jest-regex-util": "^27.0.6", - "jest-resolve": "^27.0.6", - "jest-runner": "^27.0.6", - "jest-util": "^27.0.6", - "jest-validate": "^27.0.6", - "micromatch": "^4.0.4", - "pretty-format": "^27.0.6" - } - }, - "jest-diff": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-diff/-/jest-diff-27.0.6.tgz", - "integrity": "sha512-Z1mqgkTCSYaFgwTlP/NUiRzdqgxmmhzHY1Tq17zL94morOHfHu3K4bgSgl+CR4GLhpV8VxkuOYuIWnQ9LnFqmg==", - "requires": { - "chalk": "^4.0.0", - "diff-sequences": "^27.0.6", - "jest-get-type": "^27.0.6", - "pretty-format": "^27.0.6" - } - }, - "jest-docblock": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-docblock/-/jest-docblock-27.0.6.tgz", - "integrity": "sha512-Fid6dPcjwepTFraz0YxIMCi7dejjJ/KL9FBjPYhBp4Sv1Y9PdhImlKZqYU555BlN4TQKaTc+F2Av1z+anVyGkA==", - "requires": { - "detect-newline": "^3.0.0" - } - }, - "jest-each": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-each/-/jest-each-27.0.6.tgz", - "integrity": "sha512-m6yKcV3bkSWrUIjxkE9OC0mhBZZdhovIW5ergBYirqnkLXkyEn3oUUF/QZgyecA1cF1QFyTE8bRRl8Tfg1pfLA==", - "requires": { - "@jest/types": "^27.0.6", - "chalk": "^4.0.0", - "jest-get-type": "^27.0.6", - "jest-util": "^27.0.6", - "pretty-format": "^27.0.6" - } - }, - "jest-environment-jsdom": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-environment-jsdom/-/jest-environment-jsdom-27.0.6.tgz", - "integrity": "sha512-FvetXg7lnXL9+78H+xUAsra3IeZRTiegA3An01cWeXBspKXUhAwMM9ycIJ4yBaR0L7HkoMPaZsozCLHh4T8fuw==", - "requires": { - "@jest/environment": "^27.0.6", - "@jest/fake-timers": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "jest-mock": "^27.0.6", - "jest-util": "^27.0.6", - "jsdom": "^16.6.0" - } - }, - "jest-environment-node": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-environment-node/-/jest-environment-node-27.0.6.tgz", - "integrity": "sha512-+Vi6yLrPg/qC81jfXx3IBlVnDTI6kmRr08iVa2hFCWmJt4zha0XW7ucQltCAPhSR0FEKEoJ3i+W4E6T0s9is0w==", - "requires": { - "@jest/environment": "^27.0.6", - "@jest/fake-timers": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "jest-mock": "^27.0.6", - "jest-util": "^27.0.6" - } - }, - "jest-get-type": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-get-type/-/jest-get-type-27.0.6.tgz", - "integrity": "sha512-XTkK5exIeUbbveehcSR8w0bhH+c0yloW/Wpl+9vZrjzztCPWrxhHwkIFpZzCt71oRBsgxmuUfxEqOYoZI2macg==" - }, - "jest-haste-map": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-haste-map/-/jest-haste-map-27.0.6.tgz", - "integrity": "sha512-4ldjPXX9h8doB2JlRzg9oAZ2p6/GpQUNAeiYXqcpmrKbP0Qev0wdZlxSMOmz8mPOEnt4h6qIzXFLDi8RScX/1w==", - "requires": { - "@jest/types": "^27.0.6", - "@types/graceful-fs": "^4.1.2", - "@types/node": "*", - "anymatch": "^3.0.3", - "fb-watchman": "^2.0.0", - "fsevents": "^2.3.2", - "graceful-fs": "^4.2.4", - "jest-regex-util": "^27.0.6", - "jest-serializer": "^27.0.6", - "jest-util": "^27.0.6", - "jest-worker": "^27.0.6", - "micromatch": "^4.0.4", - "walker": "^1.0.7" - } - }, - "jest-jasmine2": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-jasmine2/-/jest-jasmine2-27.0.6.tgz", - "integrity": "sha512-cjpH2sBy+t6dvCeKBsHpW41mjHzXgsavaFMp+VWRf0eR4EW8xASk1acqmljFtK2DgyIECMv2yCdY41r2l1+4iA==", - "requires": { - "@babel/traverse": "^7.1.0", - "@jest/environment": "^27.0.6", - "@jest/source-map": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "chalk": "^4.0.0", - "co": "^4.6.0", - "expect": "^27.0.6", - "is-generator-fn": "^2.0.0", - "jest-each": "^27.0.6", - "jest-matcher-utils": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-runtime": "^27.0.6", - "jest-snapshot": "^27.0.6", - "jest-util": "^27.0.6", - "pretty-format": "^27.0.6", - "throat": "^6.0.1" - } - }, - "jest-leak-detector": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-leak-detector/-/jest-leak-detector-27.0.6.tgz", - "integrity": "sha512-2/d6n2wlH5zEcdctX4zdbgX8oM61tb67PQt4Xh8JFAIy6LRKUnX528HulkaG6nD5qDl5vRV1NXejCe1XRCH5gQ==", - "requires": { - "jest-get-type": "^27.0.6", - "pretty-format": "^27.0.6" - } - }, - "jest-matcher-utils": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-matcher-utils/-/jest-matcher-utils-27.0.6.tgz", - "integrity": "sha512-OFgF2VCQx9vdPSYTHWJ9MzFCehs20TsyFi6bIHbk5V1u52zJOnvF0Y/65z3GLZHKRuTgVPY4Z6LVePNahaQ+tA==", - "requires": { - "chalk": "^4.0.0", - "jest-diff": "^27.0.6", - "jest-get-type": "^27.0.6", - "pretty-format": "^27.0.6" - } - }, - "jest-message-util": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-message-util/-/jest-message-util-27.0.6.tgz", - "integrity": "sha512-rBxIs2XK7rGy+zGxgi+UJKP6WqQ+KrBbD1YMj517HYN3v2BG66t3Xan3FWqYHKZwjdB700KiAJ+iES9a0M+ixw==", - "requires": { - "@babel/code-frame": "^7.12.13", - "@jest/types": "^27.0.6", - "@types/stack-utils": "^2.0.0", - "chalk": "^4.0.0", - "graceful-fs": "^4.2.4", - "micromatch": "^4.0.4", - "pretty-format": "^27.0.6", - "slash": "^3.0.0", - "stack-utils": "^2.0.3" - } - }, - "jest-mock": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-mock/-/jest-mock-27.0.6.tgz", - "integrity": "sha512-lzBETUoK8cSxts2NYXSBWT+EJNzmUVtVVwS1sU9GwE1DLCfGsngg+ZVSIe0yd0ZSm+y791esiuo+WSwpXJQ5Bw==", - "requires": { - "@jest/types": "^27.0.6", - "@types/node": "*" - } - }, - "jest-pnp-resolver": { - "version": "1.2.2", - "resolved": "https://registry.npmjs.org/jest-pnp-resolver/-/jest-pnp-resolver-1.2.2.tgz", - "integrity": "sha512-olV41bKSMm8BdnuMsewT4jqlZ8+3TCARAXjZGT9jcoSnrfUnRCqnMoF9XEeoWjbzObpqF9dRhHQj0Xb9QdF6/w==" - }, - "jest-regex-util": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-regex-util/-/jest-regex-util-27.0.6.tgz", - "integrity": "sha512-SUhPzBsGa1IKm8hx2F4NfTGGp+r7BXJ4CulsZ1k2kI+mGLG+lxGrs76veN2LF/aUdGosJBzKgXmNCw+BzFqBDQ==" - }, - "jest-resolve": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-resolve/-/jest-resolve-27.0.6.tgz", - "integrity": "sha512-yKmIgw2LgTh7uAJtzv8UFHGF7Dm7XfvOe/LQ3Txv101fLM8cx2h1QVwtSJ51Q/SCxpIiKfVn6G2jYYMDNHZteA==", - "requires": { - "@jest/types": "^27.0.6", - "chalk": "^4.0.0", - "escalade": "^3.1.1", - "graceful-fs": "^4.2.4", - "jest-pnp-resolver": "^1.2.2", - "jest-util": "^27.0.6", - "jest-validate": "^27.0.6", - "resolve": "^1.20.0", - "slash": "^3.0.0" - } - }, - "jest-resolve-dependencies": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-resolve-dependencies/-/jest-resolve-dependencies-27.0.6.tgz", - "integrity": "sha512-mg9x9DS3BPAREWKCAoyg3QucCr0n6S8HEEsqRCKSPjPcu9HzRILzhdzY3imsLoZWeosEbJZz6TKasveczzpJZA==", - "requires": { - "@jest/types": "^27.0.6", - "jest-regex-util": "^27.0.6", - "jest-snapshot": "^27.0.6" - } - }, - "jest-runner": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-runner/-/jest-runner-27.0.6.tgz", - "integrity": "sha512-W3Bz5qAgaSChuivLn+nKOgjqNxM7O/9JOJoKDCqThPIg2sH/d4A/lzyiaFgnb9V1/w29Le11NpzTJSzga1vyYQ==", - "requires": { - "@jest/console": "^27.0.6", - "@jest/environment": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/transform": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "chalk": "^4.0.0", - "emittery": "^0.8.1", - "exit": "^0.1.2", - "graceful-fs": "^4.2.4", - "jest-docblock": "^27.0.6", - "jest-environment-jsdom": "^27.0.6", - "jest-environment-node": "^27.0.6", - "jest-haste-map": "^27.0.6", - "jest-leak-detector": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-resolve": "^27.0.6", - "jest-runtime": "^27.0.6", - "jest-util": "^27.0.6", - "jest-worker": "^27.0.6", - "source-map-support": "^0.5.6", - "throat": "^6.0.1" - } - }, - "jest-runtime": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-runtime/-/jest-runtime-27.0.6.tgz", - "integrity": "sha512-BhvHLRVfKibYyqqEFkybsznKwhrsu7AWx2F3y9G9L95VSIN3/ZZ9vBpm/XCS2bS+BWz3sSeNGLzI3TVQ0uL85Q==", - "requires": { - "@jest/console": "^27.0.6", - "@jest/environment": "^27.0.6", - "@jest/fake-timers": "^27.0.6", - "@jest/globals": "^27.0.6", - "@jest/source-map": "^27.0.6", - "@jest/test-result": "^27.0.6", - "@jest/transform": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/yargs": "^16.0.0", - "chalk": "^4.0.0", - "cjs-module-lexer": "^1.0.0", - "collect-v8-coverage": "^1.0.0", - "exit": "^0.1.2", - "glob": "^7.1.3", - "graceful-fs": "^4.2.4", - "jest-haste-map": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-mock": "^27.0.6", - "jest-regex-util": "^27.0.6", - "jest-resolve": "^27.0.6", - "jest-snapshot": "^27.0.6", - "jest-util": "^27.0.6", - "jest-validate": "^27.0.6", - "slash": "^3.0.0", - "strip-bom": "^4.0.0", - "yargs": "^16.0.3" - } - }, - "jest-serializer": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-serializer/-/jest-serializer-27.0.6.tgz", - "integrity": "sha512-PtGdVK9EGC7dsaziskfqaAPib6wTViY3G8E5wz9tLVPhHyiDNTZn/xjZ4khAw+09QkoOVpn7vF5nPSN6dtBexA==", - "requires": { - "@types/node": "*", - "graceful-fs": "^4.2.4" - } - }, - "jest-snapshot": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-snapshot/-/jest-snapshot-27.0.6.tgz", - "integrity": "sha512-NTHaz8He+ATUagUgE7C/UtFcRoHqR2Gc+KDfhQIyx+VFgwbeEMjeP+ILpUTLosZn/ZtbNdCF5LkVnN/l+V751A==", - "requires": { - "@babel/core": "^7.7.2", - "@babel/generator": "^7.7.2", - "@babel/parser": "^7.7.2", - "@babel/plugin-syntax-typescript": "^7.7.2", - "@babel/traverse": "^7.7.2", - "@babel/types": "^7.0.0", - "@jest/transform": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/babel__traverse": "^7.0.4", - "@types/prettier": "^2.1.5", - "babel-preset-current-node-syntax": "^1.0.0", - "chalk": "^4.0.0", - "expect": "^27.0.6", - "graceful-fs": "^4.2.4", - "jest-diff": "^27.0.6", - "jest-get-type": "^27.0.6", - "jest-haste-map": "^27.0.6", - "jest-matcher-utils": "^27.0.6", - "jest-message-util": "^27.0.6", - "jest-resolve": "^27.0.6", - "jest-util": "^27.0.6", - "natural-compare": "^1.4.0", - "pretty-format": "^27.0.6", - "semver": "^7.3.2" - }, - "dependencies": { - "semver": { - "version": "7.3.5", - "resolved": "https://registry.npmjs.org/semver/-/semver-7.3.5.tgz", - "integrity": "sha512-PoeGJYh8HK4BTO/a9Tf6ZG3veo/A7ZVsYrSA6J8ny9nb3B1VrpkuN+z9OE5wfE5p6H4LchYZsegiQgbJD94ZFQ==", - "requires": { - "lru-cache": "^6.0.0" - } - } - } - }, - "jest-util": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-util/-/jest-util-27.0.6.tgz", - "integrity": "sha512-1JjlaIh+C65H/F7D11GNkGDDZtDfMEM8EBXsvd+l/cxtgQ6QhxuloOaiayt89DxUvDarbVhqI98HhgrM1yliFQ==", - "requires": { - "@jest/types": "^27.0.6", - "@types/node": "*", - "chalk": "^4.0.0", - "graceful-fs": "^4.2.4", - "is-ci": "^3.0.0", - "picomatch": "^2.2.3" - } - }, - "jest-validate": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-validate/-/jest-validate-27.0.6.tgz", - "integrity": "sha512-yhZZOaMH3Zg6DC83n60pLmdU1DQE46DW+KLozPiPbSbPhlXXaiUTDlhHQhHFpaqIFRrInko1FHXjTRpjWRuWfA==", - "requires": { - "@jest/types": "^27.0.6", - "camelcase": "^6.2.0", - "chalk": "^4.0.0", - "jest-get-type": "^27.0.6", - "leven": "^3.1.0", - "pretty-format": "^27.0.6" - }, - "dependencies": { - "camelcase": { - "version": "6.2.0", - "resolved": "https://registry.npmjs.org/camelcase/-/camelcase-6.2.0.tgz", - "integrity": "sha512-c7wVvbw3f37nuobQNtgsgG9POC9qMbNuMQmTCqZv23b6MIz0fcYpBiOlv9gEN/hdLdnZTDQhg6e9Dq5M1vKvfg==" - } - } - }, - "jest-watcher": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-watcher/-/jest-watcher-27.0.6.tgz", - "integrity": "sha512-/jIoKBhAP00/iMGnTwUBLgvxkn7vsOweDrOTSPzc7X9uOyUtJIDthQBTI1EXz90bdkrxorUZVhJwiB69gcHtYQ==", - "requires": { - "@jest/test-result": "^27.0.6", - "@jest/types": "^27.0.6", - "@types/node": "*", - "ansi-escapes": "^4.2.1", - "chalk": "^4.0.0", - "jest-util": "^27.0.6", - "string-length": "^4.0.1" - } - }, - "jest-worker": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.0.6.tgz", - "integrity": "sha512-qupxcj/dRuA3xHPMUd40gr2EaAurFbkwzOh7wfPaeE9id7hyjURRQoqNfHifHK3XjJU6YJJUQKILGUnwGPEOCA==", - "requires": { - "@types/node": "*", - "merge-stream": "^2.0.0", - "supports-color": "^8.0.0" - }, - "dependencies": { - "supports-color": { - "version": "8.1.1", - "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", - "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", - "requires": { - "has-flag": "^4.0.0" - } - } - } - }, - "js-tokens": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/js-tokens/-/js-tokens-4.0.0.tgz", - "integrity": "sha512-RdJUflcE3cUzKiMqQgsCu06FPu9UdIJO0beYbPhHN4k6apgJtifcoCtT9bcxOpYBtpD2kCM6Sbzg4CausW/PKQ==" - }, - "js-yaml": { - "version": "3.14.1", - "resolved": "https://registry.npmjs.org/js-yaml/-/js-yaml-3.14.1.tgz", - "integrity": "sha512-okMH7OXXJ7YrN9Ok3/SXrnu4iX9yOk+25nqX4imS2npuvTYDmo/QEZoqwZkYaIDk3jVvBOTOIEgEhaLOynBS9g==", - "requires": { - "argparse": "^1.0.7", - "esprima": "^4.0.0" - } - }, - "jsdom": { - "version": "16.6.0", - "resolved": "https://registry.npmjs.org/jsdom/-/jsdom-16.6.0.tgz", - "integrity": "sha512-Ty1vmF4NHJkolaEmdjtxTfSfkdb8Ywarwf63f+F8/mDD1uLSSWDxDuMiZxiPhwunLrn9LOSVItWj4bLYsLN3Dg==", - "requires": { - "abab": "^2.0.5", - "acorn": "^8.2.4", - "acorn-globals": "^6.0.0", - "cssom": "^0.4.4", - "cssstyle": "^2.3.0", - "data-urls": "^2.0.0", - "decimal.js": "^10.2.1", - "domexception": "^2.0.1", - "escodegen": "^2.0.0", - "form-data": "^3.0.0", - "html-encoding-sniffer": "^2.0.1", - "http-proxy-agent": "^4.0.1", - "https-proxy-agent": "^5.0.0", - "is-potential-custom-element-name": "^1.0.1", - "nwsapi": "^2.2.0", - "parse5": "6.0.1", - "saxes": "^5.0.1", - "symbol-tree": "^3.2.4", - "tough-cookie": "^4.0.0", - "w3c-hr-time": "^1.0.2", - "w3c-xmlserializer": "^2.0.0", - "webidl-conversions": "^6.1.0", - "whatwg-encoding": "^1.0.5", - "whatwg-mimetype": "^2.3.0", - "whatwg-url": "^8.5.0", - "ws": "^7.4.5", - "xml-name-validator": "^3.0.0" - } - }, - "jsesc": { - "version": "2.5.2", - "resolved": "https://registry.npmjs.org/jsesc/-/jsesc-2.5.2.tgz", - "integrity": "sha512-OYu7XEzjkCQ3C5Ps3QIZsQfNpqoJyZZA99wd9aWd05NCtC5pWOkShK2mkL6HXQR6/Cy2lbNdPlZBpuQHXE63gA==" - }, - "json-buffer": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/json-buffer/-/json-buffer-3.0.1.tgz", - "integrity": "sha512-4bV5BfR2mqfQTJm+V5tPPdf+ZpuhiIvTuAB5g8kcrXOZpTT/QwwVRWBywX1ozr6lEuPdbHxwaJlm9G6mI2sfSQ==" - }, - "json5": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/json5/-/json5-2.2.0.tgz", - "integrity": "sha512-f+8cldu7X/y7RAJurMEJmdoKXGB/X550w2Nr3tTbezL6RwEE/iMcm+tZnXeoZtKuOq6ft8+CqzEkrIgx1fPoQA==", - "requires": { - "minimist": "^1.2.5" - } - }, - "jszip": { - "version": "3.7.0", - "resolved": "https://registry.npmjs.org/jszip/-/jszip-3.7.0.tgz", - "integrity": "sha512-Y2OlFIzrDOPWUnpU0LORIcDn2xN7rC9yKffFM/7pGhQuhO+SUhfm2trkJ/S5amjFvem0Y+1EALz/MEPkvHXVNw==", - "requires": { - "lie": "~3.3.0", - "pako": "~1.0.2", - "readable-stream": "~2.3.6", - "set-immediate-shim": "~1.0.1" - } - }, - "keyv": { - "version": "4.0.3", - "resolved": "https://registry.npmjs.org/keyv/-/keyv-4.0.3.tgz", - "integrity": "sha512-zdGa2TOpSZPq5mU6iowDARnMBZgtCqJ11dJROFi6tg6kTn4nuUdU09lFyLFSaHrWqpIJ+EBq4E8/Dc0Vx5vLdA==", - "requires": { - "json-buffer": "3.0.1" - } - }, - "kleur": { - "version": "3.0.3", - "resolved": "https://registry.npmjs.org/kleur/-/kleur-3.0.3.tgz", - "integrity": "sha512-eTIzlVOSUR+JxdDFepEYcBMtZ9Qqdef+rnzWdRZuMbOywu5tO2w2N7rqjoANZ5k9vywhL6Br1VRjUIgTQx4E8w==" - }, - "leven": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/leven/-/leven-3.1.0.tgz", - "integrity": "sha512-qsda+H8jTaUaN/x5vzW2rzc+8Rw4TAQ/4KjB46IwK5VH+IlVeeeje/EoZRpiXvIqjFgK84QffqPztGI3VBLG1A==" - }, - "levn": { - "version": "0.3.0", - "resolved": "https://registry.npmjs.org/levn/-/levn-0.3.0.tgz", - "integrity": "sha1-OwmSTt+fCDwEkP3UwLxEIeBHZO4=", - "requires": { - "prelude-ls": "~1.1.2", - "type-check": "~0.3.2" - } - }, - "lie": { - "version": "3.3.0", - "resolved": "https://registry.npmjs.org/lie/-/lie-3.3.0.tgz", - "integrity": "sha512-UaiMJzeWRlEujzAuw5LokY1L5ecNQYZKfmyZ9L7wDHb/p5etKaxXhohBcrw0EYby+G/NA52vRSN4N39dxHAIwQ==", - "requires": { - "immediate": "~3.0.5" - } - }, - "locate-path": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/locate-path/-/locate-path-5.0.0.tgz", - "integrity": "sha512-t7hw9pI+WvuwNJXwk5zVHpyhIqzg2qTlklJOf0mVxGSbe3Fp2VieZcduNYjaLDoy6p9uGpQEGWG87WpMKlNq8g==", - "requires": { - "p-locate": "^4.1.0" - } - }, - "lodash": { - "version": "4.17.21", - "resolved": "https://registry.npmjs.org/lodash/-/lodash-4.17.21.tgz", - "integrity": "sha512-v2kDEe57lecTulaDIuNTPy3Ry4gLGJ6Z1O3vE1krgXZNrsQ+LFTGHVxVjcXPs17LhbZVGedAJv8XZ1tvj5FvSg==" - }, - "lowercase-keys": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/lowercase-keys/-/lowercase-keys-2.0.0.tgz", - "integrity": "sha512-tqNXrS78oMOE73NMxK4EMLQsQowWf8jKooH9g7xPavRT706R6bkQJ6DY2Te7QukaZsulxa30wQ7bk0pm4XiHmA==" - }, - "lru-cache": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/lru-cache/-/lru-cache-6.0.0.tgz", - "integrity": "sha512-Jo6dJ04CmSjuznwJSS3pUeWmd/H0ffTlkXXgwZi+eq1UCmqQwCh+eLsYOYCwY991i2Fah4h1BEMCx4qThGbsiA==", - "requires": { - "yallist": "^4.0.0" - } - }, - "make-dir": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/make-dir/-/make-dir-3.1.0.tgz", - "integrity": "sha512-g3FeP20LNwhALb/6Cz6Dd4F2ngze0jz7tbzrD2wAV+o9FeNHe4rL+yK2md0J/fiSf1sa1ADhXqi5+oVwOM/eGw==", - "requires": { - "semver": "^6.0.0" - } - }, - "makeerror": { - "version": "1.0.11", - "resolved": "https://registry.npmjs.org/makeerror/-/makeerror-1.0.11.tgz", - "integrity": "sha1-4BpckQnyr3lmDk6LlYd5AYT1qWw=", - "requires": { - "tmpl": "1.0.x" - } - }, - "merge-stream": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", - "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" - }, - "merge2": { - "version": "1.4.1", - "resolved": "https://registry.npmjs.org/merge2/-/merge2-1.4.1.tgz", - "integrity": "sha512-8q7VEgMJW4J8tcfVPy8g09NcQwZdbwFEqhe/WZkoIzjn/3TGDwtOCYtXGxA3O8tPzpczCCDgv+P2P5y00ZJOOg==" - }, - "micromatch": { - "version": "4.0.4", - "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-4.0.4.tgz", - "integrity": "sha512-pRmzw/XUcwXGpD9aI9q/0XOwLNygjETJ8y0ao0wdqprrzDa4YnxLcz7fQRZr8voh8V10kGhABbNcHVk5wHgWwg==", - "requires": { - "braces": "^3.0.1", - "picomatch": "^2.2.3" - } - }, - "mime-db": { - "version": "1.48.0", - "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.48.0.tgz", - "integrity": "sha512-FM3QwxV+TnZYQ2aRqhlKBMHxk10lTbMt3bBkMAp54ddrNeVSfcQYOOKuGuy3Ddrm38I04If834fOUSq1yzslJQ==" - }, - "mime-types": { - "version": "2.1.31", - "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.31.tgz", - "integrity": "sha512-XGZnNzm3QvgKxa8dpzyhFTHmpP3l5YNusmne07VUOXxou9CqUqYa/HBy124RqtVh/O2pECas/MOcsDgpilPOPg==", - "requires": { - "mime-db": "1.48.0" - } - }, - "mimic-fn": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/mimic-fn/-/mimic-fn-2.1.0.tgz", - "integrity": "sha512-OqbOk5oEQeAZ8WXWydlu9HJjz9WVdEIvamMCcXmuqUYjTknH/sqsWvhQ3vgwKFRR1HpjvNBKQ37nbJgYzGqGcg==" - }, - "mimic-response": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/mimic-response/-/mimic-response-1.0.1.tgz", - "integrity": "sha512-j5EctnkH7amfV/q5Hgmoal1g2QHFJRraOtmx0JpIqkxhBhI/lJSl1nMpQ45hVarwNETOoWEimndZ4QK0RHxuxQ==" - }, - "minimatch": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.0.4.tgz", - "integrity": "sha512-yJHVQEhyqPLUTgt9B83PXu6W3rx4MvvHvSUvToogpwoGDOUQ+yDrR0HRot+yOCdCO7u4hX3pWft6kWBBcqh0UA==", - "requires": { - "brace-expansion": "^1.1.7" - } - }, - "minimist": { - "version": "1.2.6", - "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.6.tgz", - "integrity": "sha512-Jsjnk4bw3YJqYzbdyBiNsPWHPfO++UGG749Cxs6peCu5Xg4nrena6OVxOYxrQTqww0Jmwt+Ref8rggumkTLz9Q==" - }, - "minipass": { - "version": "3.1.3", - "resolved": "https://registry.npmjs.org/minipass/-/minipass-3.1.3.tgz", - "integrity": "sha512-Mgd2GdMVzY+x3IJ+oHnVM+KG3lA5c8tnabyJKmHSaG2kAGpudxuOf8ToDkhumF7UzME7DecbQE9uOZhNm7PuJg==", - "requires": { - "yallist": "^4.0.0" - } - }, - "minizlib": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/minizlib/-/minizlib-2.1.2.tgz", - "integrity": "sha512-bAxsR8BVfj60DWXHE3u30oHzfl4G7khkSuPW+qvpd7jFRHm7dLxOjUk1EHACJ/hxLY8phGJ0YhYHZo7jil7Qdg==", - "requires": { - "minipass": "^3.0.0", - "yallist": "^4.0.0" - } - }, - "mkdirp": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-1.0.4.tgz", - "integrity": "sha512-vVqVZQyf3WLx2Shd0qJ9xuvqgAyKPLAiqITEtqW0oIUjzo3PePDd6fW9iFz30ef7Ysp/oiWqbhszeGWW2T6Gzw==" - }, - "ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "natural-compare": { - "version": "1.4.0", - "resolved": "https://registry.npmjs.org/natural-compare/-/natural-compare-1.4.0.tgz", - "integrity": "sha1-Sr6/7tdUHywnrPspvbvRXI1bpPc=" - }, - "node-domexception": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/node-domexception/-/node-domexception-1.0.0.tgz", - "integrity": "sha512-/jKZoMpw0F8GRwl4/eLROPA3cfcXtLApP0QzLmUT/HuPCZWyB7IY9ZrMeKw2O/nFIqPQB3PVM9aYm0F312AXDQ==" - }, - "node-fetch": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/node-fetch/-/node-fetch-3.1.1.tgz", - "integrity": "sha512-SMk+vKgU77PYotRdWzqZGTZeuFKlsJ0hu4KPviQKkfY+N3vn2MIzr0rvpnYpR8MtB3IEuhlEcuOLbGvLRlA+yg==", - "requires": { - "data-uri-to-buffer": "^4.0.0", - "fetch-blob": "^3.1.3", - "formdata-polyfill": "^4.0.10" - } - }, - "node-int64": { - "version": "0.4.0", - "resolved": "https://registry.npmjs.org/node-int64/-/node-int64-0.4.0.tgz", - "integrity": "sha1-h6kGXNs1XTGC2PlM4RGIuCXGijs=" - }, - "node-modules-regexp": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/node-modules-regexp/-/node-modules-regexp-1.0.0.tgz", - "integrity": "sha1-jZ2+KJZKSsVxLpExZCEHxx6Q7EA=" - }, - "node-releases": { - "version": "1.1.73", - "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-1.1.73.tgz", - "integrity": "sha512-uW7fodD6pyW2FZNZnp/Z3hvWKeEW1Y8R1+1CnErE8cXFXzl5blBOoVB41CvMer6P6Q0S5FXDwcHgFd1Wj0U9zg==" - }, - "normalize-path": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/normalize-path/-/normalize-path-3.0.0.tgz", - "integrity": "sha512-6eZs5Ls3WtCisHWp9S2GUy8dqkpGi4BVSz3GaqiE6ezub0512ESztXUwUB6C6IKbQkY2Pnb/mD4WYojCRwcwLA==" - }, - "normalize-url": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/normalize-url/-/normalize-url-6.1.0.tgz", - "integrity": "sha512-DlL+XwOy3NxAQ8xuC0okPgK46iuVNAK01YN7RueYBqqFeGsBjV9XmCAzAdgt+667bCl5kPh9EqKKDwnaPG1I7A==" - }, - "npm-run-path": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/npm-run-path/-/npm-run-path-4.0.1.tgz", - "integrity": "sha512-S48WzZW777zhNIrn7gxOlISNAqi9ZC/uQFnRdbeIHhZhCA6UqpkOT8T1G7BvfdgP4Er8gF4sUbaS0i7QvIfCWw==", - "requires": { - "path-key": "^3.0.0" - } - }, - "nwsapi": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/nwsapi/-/nwsapi-2.2.0.tgz", - "integrity": "sha512-h2AatdwYH+JHiZpv7pt/gSX1XoRGb7L/qSIeuqA6GwYoF9w1vP1cw42TO0aI2pNyshRK5893hNSl+1//vHK7hQ==" - }, - "once": { - "version": "1.4.0", - "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", - "integrity": "sha1-WDsap3WWHUsROsF9nFC6753Xa9E=", - "requires": { - "wrappy": "1" - } - }, - "onetime": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/onetime/-/onetime-5.1.2.tgz", - "integrity": "sha512-kbpaSSGJTWdAY5KPVeMOKXSrPtr8C8C7wodJbcsd51jRnmD+GZu8Y0VoU6Dm5Z4vWr0Ig/1NKuWRKf7j5aaYSg==", - "requires": { - "mimic-fn": "^2.1.0" - } - }, - "optionator": { - "version": "0.8.3", - "resolved": "https://registry.npmjs.org/optionator/-/optionator-0.8.3.tgz", - "integrity": "sha512-+IW9pACdk3XWmmTXG8m3upGUJst5XRGzxMRjXzAuJ1XnIFNvfhjjIuYkDvysnPQ7qzqVzLt78BCruntqRhWQbA==", - "requires": { - "deep-is": "~0.1.3", - "fast-levenshtein": "~2.0.6", - "levn": "~0.3.0", - "prelude-ls": "~1.1.2", - "type-check": "~0.3.2", - "word-wrap": "~1.2.3" - } - }, - "p-cancelable": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/p-cancelable/-/p-cancelable-2.1.1.tgz", - "integrity": "sha512-BZOr3nRQHOntUjTrH8+Lh54smKHoHyur8We1V8DSMVrl5A2malOOwuJRnKRDjSnkoeBh4at6BwEnb5I7Jl31wg==" - }, - "p-each-series": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/p-each-series/-/p-each-series-2.2.0.tgz", - "integrity": "sha512-ycIL2+1V32th+8scbpTvyHNaHe02z0sjgh91XXjAk+ZeXoPN4Z46DVUnzdso0aX4KckKw0FNNFHdjZ2UsZvxiA==" - }, - "p-limit": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/p-limit/-/p-limit-2.3.0.tgz", - "integrity": "sha512-//88mFWSJx8lxCzwdAABTJL2MyWB12+eIY7MDL2SqLmAkeKU9qxRvWuSyTjm3FUmpBEMuFfckAIqEaVGUDxb6w==", - "requires": { - "p-try": "^2.0.0" - } - }, - "p-locate": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/p-locate/-/p-locate-4.1.0.tgz", - "integrity": "sha512-R79ZZ/0wAxKGu3oYMlz8jy/kbhsNrS7SKZ7PxEHBgJ5+F2mtFW2fK2cOtBh1cHYkQsbzFV7I+EoRKe6Yt0oK7A==", - "requires": { - "p-limit": "^2.2.0" - } - }, - "p-map": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/p-map/-/p-map-4.0.0.tgz", - "integrity": "sha512-/bjOqmgETBYB5BoEeGVea8dmvHb2m9GLy1E9W43yeyfP6QQCZGFNa+XRceJEuDB6zqr+gKpIAmlLebMpykw/MQ==", - "requires": { - "aggregate-error": "^3.0.0" - } - }, - "p-try": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/p-try/-/p-try-2.2.0.tgz", - "integrity": "sha512-R4nPAVTAU0B9D35/Gk3uJf/7XYbQcyohSKdvAxIRSNghFl4e71hVoGnBNQz9cWaXxO2I10KTC+3jMdvvoKw6dQ==" - }, - "pako": { - "version": "1.0.11", - "resolved": "https://registry.npmjs.org/pako/-/pako-1.0.11.tgz", - "integrity": "sha512-4hLB8Py4zZce5s4yd9XzopqwVv/yGNhV1Bl8NTmCq1763HeK2+EwVTv+leGeL13Dnh2wfbqowVPXCIO0z4taYw==" - }, - "parse5": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/parse5/-/parse5-6.0.1.tgz", - "integrity": "sha512-Ofn/CTFzRGTTxwpNEs9PP93gXShHcTq255nzRYSKe8AkVpZY7e1fpmTfOyoIvjP5HG7Z2ZM7VS9PPhQGW2pOpw==" - }, - "path-exists": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/path-exists/-/path-exists-4.0.0.tgz", - "integrity": "sha512-ak9Qy5Q7jYb2Wwcey5Fpvg2KoAc/ZIhLSLOSBmRmygPsGwkVVt0fZa0qrtMz+m6tJTAHfZQ8FnmB4MG4LWy7/w==" - }, - "path-is-absolute": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", - "integrity": "sha1-F0uSaHNVNP+8es5r9TpanhtcX18=" - }, - "path-key": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/path-key/-/path-key-3.1.1.tgz", - "integrity": "sha512-ojmeN0qd+y0jszEtoY48r0Peq5dwMEkIlCOu6Q5f41lfkswXuKtYrhgoTpLnyIcHm24Uhqx+5Tqm2InSwLhE6Q==" - }, - "path-parse": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/path-parse/-/path-parse-1.0.7.tgz", - "integrity": "sha512-LDJzPVEEEPR+y48z93A0Ed0yXb8pAByGWo/k5YYdYgpY2/2EsOsksJrq7lOHxryrVOn1ejG6oAp8ahvOIQD8sw==" - }, - "path-type": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/path-type/-/path-type-4.0.0.tgz", - "integrity": "sha512-gDKb8aZMDeD/tZWs9P6+q0J9Mwkdl6xMV8TjnGP3qJVJ06bdMgkbBlLU8IdfOsIsFz2BW1rNVT3XuNEl8zPAvw==" - }, - "pend": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/pend/-/pend-1.2.0.tgz", - "integrity": "sha1-elfrVQpng/kRUzH89GY9XI4AelA=" - }, - "picomatch": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/picomatch/-/picomatch-2.3.0.tgz", - "integrity": "sha512-lY1Q/PiJGC2zOv/z391WOTD+Z02bCgsFfvxoXXf6h7kv9o+WmsmzYqrAwY63sNgOxE4xEdq0WyUnXfKeBrSvYw==" - }, - "pirates": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/pirates/-/pirates-4.0.1.tgz", - "integrity": "sha512-WuNqLTbMI3tmfef2TKxlQmAiLHKtFhlsCZnPIpuv2Ow0RDVO8lfy1Opf4NUzlMXLjPl+Men7AuVdX6TA+s+uGA==", - "requires": { - "node-modules-regexp": "^1.0.0" - } - }, - "pkg-dir": { - "version": "4.2.0", - "resolved": "https://registry.npmjs.org/pkg-dir/-/pkg-dir-4.2.0.tgz", - "integrity": "sha512-HRDzbaKjC+AOWVXxAU/x54COGeIv9eb+6CkDSQoNTt4XyWoIJvuPsXizxu/Fr23EiekbtZwmh1IcIG/l/a10GQ==", - "requires": { - "find-up": "^4.0.0" - } - }, - "prelude-ls": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/prelude-ls/-/prelude-ls-1.1.2.tgz", - "integrity": "sha1-IZMqVJ9eUv/ZqCf1cOBL5iqX2lQ=" - }, - "pretty-format": { - "version": "27.0.6", - "resolved": "https://registry.npmjs.org/pretty-format/-/pretty-format-27.0.6.tgz", - "integrity": "sha512-8tGD7gBIENgzqA+UBzObyWqQ5B778VIFZA/S66cclyd5YkFLYs2Js7gxDKf0MXtTc9zcS7t1xhdfcElJ3YIvkQ==", - "requires": { - "@jest/types": "^27.0.6", - "ansi-regex": "^5.0.0", - "ansi-styles": "^5.0.0", - "react-is": "^17.0.1" - }, - "dependencies": { - "ansi-regex": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-5.0.1.tgz", - "integrity": "sha512-quJQXlTSUGL2LH9SUXo8VwsY4soanhgo6LNSm84E1LBcE8s3O0wpdiRzyR9z/ZZJMlMWv37qOOb9pdJlMUEKFQ==" - }, - "ansi-styles": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/ansi-styles/-/ansi-styles-5.2.0.tgz", - "integrity": "sha512-Cxwpt2SfTzTtXcfOlzGEee8O+c+MmUgGrNiBcXnuWxuFJHe6a5Hz7qwhwe5OgaSYI0IJvkLqWX1ASG+cJOkEiA==" - } - } - }, - "process-nextick-args": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.1.tgz", - "integrity": "sha512-3ouUOpQhtgrbOa17J7+uxOTpITYWaGP7/AhoR3+A+/1e9skrzelGi/dXzEYyvbxubEF6Wn2ypscTKiKJFFn1ag==" - }, - "prompts": { - "version": "2.4.1", - "resolved": "https://registry.npmjs.org/prompts/-/prompts-2.4.1.tgz", - "integrity": "sha512-EQyfIuO2hPDsX1L/blblV+H7I0knhgAd82cVneCwcdND9B8AuCDuRcBH6yIcG4dFzlOUqbazQqwGjx5xmsNLuQ==", - "requires": { - "kleur": "^3.0.3", - "sisteransi": "^1.0.5" - } - }, - "proxy-from-env": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/proxy-from-env/-/proxy-from-env-1.1.0.tgz", - "integrity": "sha512-D+zkORCbA9f1tdWRK0RaCR3GPv50cMxcrz4X8k5LTSUD1Dkw47mKJEZQNunItRTkWwgtaUSo1RVFRIG9ZXiFYg==" - }, - "psl": { - "version": "1.8.0", - "resolved": "https://registry.npmjs.org/psl/-/psl-1.8.0.tgz", - "integrity": "sha512-RIdOzyoavK+hA18OGGWDqUTsCLhtA7IcZ/6NCs4fFJaHBDab+pDDmDIByWFRQJq2Cd7r1OoQxBGKOaztq+hjIQ==" - }, - "pump": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/pump/-/pump-3.0.0.tgz", - "integrity": "sha512-LwZy+p3SFs1Pytd/jYct4wpv49HiYCqd9Rlc5ZVdk0V+8Yzv6jR5Blk3TRmPL1ft69TxP0IMZGJ+WPFU2BFhww==", - "requires": { - "end-of-stream": "^1.1.0", - "once": "^1.3.1" - } - }, - "punycode": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/punycode/-/punycode-2.1.1.tgz", - "integrity": "sha512-XRsRjdf+j5ml+y/6GKHPZbrF/8p2Yga0JPtdqTIY2Xe5ohJPD9saDJJLPvp9+NSBprVvevdXZybnj2cv8OEd0A==" - }, - "queue-microtask": { - "version": "1.2.3", - "resolved": "https://registry.npmjs.org/queue-microtask/-/queue-microtask-1.2.3.tgz", - "integrity": "sha512-NuaNSa6flKT5JaSYQzJok04JzTL1CA6aGhv5rfLW3PgqA+M2ChpZQnAC8h8i4ZFkBS8X5RqkDBHA7r4hej3K9A==" - }, - "quick-lru": { - "version": "5.1.1", - "resolved": "https://registry.npmjs.org/quick-lru/-/quick-lru-5.1.1.tgz", - "integrity": "sha512-WuyALRjWPDGtt/wzJiadO5AXY+8hZ80hVpe6MyivgraREW751X3SbhRvG3eLKOYN+8VEvqLcf3wdnt44Z4S4SA==" - }, - "react-is": { - "version": "17.0.2", - "resolved": "https://registry.npmjs.org/react-is/-/react-is-17.0.2.tgz", - "integrity": "sha512-w2GsyukL62IJnlaff/nRegPQR94C/XXamvMWmSHRJ4y7Ts/4ocGRmTHvOs8PSE6pB3dWOrD/nueuU5sduBsQ4w==" - }, - "readable-stream": { - "version": "2.3.7", - "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.3.7.tgz", - "integrity": "sha512-Ebho8K4jIbHAxnuxi7o42OrZgF/ZTNcsZj6nRKyUmkhLFq8CHItp/fy6hQZuZmP/n3yZ9VBUbp4zz/mX8hmYPw==", - "requires": { - "core-util-is": "~1.0.0", - "inherits": "~2.0.3", - "isarray": "~1.0.0", - "process-nextick-args": "~2.0.0", - "safe-buffer": "~5.1.1", - "string_decoder": "~1.1.1", - "util-deprecate": "~1.0.1" - } - }, - "require-directory": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/require-directory/-/require-directory-2.1.1.tgz", - "integrity": "sha1-jGStX9MNqxyXbiNE/+f3kqam30I=" - }, - "resolve": { - "version": "1.20.0", - "resolved": "https://registry.npmjs.org/resolve/-/resolve-1.20.0.tgz", - "integrity": "sha512-wENBPt4ySzg4ybFQW2TT1zMQucPK95HSh/nq2CFTZVOGut2+pQvSsgtda4d26YrYcr067wjbmzOG8byDPBX63A==", - "requires": { - "is-core-module": "^2.2.0", - "path-parse": "^1.0.6" - } - }, - "resolve-alpn": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/resolve-alpn/-/resolve-alpn-1.2.1.tgz", - "integrity": "sha512-0a1F4l73/ZFZOakJnQ3FvkJ2+gSTQWz/r2KE5OdDY0TxPm5h4GkqkWWfM47T7HsbnOtcJVEF4epCVy6u7Q3K+g==" - }, - "resolve-cwd": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/resolve-cwd/-/resolve-cwd-3.0.0.tgz", - "integrity": "sha512-OrZaX2Mb+rJCpH/6CpSqt9xFVpN++x01XnN2ie9g6P5/3xelLAkXWVADpdz1IHD/KFfEXyE6V0U01OQ3UO2rEg==", - "requires": { - "resolve-from": "^5.0.0" - } - }, - "resolve-from": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/resolve-from/-/resolve-from-5.0.0.tgz", - "integrity": "sha512-qYg9KP24dD5qka9J47d0aVky0N+b4fTU89LN9iDnjB5waksiC49rvMB0PrUJQGoTmH50XPiqOvAjDfaijGxYZw==" - }, - "responselike": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/responselike/-/responselike-2.0.0.tgz", - "integrity": "sha512-xH48u3FTB9VsZw7R+vvgaKeLKzT6jOogbQhEe/jewwnZgzPcnyWui2Av6JpoYZF/91uueC+lqhWqeURw5/qhCw==", - "requires": { - "lowercase-keys": "^2.0.0" - } - }, - "reusify": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/reusify/-/reusify-1.0.4.tgz", - "integrity": "sha512-U9nH88a3fc/ekCF1l0/UP1IosiuIjyTh7hBvXVMHYgVcfGvt897Xguj2UOLDeI5BG2m7/uwyaLVT6fbtCwTyzw==" - }, - "rimraf": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/rimraf/-/rimraf-3.0.2.tgz", - "integrity": "sha512-JZkJMZkAGFFPP2YqXZXPbMlMBgsxzE8ILs4lMIX/2o0L9UBw9O/Y3o6wFw/i9YLapcUJWwqbi3kdxIPdC62TIA==", - "requires": { - "glob": "^7.1.3" - } - }, - "run-parallel": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/run-parallel/-/run-parallel-1.2.0.tgz", - "integrity": "sha512-5l4VyZR86LZ/lDxZTR6jqL8AFE2S0IFLMP26AbjsLVADxHdhB/c0GUsH+y39UfCi3dzz8OlQuPmnaJOMoDHQBA==", - "requires": { - "queue-microtask": "^1.2.2" - } - }, - "safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==" - }, - "safer-buffer": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/safer-buffer/-/safer-buffer-2.1.2.tgz", - "integrity": "sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==" - }, - "saxes": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/saxes/-/saxes-5.0.1.tgz", - "integrity": "sha512-5LBh1Tls8c9xgGjw3QrMwETmTMVk0oFgvrFSvWx62llR2hcEInrKNZ2GZCCuuy2lvWrdl5jhbpeqc5hRYKFOcw==", - "requires": { - "xmlchars": "^2.2.0" - } - }, - "selenium-webdriver": { - "version": "4.0.0-beta.4", - "resolved": "https://registry.npmjs.org/selenium-webdriver/-/selenium-webdriver-4.0.0-beta.4.tgz", - "integrity": "sha512-+s/CIYkWzmnC9WASBxxVj7Lm0dcyl6OaFxwIJaFCT5WCuACiimEEr4lUnOOFP/QlKfkDQ56m+aRczaq2EvJEJg==", - "requires": { - "jszip": "^3.6.0", - "rimraf": "^3.0.2", - "tmp": "^0.2.1", - "ws": ">=7.4.6" - } - }, - "semver": { - "version": "6.3.0", - "resolved": "https://registry.npmjs.org/semver/-/semver-6.3.0.tgz", - "integrity": "sha512-b39TBaTSfV6yBrapU89p5fKekE2m/NwnDocOVruQFS1/veMgdzuPcnOM34M6CwxW8jH/lxEa5rBoDeUwu5HHTw==" - }, - "set-immediate-shim": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/set-immediate-shim/-/set-immediate-shim-1.0.1.tgz", - "integrity": "sha1-SysbJ+uAip+NzEgaWOXlb1mfP2E=" - }, - "shebang-command": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/shebang-command/-/shebang-command-2.0.0.tgz", - "integrity": "sha512-kHxr2zZpYtdmrN1qDjrrX/Z1rR1kG8Dx+gkpK1G4eXmvXswmcE1hTWBWYUzlraYw1/yZp6YuDY77YtvbN0dmDA==", - "requires": { - "shebang-regex": "^3.0.0" - } - }, - "shebang-regex": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/shebang-regex/-/shebang-regex-3.0.0.tgz", - "integrity": "sha512-7++dFhtcx3353uBaq8DDR4NuxBetBzC7ZQOhmTQInHEd6bSrXdiEyzCvG07Z44UYdLShWUyXt5M/yhz8ekcb1A==" - }, - "signal-exit": { - "version": "3.0.3", - "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.3.tgz", - "integrity": "sha512-VUJ49FC8U1OxwZLxIbTTrDvLnf/6TDgxZcK8wxR8zs13xpx7xbG60ndBlhNrFi2EMuFRoeDoJO7wthSLq42EjA==" - }, - "sisteransi": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/sisteransi/-/sisteransi-1.0.5.tgz", - "integrity": "sha512-bLGGlR1QxBcynn2d5YmDX4MGjlZvy2MRBDRNHLJ8VI6l6+9FUiyTFNJ0IveOSP0bcXgVDPRcfGqA0pjaqUpfVg==" - }, - "slash": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/slash/-/slash-3.0.0.tgz", - "integrity": "sha512-g9Q1haeby36OSStwb4ntCGGGaKsaVSjQ68fBxoQcutl5fS1vuY18H3wSt3jFyFtrkx+Kz0V1G85A4MyAdDMi2Q==" - }, - "source-map": { - "version": "0.6.1", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", - "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==" - }, - "source-map-support": { - "version": "0.5.19", - "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.19.tgz", - "integrity": "sha512-Wonm7zOCIJzBGQdB+thsPar0kYuCIzYvxZwlBa87yi/Mdjv7Tip2cyVbLj5o0cFPN4EVkuTwb3GDDyUx2DGnGw==", - "requires": { - "buffer-from": "^1.0.0", - "source-map": "^0.6.0" - } - }, - "sprintf-js": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/sprintf-js/-/sprintf-js-1.0.3.tgz", - "integrity": "sha1-BOaSb2YolTVPPdAVIDYzuFcpfiw=" - }, - "stack-utils": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/stack-utils/-/stack-utils-2.0.3.tgz", - "integrity": "sha512-gL//fkxfWUsIlFL2Tl42Cl6+HFALEaB1FU76I/Fy+oZjRreP7OPMXFlGbxM7NQsI0ZpUfw76sHnv0WNYuTb7Iw==", - "requires": { - "escape-string-regexp": "^2.0.0" - } - }, - "string-length": { - "version": "4.0.2", - "resolved": "https://registry.npmjs.org/string-length/-/string-length-4.0.2.tgz", - "integrity": "sha512-+l6rNN5fYHNhZZy41RXsYptCjA2Igmq4EG7kZAYFQI1E1VTXarr6ZPXBg6eq7Y6eK4FEhY6AJlyuFIb/v/S0VQ==", - "requires": { - "char-regex": "^1.0.2", - "strip-ansi": "^6.0.0" - } - }, - "string-width": { - "version": "4.2.2", - "resolved": "https://registry.npmjs.org/string-width/-/string-width-4.2.2.tgz", - "integrity": "sha512-XBJbT3N4JhVumXE0eoLU9DCjcaF92KLNqTmFCnG1pf8duUxFGwtP6AD6nkjw9a3IdiRtL3E2w3JDiE/xi3vOeA==", - "requires": { - "emoji-regex": "^8.0.0", - "is-fullwidth-code-point": "^3.0.0", - "strip-ansi": "^6.0.0" - } - }, - "string_decoder": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", - "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", - "requires": { - "safe-buffer": "~5.1.0" - } - }, - "strip-ansi": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.0.tgz", - "integrity": "sha512-AuvKTrTfQNYNIctbR1K/YGTR1756GycPsg7b9bdV9Duqur4gv6aKqHXah67Z8ImS7WEz5QVcOtlfW2rZEugt6w==", - "requires": { - "ansi-regex": "^5.0.0" - }, - "dependencies": { - "ansi-regex": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-5.0.1.tgz", - "integrity": "sha512-quJQXlTSUGL2LH9SUXo8VwsY4soanhgo6LNSm84E1LBcE8s3O0wpdiRzyR9z/ZZJMlMWv37qOOb9pdJlMUEKFQ==" - } - } - }, - "strip-bom": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/strip-bom/-/strip-bom-4.0.0.tgz", - "integrity": "sha512-3xurFv5tEgii33Zi8Jtp55wEIILR9eh34FAW00PZf+JnSsTmV/ioewSgQl97JHvgjoRGwPShsWm+IdrxB35d0w==" - }, - "strip-final-newline": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/strip-final-newline/-/strip-final-newline-2.0.0.tgz", - "integrity": "sha512-BrpvfNAE3dcvq7ll3xVumzjKjZQ5tI1sEUIKr3Uoks0XUl45St3FlatVqef9prk4jRDzhW6WZg+3bk93y6pLjA==" - }, - "supports-color": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-7.2.0.tgz", - "integrity": "sha512-qpCAvRl9stuOHveKsn7HncJRvv501qIacKzQlO/+Lwxc9+0q2wLyv4Dfvt80/DPn2pqOBsJdDiogXGR9+OvwRw==", - "requires": { - "has-flag": "^4.0.0" - } - }, - "supports-hyperlinks": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/supports-hyperlinks/-/supports-hyperlinks-2.2.0.tgz", - "integrity": "sha512-6sXEzV5+I5j8Bmq9/vUphGRM/RJNT9SCURJLjwfOg51heRtguGWDzcaBlgAzKhQa0EVNpPEKzQuBwZ8S8WaCeQ==", - "requires": { - "has-flag": "^4.0.0", - "supports-color": "^7.0.0" - } - }, - "symbol-tree": { - "version": "3.2.4", - "resolved": "https://registry.npmjs.org/symbol-tree/-/symbol-tree-3.2.4.tgz", - "integrity": "sha512-9QNk5KwDF+Bvz+PyObkmSYjI5ksVUYtjW7AU22r2NKcfLJcXp96hkDWU3+XndOsUb+AQ9QhfzfCT2O+CNWT5Tw==" - }, - "tar": { - "version": "6.1.11", - "resolved": "https://registry.npmjs.org/tar/-/tar-6.1.11.tgz", - "integrity": "sha512-an/KZQzQUkZCkuoAA64hM92X0Urb6VpRhAFllDzz44U2mcD5scmT3zBc4VgVpkugF580+DQn8eAFSyoQt0tznA==", - "requires": { - "chownr": "^2.0.0", - "fs-minipass": "^2.0.0", - "minipass": "^3.0.0", - "minizlib": "^2.1.1", - "mkdirp": "^1.0.3", - "yallist": "^4.0.0" - } - }, - "tcp-port-used": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/tcp-port-used/-/tcp-port-used-1.0.2.tgz", - "integrity": "sha512-l7ar8lLUD3XS1V2lfoJlCBaeoaWo/2xfYt81hM7VlvR4RrMVFqfmzfhLVk40hAb368uitje5gPtBRL1m/DGvLA==", - "requires": { - "debug": "4.3.1", - "is2": "^2.0.6" - }, - "dependencies": { - "debug": { - "version": "4.3.1", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.1.tgz", - "integrity": "sha512-doEwdvm4PCeK4K3RQN2ZC2BYUBaxwLARCqZmMjtF8a51J2Rb0xpVloFRnCODwqjpwnAoao4pelN8l3RJdv3gRQ==", - "requires": { - "ms": "2.1.2" - } - } - } - }, - "terminal-link": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/terminal-link/-/terminal-link-2.1.1.tgz", - "integrity": "sha512-un0FmiRUQNr5PJqy9kP7c40F5BOfpGlYTrxonDChEZB7pzZxRNp/bt+ymiy9/npwXya9KH99nJ/GXFIiUkYGFQ==", - "requires": { - "ansi-escapes": "^4.2.1", - "supports-hyperlinks": "^2.0.0" - } - }, - "test-exclude": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/test-exclude/-/test-exclude-6.0.0.tgz", - "integrity": "sha512-cAGWPIyOHU6zlmg88jwm7VRyXnMN7iV68OGAbYDk/Mh/xC/pzVPlQtY6ngoIH/5/tciuhGfvESU8GrHrcxD56w==", - "requires": { - "@istanbuljs/schema": "^0.1.2", - "glob": "^7.1.4", - "minimatch": "^3.0.4" - } - }, - "throat": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/throat/-/throat-6.0.1.tgz", - "integrity": "sha512-8hmiGIJMDlwjg7dlJ4yKGLK8EsYqKgPWbG3b4wjJddKNwc7N7Dpn08Df4szr/sZdMVeOstrdYSsqzX6BYbcB+w==" - }, - "tmp": { - "version": "0.2.1", - "resolved": "https://registry.npmjs.org/tmp/-/tmp-0.2.1.tgz", - "integrity": "sha512-76SUhtfqR2Ijn+xllcI5P1oyannHNHByD80W1q447gU3mp9G9PSpGdWmjUOHRDPiHYacIk66W7ubDTuPF3BEtQ==", - "requires": { - "rimraf": "^3.0.0" - } - }, - "tmpl": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/tmpl/-/tmpl-1.0.5.tgz", - "integrity": "sha512-3f0uOEAQwIqGuWW2MVzYg8fV/QNnc/IpuJNG837rLuczAaLVHslWHZQj4IGiEl5Hs3kkbhwL9Ab7Hrsmuj+Smw==" - }, - "to-fast-properties": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/to-fast-properties/-/to-fast-properties-2.0.0.tgz", - "integrity": "sha1-3F5pjL0HkmW8c+A3doGk5Og/YW4=" - }, - "to-regex-range": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/to-regex-range/-/to-regex-range-5.0.1.tgz", - "integrity": "sha512-65P7iz6X5yEr1cwcgvQxbbIw7Uk3gOy5dIdtZ4rDveLqhrdJP+Li/Hx6tyK0NEb+2GCyneCMJiGqrADCSNk8sQ==", - "requires": { - "is-number": "^7.0.0" - } - }, - "tough-cookie": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/tough-cookie/-/tough-cookie-4.0.0.tgz", - "integrity": "sha512-tHdtEpQCMrc1YLrMaqXXcj6AxhYi/xgit6mZu1+EDWUn+qhUf8wMQoFIy9NXuq23zAwtcB0t/MjACGR18pcRbg==", - "requires": { - "psl": "^1.1.33", - "punycode": "^2.1.1", - "universalify": "^0.1.2" - } - }, - "tr46": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/tr46/-/tr46-2.1.0.tgz", - "integrity": "sha512-15Ih7phfcdP5YxqiB+iDtLoaTz4Nd35+IiAv0kQ5FNKHzXgdWqPoTIqEDDJmXceQt4JZk6lVPT8lnDlPpGDppw==", - "requires": { - "punycode": "^2.1.1" - } - }, - "type-check": { - "version": "0.3.2", - "resolved": "https://registry.npmjs.org/type-check/-/type-check-0.3.2.tgz", - "integrity": "sha1-WITKtRLPHTVeP7eE8wgEsrUg23I=", - "requires": { - "prelude-ls": "~1.1.2" - } - }, - "type-detect": { - "version": "4.0.8", - "resolved": "https://registry.npmjs.org/type-detect/-/type-detect-4.0.8.tgz", - "integrity": "sha512-0fr/mIH1dlO+x7TlcMy+bIDqKPsw/70tVyeHW787goQjhmqaZe10uwLujubK9q9Lg6Fiho1KUKDYz0Z7k7g5/g==" - }, - "type-fest": { - "version": "0.21.3", - "resolved": "https://registry.npmjs.org/type-fest/-/type-fest-0.21.3.tgz", - "integrity": "sha512-t0rzBq87m3fVcduHDUFhKmyyX+9eo6WQjZvf51Ea/M0Q7+T374Jp1aUiyUl0GKxp8M/OETVHSDvmkyPgvX+X2w==" - }, - "typedarray-to-buffer": { - "version": "3.1.5", - "resolved": "https://registry.npmjs.org/typedarray-to-buffer/-/typedarray-to-buffer-3.1.5.tgz", - "integrity": "sha512-zdu8XMNEDepKKR+XYOXAVPtWui0ly0NtohUscw+UmaHiAWT8hrV1rr//H6V+0DvJ3OQ19S979M0laLfX8rm82Q==", - "requires": { - "is-typedarray": "^1.0.0" - } - }, - "universalify": { - "version": "0.1.2", - "resolved": "https://registry.npmjs.org/universalify/-/universalify-0.1.2.tgz", - "integrity": "sha512-rBJeI5CXAlmy1pV+617WB9J63U6XcazHHF2f2dbJix4XzpUF0RS3Zbj0FGIOCAva5P/d/GBOYaACQ1w+0azUkg==" - }, - "util-deprecate": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", - "integrity": "sha1-RQ1Nyfpw3nMnYvvS1KKJgUGaDM8=" - }, - "v8-to-istanbul": { - "version": "8.0.0", - "resolved": "https://registry.npmjs.org/v8-to-istanbul/-/v8-to-istanbul-8.0.0.tgz", - "integrity": "sha512-LkmXi8UUNxnCC+JlH7/fsfsKr5AU110l+SYGJimWNkWhxbN5EyeOtm1MJ0hhvqMMOhGwBj1Fp70Yv9i+hX0QAg==", - "requires": { - "@types/istanbul-lib-coverage": "^2.0.1", - "convert-source-map": "^1.6.0", - "source-map": "^0.7.3" - }, - "dependencies": { - "source-map": { - "version": "0.7.3", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.7.3.tgz", - "integrity": "sha512-CkCj6giN3S+n9qrYiBTX5gystlENnRW5jZeNLHpe6aue+SrHcG5VYwujhW9s4dY31mEGsxBDrHR6oI69fTXsaQ==" - } - } - }, - "w3c-hr-time": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/w3c-hr-time/-/w3c-hr-time-1.0.2.tgz", - "integrity": "sha512-z8P5DvDNjKDoFIHK7q8r8lackT6l+jo/Ye3HOle7l9nICP9lf1Ci25fy9vHd0JOWewkIFzXIEig3TdKT7JQ5fQ==", - "requires": { - "browser-process-hrtime": "^1.0.0" - } - }, - "w3c-xmlserializer": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/w3c-xmlserializer/-/w3c-xmlserializer-2.0.0.tgz", - "integrity": "sha512-4tzD0mF8iSiMiNs30BiLO3EpfGLZUT2MSX/G+o7ZywDzliWQ3OPtTZ0PTC3B3ca1UAf4cJMHB+2Bf56EriJuRA==", - "requires": { - "xml-name-validator": "^3.0.0" - } - }, - "walker": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/walker/-/walker-1.0.7.tgz", - "integrity": "sha1-L3+bj9ENZ3JisYqITijRlhjgKPs=", - "requires": { - "makeerror": "1.0.x" - } - }, - "web-streams-polyfill": { - "version": "3.2.0", - "resolved": "https://registry.npmjs.org/web-streams-polyfill/-/web-streams-polyfill-3.2.0.tgz", - "integrity": "sha512-EqPmREeOzttaLRm5HS7io98goBgZ7IVz79aDvqjD0kYXLtFZTc0T/U6wHTPKyIjb+MdN7DFIIX6hgdBEpWmfPA==" - }, - "webidl-conversions": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-6.1.0.tgz", - "integrity": "sha512-qBIvFLGiBpLjfwmYAaHPXsn+ho5xZnGvyGvsarywGNc8VyQJUMHJ8OBKGGrPER0okBeMDaan4mNBlgBROxuI8w==" - }, - "whatwg-encoding": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/whatwg-encoding/-/whatwg-encoding-1.0.5.tgz", - "integrity": "sha512-b5lim54JOPN9HtzvK9HFXvBma/rnfFeqsic0hSpjtDbVxR3dJKLc+KB4V6GgiGOvl7CY/KNh8rxSo9DKQrnUEw==", - "requires": { - "iconv-lite": "0.4.24" - } - }, - "whatwg-mimetype": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/whatwg-mimetype/-/whatwg-mimetype-2.3.0.tgz", - "integrity": "sha512-M4yMwr6mAnQz76TbJm914+gPpB/nCwvZbJU28cUD6dR004SAxDLOOSUaB1JDRqLtaOV/vi0IC5lEAGFgrjGv/g==" - }, - "whatwg-url": { - "version": "8.7.0", - "resolved": "https://registry.npmjs.org/whatwg-url/-/whatwg-url-8.7.0.tgz", - "integrity": "sha512-gAojqb/m9Q8a5IV96E3fHJM70AzCkgt4uXYX2O7EmuyOnLrViCQlsEBmF9UQIu3/aeAIp2U17rtbpZWNntQqdg==", - "requires": { - "lodash": "^4.7.0", - "tr46": "^2.1.0", - "webidl-conversions": "^6.1.0" - } - }, - "which": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", - "integrity": "sha512-BLI3Tl1TW3Pvl70l3yq3Y64i+awpwXqsGBYWkkqMtnbXgrMD+yj7rhW0kuEDxzJaYXGjEW5ogapKNMEKNMjibA==", - "requires": { - "isexe": "^2.0.0" - } - }, - "word-wrap": { - "version": "1.2.3", - "resolved": "https://registry.npmjs.org/word-wrap/-/word-wrap-1.2.3.tgz", - "integrity": "sha512-Hz/mrNwitNRh/HUAtM/VT/5VH+ygD6DV7mYKZAtHOrbs8U7lvPS6xf7EJKMF0uW1KJCl0H701g3ZGus+muE5vQ==" - }, - "wrap-ansi": { - "version": "7.0.0", - "resolved": "https://registry.npmjs.org/wrap-ansi/-/wrap-ansi-7.0.0.tgz", - "integrity": "sha512-YVGIj2kamLSTxw6NsZjoBxfSwsn0ycdesmc4p+Q21c5zPuZ1pl+NfxVdxPtdHvmNVOQ6XSYG4AUtyt/Fi7D16Q==", - "requires": { - "ansi-styles": "^4.0.0", - "string-width": "^4.1.0", - "strip-ansi": "^6.0.0" - } - }, - "wrappy": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", - "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=" - }, - "write-file-atomic": { - "version": "3.0.3", - "resolved": "https://registry.npmjs.org/write-file-atomic/-/write-file-atomic-3.0.3.tgz", - "integrity": "sha512-AvHcyZ5JnSfq3ioSyjrBkH9yW4m7Ayk8/9My/DD9onKeu/94fwrMocemO2QAJFAlnnDN+ZDS+ZjAR5ua1/PV/Q==", - "requires": { - "imurmurhash": "^0.1.4", - "is-typedarray": "^1.0.0", - "signal-exit": "^3.0.2", - "typedarray-to-buffer": "^3.1.5" - } - }, - "ws": { - "version": "7.5.3", - "resolved": "https://registry.npmjs.org/ws/-/ws-7.5.3.tgz", - "integrity": "sha512-kQ/dHIzuLrS6Je9+uv81ueZomEwH0qVYstcAQ4/Z93K8zeko9gtAbttJWzoC5ukqXY1PpoouV3+VSOqEAFt5wg==" - }, - "xml-name-validator": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/xml-name-validator/-/xml-name-validator-3.0.0.tgz", - "integrity": "sha512-A5CUptxDsvxKJEU3yO6DuWBSJz/qizqzJKOMIfUJHETbBw/sFaDxgd6fxm1ewUaM0jZ444Fc5vC5ROYurg/4Pw==" - }, - "xmlchars": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/xmlchars/-/xmlchars-2.2.0.tgz", - "integrity": "sha512-JZnDKK8B0RCDw84FNdDAIpZK+JuJw+s7Lz8nksI7SIuU3UXJJslUthsi+uWBUYOwPFwW7W7PRLRfUKpxjtjFCw==" - }, - "y18n": { - "version": "5.0.8", - "resolved": "https://registry.npmjs.org/y18n/-/y18n-5.0.8.tgz", - "integrity": "sha512-0pfFzegeDWJHJIAmTLRP2DwHjdF5s7jo9tuztdQxAhINCdvS+3nGINqPd00AphqJR/0LhANUS6/+7SCb98YOfA==" - }, - "yallist": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/yallist/-/yallist-4.0.0.tgz", - "integrity": "sha512-3wdGidZyq5PB084XLES5TpOSRA3wjXAlIWMhum2kRcv/41Sn2emQ0dycQW4uZXLejwKvg6EsvbdlVL+FYEct7A==" - }, - "yargs": { - "version": "16.2.0", - "resolved": "https://registry.npmjs.org/yargs/-/yargs-16.2.0.tgz", - "integrity": "sha512-D1mvvtDG0L5ft/jGWkLpG1+m0eQxOfaBvTNELraWj22wSVUMWxZUvYgJYcKh6jGGIkJFhH4IZPQhR4TKpc8mBw==", - "requires": { - "cliui": "^7.0.2", - "escalade": "^3.1.1", - "get-caller-file": "^2.0.5", - "require-directory": "^2.1.1", - "string-width": "^4.2.0", - "y18n": "^5.0.5", - "yargs-parser": "^20.2.2" - } - }, - "yargs-parser": { - "version": "20.2.9", - "resolved": "https://registry.npmjs.org/yargs-parser/-/yargs-parser-20.2.9.tgz", - "integrity": "sha512-y11nGElTIV+CT3Zv9t7VKl+Q3hTQoT9a1Qzezhhl6Rp21gJ/IVTW7Z3y9EWXhuUBC2Shnf+DX0antecpAwSP8w==" - }, - "yauzl": { - "version": "2.10.0", - "resolved": "https://registry.npmjs.org/yauzl/-/yauzl-2.10.0.tgz", - "integrity": "sha1-x+sXyT4RLLEIb6bY5R+wZnt5pfk=", - "requires": { - "buffer-crc32": "~0.2.3", - "fd-slicer": "~1.1.0" - } - } - } -} diff --git a/tests/headless/package.json b/tests/headless/package.json deleted file mode 100644 index df084cdf4..000000000 --- a/tests/headless/package.json +++ /dev/null @@ -1,25 +0,0 @@ -{ - "name": "links-end-to-end", - "main": "index.js", - "directories": { - "test": "tests" - }, - "scripts": { - "test": "jest --detectOpenHandles" - }, - "jest": { - "testTimeout": 35000 - }, - "author": "ChefYeum", - "dependencies": { - "ansi-regex": ">=6.0.1", - "axios": ">=0.21.2", - "chromedriver": "^92.0.1", - "dotenv": "^10.0.0", - "geckodriver": "^2.0.4", - "jest": "^27.0.6", - "node-fetch": "^3.1.1", - "selenium-webdriver": "^4.0.0-beta.4", - "tar": ">=6.1.9" - } -} diff --git a/tests/headless/tests/buttons.test.js b/tests/headless/tests/buttons.test.js deleted file mode 100644 index 706b62c14..000000000 --- a/tests/headless/tests/buttons.test.js +++ /dev/null @@ -1,39 +0,0 @@ -const { By, Key, until } = require('selenium-webdriver'); -const { loadBrowser } = require('../browserDrivers'); -const { startServer, DEFAULT_BASE_URL, LINKS_ROOT } = require('../linksServerRunner'); - -let driver, linksServer; - -beforeAll(async () => { - // Instantiate browser driver - driver = await loadBrowser(); - - // Start Links server - linksServer = await startServer(`${LINKS_ROOT}/examples/webserver/buttons.links`); - return linksServer; -}); - -afterAll(async () => { - await driver.quit(); - - process.kill(-linksServer.pid, 'SIGTERM'); -}); - -test('adds 1 + 2 to equal 3', async () => { - await driver.get(DEFAULT_BASE_URL); - - // Wait for all elements to be located - Promise.all(['input_0', 'input_1'] - .map(inputName => driver.wait(until.elementsLocated(By.name(inputName))))); - - await driver.findElement(By.name('input_0')).sendKeys('1'); - await driver.findElement(By.name('input_1')).sendKeys('2', Key.ENTER); - - // Wait for the result to load - await driver.wait(until.urlIs(DEFAULT_BASE_URL + '/#')); - - var elem = await driver.findElement(By.css('body')); - var output = await elem.getText(); - - expect(output.trim()).toBe('3'); -}); \ No newline at end of file diff --git a/tests/headless/tests/examples.dictSuggestUpdate.test.js b/tests/headless/tests/examples.dictSuggestUpdate.test.js deleted file mode 100644 index bdc291cfe..000000000 --- a/tests/headless/tests/examples.dictSuggestUpdate.test.js +++ /dev/null @@ -1,74 +0,0 @@ -const { By, error, until, Condition } = require('selenium-webdriver'); -const { loadBrowser } = require('../browserDrivers'); -const { startServer, DEFAULT_BASE_URL, LINKS_ROOT } = require('../linksServerRunner'); - -let driver, linksServer; - -beforeAll(async () => { - // Instantiate browser driver - driver = await loadBrowser(); - - // Start Links server - linksServer = await startServer(`${LINKS_ROOT}/examples/webserver/examples.links`, - `${LINKS_ROOT}/examples:${LINKS_ROOT}/examples/games:${LINKS_ROOT}/examples/handlers:${LINKS_ROOT}/examples/dictionary`, - 'config=linksconfig' - ); - - return linksServer; -}); - -afterAll(async () => { - await driver.quit(); - - process.kill(-linksServer.pid, 'SIGTERM'); -}); - -test('Test dictSuggestUpdate', async () => { - await driver.get(`${DEFAULT_BASE_URL}/examples/dictionary/dictSuggestUpdate.links`); - - const searchBar = By.xpath('/html/body/form/input'); - - const newWordInput = By.xpath('/html/body/div[2]/div/form/table/tbody/tr[1]/td[2]/input'); - const newWordMeaningInput = By.xpath('/html/body/div[2]/div/form/table/tbody/tr[2]/td[2]/textarea'); - const newWordAddButton = By.css('#add > form > table > tbody > tr:nth-child(3) > td > button'); - const allChildren = By.xpath('*'); - - // Add new word "Dee" - await driver.findElement(newWordInput).sendKeys('Dee'); - await driver.findElement(newWordMeaningInput).sendKeys('A very important person'); - await driver.findElement(newWordAddButton).click(); - - // search Dee - await driver.findElement(searchBar).sendKeys('Dee'); - - const searchResultTable = By.css('#suggestions > div > table'); - await driver.wait(until.elementLocated(searchResultTable)); - await driver.wait( - new Condition("until progress bar is complete", async (driver) => { - try { - let table = await driver.findElement(searchResultTable); - return await table.findElements(allChildren); - } catch (e) { - if (e instanceof error.StaleElementReferenceError) { - // ignore - } else { - throw e; - } - } - })); - - // confirm search result showing - const searchResult = await driver.findElement(searchResultTable); - let tableItems = (await searchResult.findElements(allChildren)) - .map(async (element) => { - const word = await element.findElement(By.xpath('td[1]')) - .then(async elem => await elem.getText()); - const definition = await element.findElement(By.xpath('td[2]/span')) - .then(async elem => await elem.getText()); - return [word, definition]; - }); - - await Promise.all(tableItems).then(resolvedItems => { - expect(resolvedItems).toContainEqual(['Dee', 'A very important person']); - }); -}); \ No newline at end of file diff --git a/tests/headless/tests/examples.factorial.test.js b/tests/headless/tests/examples.factorial.test.js deleted file mode 100644 index 4971c7fbf..000000000 --- a/tests/headless/tests/examples.factorial.test.js +++ /dev/null @@ -1,57 +0,0 @@ -const { By, until } = require('selenium-webdriver'); -const { loadBrowser } = require('../browserDrivers'); -const { startServer, DEFAULT_BASE_URL, LINKS_ROOT } = require('../linksServerRunner'); - -let driver, linksServer; - -beforeAll(async () => { - // Instantiate browser driver - driver = await loadBrowser(); - - // Start Links server - linksServer = await startServer(`${LINKS_ROOT}/examples/webserver/examples.links`, - `${LINKS_ROOT}/examples:${LINKS_ROOT}/examples/games:${LINKS_ROOT}/examples/handlers:${LINKS_ROOT}/examples/dictionary`, - 'config=linksconfig' - ); - - return linksServer; -}); - -afterAll(async () => { - await driver.quit(); - - process.kill(-linksServer.pid, 'SIGTERM'); -}); - -test('Check factorial up to 64', async () => { - await driver.get(`${DEFAULT_BASE_URL}/examples/factorial.links`); - - const inputBox = By.xpath('/html/body/form/input[1]'); - const button = By.xpath('/html/body/form/input[2]'); - - // Type '64' in the text box - // Due to refresh, the element need to be located twice. - await driver.findElement(inputBox).sendKeys('6'); - await driver.findElement(inputBox).sendKeys('4'); - await driver.findElement(button).click(); - - // Find tables - await driver.wait(until.elementsLocated(By.xpath('/html/body/table/tbody'))); - let table = await driver.findElement(By.xpath('/html/body/table/tbody')); - - // Find all rows - let rows = await table.findElements(By.css('tr')); - let factAccum = 1; - - for await (const row of rows.map(r => r.findElements(By.css('td')))) { - - // Extract two values from a row - let i = parseInt(await (row[0].getText())); - let fact = parseInt(await (row[1].getText())); - - // Accumulate factorial value - factAccum *= i; - - expect(fact).toBe(factAccum); - } -}); \ No newline at end of file diff --git a/tests/headless/tests/progress.test.js b/tests/headless/tests/progress.test.js deleted file mode 100644 index c2b189af4..000000000 --- a/tests/headless/tests/progress.test.js +++ /dev/null @@ -1,57 +0,0 @@ -const { By, until, Condition, error } = require('selenium-webdriver'); -const { loadBrowser } = require('../browserDrivers'); -const { startServer, DEFAULT_BASE_URL, LINKS_ROOT } = require('../linksServerRunner'); - -let driver, linksServer; - -beforeAll(async () => { - // Instantiate browser driver - driver = await loadBrowser(); - - // Start Links server - linksServer = await startServer(`${LINKS_ROOT}/examples/webserver/progress.links`); - return linksServer; -}); - -afterAll(async () => { - await driver.quit(); - - process.kill(-linksServer.pid, 'SIGTERM'); -}); - -test('Count up to 1234', async () => { - await driver.get(DEFAULT_BASE_URL); - - // Define locators for each element - const inputBox = By.xpath('/html/body/form/input[1]'); - const outputBar = By.id('bar'); - const submitButton = By.xpath('/html/body/form/input[2]'); - - await driver.wait(until.elementsLocated(inputBox)); - - // Insert 1234 into the input box - await driver.findElement(inputBox).sendKeys('1234'); - - // Press submit - await driver.findElement(submitButton).click(); - - // Wait for the progress bar to fill up - await driver.wait( - new Condition("until progress bar is complete", async (driver) => { - try { - let bar = await driver.findElement(outputBar); - return await bar.getCssValue('width'); - } catch (e) { - if (e instanceof error.StaleElementReferenceError) { - // ignore - } else { - throw e; - } - } - })); - - // Assert output - const elem = driver.findElement(outputBar); - const outputText = await elem.getText(); - expect(outputText.trim()).toBe('done counting to 1234'); -}); \ No newline at end of file diff --git a/tests/selenium-tests/selenium-suite.html b/tests/selenium-tests/selenium-suite.html deleted file mode 100644 index 15d1228a8..000000000 --- a/tests/selenium-tests/selenium-suite.html +++ /dev/null @@ -1,12 +0,0 @@ - - - - - - - -
- Tests -
- Simple Tests -
diff --git a/tests/selenium-tests/selenium-tests.html b/tests/selenium-tests/selenium-tests.html deleted file mode 100644 index 77b5b6564..000000000 --- a/tests/selenium-tests/selenium-tests.html +++ /dev/null @@ -1,74 +0,0 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Simple Selenium tests -
- open - - /progress.cgi - -
- type - - n - - 32 -
- click - - 0 - -
- pause - - 6000 - -
- verifyText - - bar - -done -