about summary refs log tree commit diff stats
path: root/ocaml/matt
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/matt')
-rwxr-xr-xocaml/matt/tourbin0 -> 244535 bytes
-rw-r--r--ocaml/matt/tour.cmibin0 -> 3429 bytes
-rw-r--r--ocaml/matt/tour.cmobin0 -> 10885 bytes
-rw-r--r--ocaml/matt/tour.ml458
4 files changed, 458 insertions, 0 deletions
diff --git a/ocaml/matt/tour b/ocaml/matt/tour
new file mode 100755
index 0000000..ab5916e
--- /dev/null
+++ b/ocaml/matt/tour
Binary files differdiff --git a/ocaml/matt/tour.cmi b/ocaml/matt/tour.cmi
new file mode 100644
index 0000000..a3aaf8b
--- /dev/null
+++ b/ocaml/matt/tour.cmi
Binary files differdiff --git a/ocaml/matt/tour.cmo b/ocaml/matt/tour.cmo
new file mode 100644
index 0000000..9f45240
--- /dev/null
+++ b/ocaml/matt/tour.cmo
Binary files differdiff --git a/ocaml/matt/tour.ml b/ocaml/matt/tour.ml
new file mode 100644
index 0000000..aeac457
--- /dev/null
+++ b/ocaml/matt/tour.ml
@@ -0,0 +1,458 @@
+(* OCaml Overview and Unique Features
+
+   This file provides a high-level overview of the OCaml programming language,
+   highlighting its key characteristics and unique features.
+
+   Key Differences from TypeScript:
+   - OCaml is a functional-first language, while TypeScript is object-oriented-first
+   - OCaml has a more powerful type system with algebraic data types and pattern matching
+   - OCaml's type inference is more powerful and pervasive
+   - OCaml has a module system with functors (functions over modules), which TypeScript lacks
+   - OCaml is compiled to native code, while TypeScript is compiled to JavaScript
+   - OCaml has no null/undefined - it uses Option types instead
+   - OCaml's object system is structural, while TypeScript's is nominal
+   - OCaml has no runtime type information, while TypeScript preserves types at runtime
+   - OCaml has no implicit type coercion, while TypeScript has some
+   - OCaml's pattern matching is exhaustive and checked at compile time
+
+   To compile and run this file (assuming you have OCaml installed):
+   1. Save it as `tour.ml`
+   2. Compile: `ocamlc -o tour tour.ml`
+   3. Run: `./tour`
+
+   Alternatively, you can run it in the OCaml toplevel (interpreter):
+   `ocaml tour.ml`
+   or load it into an interactive session:
+   `#use "tour.ml";;`
+*)
+
+(* Print a header for our overview *)
+let () = print_endline "=== OCaml Language Overview ==="; print_newline ()
+
+(* Basic Syntax and Hello World *)
+(* OCaml uses `let` to bind names to values.
+   The `()` is the "unit" value, similar to `void` in other languages.
+   `print_endline` prints a string followed by a newline. *)
+let hello_world () =
+  print_endline "Hello, OCaml World! 👋"
+
+let () = print_endline "-- Basic Syntax & Hello World --"; hello_world (); print_newline ()
+
+(* ## 1. Strong, Static Typing with Type Inference 🧠
+
+   OCaml has a powerful static type system that catches many errors at compile time.
+   Crucially, you often don't need to explicitly write down types; the compiler
+   infers them for you. This provides safety without excessive verbosity.
+
+   TypeScript Comparison:
+   - TypeScript also has type inference but it's less powerful
+   - OCaml's type inference works across module boundaries, TypeScript's doesn't
+   - OCaml's type system is sound by default, TypeScript's isn't
+   - OCaml has no type assertions or type casting
+   - OCaml's type system is structural for objects but nominal for other types
+*)
+let () = print_endline "-- 1. Strong Static Typing & Type Inference --"
+
+let an_integer = 42 (* Inferred as type `int` *)
+let a_float = 3.14159 (* Inferred as type `float` *)
+let a_string = "OCaml" (* Inferred as type `string` *)
+
+(* Functions are defined with `let`. Type annotations are optional but can be helpful. *)
+let add (x: int) (y: int) : int = x + y (* Explicit types *)
+let multiply x y = x * y (* Inferred: val multiply : int -> int -> int = <fun> *)
+
+let () =
+  Printf.printf "Integer: %d, Float: %f, String: %s\n" an_integer a_float a_string;
+  Printf.printf "add 5 3 = %d\n" (add 5 3);
+  Printf.printf "multiply 6 7 = %d\n" (multiply 6 7);
+  print_newline ()
+
+(* ## 2. Functional Programming Paradigm ⚙️
+
+   OCaml is a functional-first language. Functions are first-class citizens:
+   they can be passed as arguments, returned from other functions, and stored in
+   data structures. Immutability is encouraged.
+
+   TypeScript Comparison:
+   - TypeScript is multi-paradigm but OO-first
+   - OCaml has built-in support for currying, TypeScript doesn't
+   - OCaml's pattern matching is more powerful than TypeScript's switch/case
+   - OCaml has no classes by default, TypeScript does
+   - OCaml's functions are curried by default, TypeScript's aren't
+*)
+let () = print_endline "-- 2. Functional Programming --"
+
+(* Higher-order function: takes a function as an argument *)
+let apply_twice f x = f (f x)
+let increment x = x + 1
+let result_apply_twice = apply_twice increment 10 (* Result: 12 *)
+
+(* Anonymous functions (lambdas) using `fun` or `function` (for pattern matching) *)
+let numbers = [1; 2; 3; 4; 5]
+let doubled_numbers = List.map (fun x -> x * 2) numbers (* Result: [2; 4; 6; 8; 10] *)
+
+(* Currying: functions naturally take one argument at a time *)
+let add_five = add 5 (* Partial application: add_five is now a function int -> int *)
+let ten = add_five 5
+
+let () =
+  Printf.printf "apply_twice increment 10 = %d\n" result_apply_twice;
+  print_string "Doubled numbers: "; List.iter (Printf.printf "%d ") doubled_numbers; print_newline ();
+  Printf.printf "add_five 5 = %d\n" ten;
+  print_newline ()
+
+(* ## 3. Imperative Programming Features 🧱
+
+   While functional, OCaml also supports imperative programming when needed.
+   This includes mutable data structures (like references and arrays) and loops.
+*)
+let () = print_endline "-- 3. Imperative Programming --"
+
+(* References for mutable values *)
+let counter = ref 0
+let increment_counter () =
+  counter := !counter + 1 (* `!` dereferences, `:=` assigns *)
+
+let () =
+  increment_counter ();
+  increment_counter ();
+  Printf.printf "Counter value: %d\n" !counter (* Result: 2 *)
+
+(* Arrays (mutable, fixed-size) *)
+let my_array = [|10; 20; 30|]
+let () = my_array.(1) <- 25 (* Modify element at index 1 *)
+
+(* For loops *)
+let print_array_elements arr =
+  print_string "Array elements: ";
+  for i = 0 to Array.length arr - 1 do
+    Printf.printf "%d " arr.(i)
+  done;
+  print_newline ()
+
+let () = print_array_elements my_array (* Result: 10 25 30 *)
+
+(* While loops *)
+let mutable_i = ref 0
+let () =
+  print_string "While loop: ";
+  while !mutable_i < 3 do
+    Printf.printf "%d " !mutable_i;
+    mutable_i := !mutable_i + 1
+  done;
+  print_newline ();
+  print_newline ()
+
+(* ## 4. Powerful Module System & Functors 🧩
+
+   OCaml has a sophisticated module system for structuring large programs.
+   Modules (structures) group related definitions.
+   Signatures define interfaces for modules.
+   Functors are "functions from modules to modules," enabling parametric polymorphism
+   at the module level – a very powerful abstraction.
+
+   TypeScript Comparison:
+   - TypeScript has modules but no functors
+   - OCaml's modules are first-class, TypeScript's aren't
+   - OCaml's module system is more powerful for abstraction
+   - TypeScript uses namespaces and interfaces instead
+   - OCaml's functors are like higher-order modules, which TypeScript lacks
+*)
+let () = print_endline "-- 4. Module System & Functors --"
+
+(* Define a signature for a Set *)
+module type SET = sig
+  type 'a t (* Abstract type for a set *)
+  val empty : 'a t
+  val add : 'a -> 'a t -> 'a t
+  val mem : 'a -> 'a t -> bool
+  val elements : 'a t -> 'a list
+end
+
+(* Implement a Set using a list (a simple, inefficient example) *)
+module ListSet : SET = struct
+  type 'a t = 'a list
+  let empty = []
+  let add x s = if List.mem x s then s else x :: s
+  let mem = List.mem
+  let elements s = List.sort_uniq compare s
+end
+
+(* Using the ListSet module *)
+let my_int_set = ListSet.add 3 (ListSet.add 1 ListSet.empty)
+let has_3 = ListSet.mem 3 my_int_set (* true *)
+let set_elements = ListSet.elements my_int_set (* [1; 3] *)
+
+let () =
+  Printf.printf "Set contains 3: %b\n" has_3;
+  print_string "Set elements: "; List.iter (Printf.printf "%d ") set_elements; print_newline ()
+
+(* Functor example: Make a Set printable if its elements are printable *)
+module type PRINTABLE_ELEMENT = sig
+  type t
+  val to_string : t -> string
+end
+
+module MakePrintableSet (Element : PRINTABLE_ELEMENT) (S : SET) = struct
+  let print_set (set : Element.t S.t) =
+    let elems_str = S.elements set |> List.map Element.to_string |> String.concat ", " in
+    print_endline ("{" ^ elems_str ^ "}")
+end
+
+(* Instantiate the functor *)
+module IntPrintable = struct
+  type t = int
+  let to_string = string_of_int
+end
+
+module PrintableIntListSet = MakePrintableSet(IntPrintable)(ListSet)
+
+let () =
+  print_string "PrintableIntListSet: ";
+  PrintableIntListSet.print_set my_int_set;
+  print_newline ()
+
+(* ## 5. Pattern Matching 🎯
+
+   Pattern matching is a core feature used for deconstructing data types
+   (like lists, tuples, variants) and controlling program flow. It's concise,
+   expressive, and the compiler checks for exhaustiveness, preventing many bugs.
+
+   TypeScript Comparison:
+   - TypeScript has no built-in pattern matching
+   - OCaml's pattern matching is exhaustive and checked at compile time
+   - TypeScript uses switch/case which is less powerful
+   - OCaml's pattern matching works with algebraic data types
+   - TypeScript's destructuring is similar but less powerful
+*)
+let () = print_endline "-- 5. Pattern Matching --"
+
+(* Matching on lists *)
+let rec sum_list lst =
+  match lst with
+  | [] -> 0 (* Base case: empty list *)
+  | head :: tail -> head + sum_list tail (* Recursive case: head and rest of list *)
+
+let my_numbers = [1; 2; 3; 4; 5]
+let total_sum = sum_list my_numbers (* Result: 15 *)
+
+(* Variant types (Algebraic Data Types - ADTs) *)
+type shape =
+  | Circle of float (* radius *)
+  | Rectangle of float * float (* width * height *)
+  | Point
+
+let area s =
+  match s with
+  | Circle r -> Float.pi *. r *. r
+  | Rectangle (w, h) -> w *. h
+  | Point -> 0.0
+
+let circle = Circle 5.0
+let rect = Rectangle (3.0, 4.0)
+
+(* Option type for values that might be absent *)
+let divide (x : float) (y : float) : float option =
+  if y = 0.0 then None else Some (x /. y)
+
+let print_division_result x y =
+  match divide x y with
+  | Some result -> Printf.printf "%f / %f = %f\n" x y result
+  | None -> Printf.printf "Cannot divide %f by %f (division by zero)\n" x y
+
+let () =
+  Printf.printf "Sum of [1;2;3;4;5] = %d\n" total_sum;
+  Printf.printf "Area of Circle(5.0) = %f\n" (area circle);
+  Printf.printf "Area of Rectangle(3.0, 4.0) = %f\n" (area rect);
+  print_division_result 10.0 2.0;
+  print_division_result 10.0 0.0;
+  print_newline ()
+
+(* ## 6. Object-Oriented Programming 🎭
+
+   OCaml supports object-oriented programming, but it's different from class-based
+   OOP in languages like Java or C++. OCaml's objects are structurally typed.
+   Inheritance is available, but composition is often preferred.
+   OOP in OCaml is a powerful feature, often used for GUIs or complex systems,
+   but not as central as its functional aspects.
+
+   TypeScript Comparison:
+   - TypeScript's OOP is class-based, OCaml's is prototype-based
+   - OCaml's objects are structurally typed, TypeScript's are nominally typed
+   - OCaml has no private fields (uses module system instead)
+   - TypeScript has decorators, OCaml doesn't
+   - OCaml's inheritance is more flexible but less common
+*)
+let () = print_endline "-- 6. Object-Oriented Programming --"
+
+class point (initial_x : int) (initial_y : int) =
+  object (self)
+    val mutable x = initial_x
+    val mutable y = initial_y
+
+    method get_x = x
+    method get_y = y
+    method move dx dy = x <- x + dx; y <- y + dy
+    method to_string = Printf.sprintf "(%d, %d)" x y
+  end
+
+let p1 = new point 1 2
+let () = p1#move 3 1
+
+(* Structural typing example *)
+let get_x_coord (obj : < get_x : int; .. >) = obj#get_x
+
+class colored_point (ix:int) (iy:int) (c:string) =
+  object (self)
+    inherit point ix iy as super
+    val color = c
+    method get_color = color
+    method! to_string = Printf.sprintf "%s color: %s" (super#to_string) color
+  end
+
+let cp1 = new colored_point 0 0 "red"
+let () = cp1#move 5 5
+
+let () =
+  Printf.printf "Point p1: %s\n" (p1#to_string); (* (4, 3) *)
+  Printf.printf "p1's x-coordinate (using structural typing): %d\n" (get_x_coord p1);
+  Printf.printf "ColoredPoint cp1: %s\n" (cp1#to_string); (* (5, 5) color: red *)
+  print_newline ()
+
+
+(* ## 7. Automatic Memory Management (Garbage Collection) 🗑️
+
+   OCaml features an efficient generational garbage collector (GC).
+   This means developers don't need to manually allocate and deallocate memory,
+   reducing common bugs like memory leaks and dangling pointers.
+   The GC is generally fast and has low pause times.
+*)
+let () = print_endline "-- 7. Automatic Memory Management (Garbage Collection) --"
+let create_large_list n =
+  let rec aux i acc =
+    if i = 0 then acc else aux (i-1) (i :: acc)
+  in aux n []
+
+let () =
+  let _ = create_large_list 1_000_000 in (* GC will handle this *)
+  print_endline "A large list was created and will be garbage collected.";
+  print_newline ()
+
+(* ## 8. Concurrency and Parallelism (OCaml 5+) 🚀
+
+   Since OCaml 5.0, the language has native support for parallelism via "domains"
+   (mapping to OS threads) and a new system for concurrency based on "effect handlers".
+   This allows OCaml programs to take full advantage of multi-core processors.
+   Libraries like Eio build on these features to provide high-level concurrency.
+*)
+let () = print_endline "-- 8. Concurrency and Parallelism (OCaml 5+) --"
+
+(* Note: Actual parallel execution requires OCaml 5+ and potentially a library
+   like `Domainslib`. This is a conceptual illustration.
+   The `Domain` module is available from OCaml 5. *)
+
+(*
+   (* Example of spawning a domain (conceptual - run with OCaml 5+) *)
+   let domain_example () =
+     print_endline "Attempting to use Domains (requires OCaml 5+ compiler and runtime):";
+     if String.starts_with ~prefix:"5." Sys.ocaml_version then (
+       let d = Domain.spawn (fun () ->
+         print_endline "Hello from a new domain! Executing in parallel.";
+         Thread.delay 0.1; (* Simulate work *)
+         40 + 2
+       ) in
+       print_endline "Main domain continues while the other domain might be working.";
+       let result = Domain.join d in
+       Printf.printf "Result from domain: %d\n" result
+     ) else (
+       Printf.printf "Skipping Domain example: OCaml version is %s (requires 5.x.x).\n" Sys.ocaml_version
+     )
+
+   let () = domain_example (); print_newline ()
+*)
+let () =
+  Printf.printf "OCaml version: %s\n" Sys.ocaml_version;
+  if String.starts_with ~prefix:"5." Sys.ocaml_version then
+    print_endline "OCaml 5+ detected. True parallelism with Domains and effect-based concurrency are available."
+  else
+    print_endline "OCaml version < 5. Parallelism via Domains and effect-based concurrency are features of OCaml 5+.";
+  print_newline ()
+
+(* ## 9. Foreign Function Interface (FFI) 🔗
+
+   OCaml provides a robust FFI for interfacing with C code. This allows
+   leveraging existing C libraries or writing performance-critical parts in C.
+   Libraries like `ctypes` make using the FFI easier and safer.
+*)
+let () = print_endline "-- 9. Foreign Function Interface (FFI) --"
+
+(* Example of declaring an external C function (hypothetical) *)
+(*
+external c_strlen : string -> int = "caml_strlen" (* More complex for actual C strings *)
+external c_puts : string -> unit = "puts" (* Standard C puts *)
+
+let use_ffi () =
+  let s = "Hello from OCaml to C!" in
+  (*
+    This is a simplified view. Real FFI often involves more setup,
+    especially for linking and ensuring correct C function names/signatures.
+    The `external` keyword tells OCaml that the implementation is elsewhere.
+  *)
+  print_endline "Calling C functions via FFI (conceptual example):";
+  (*
+    Printf.printf "Length of '%s' (via hypothetical C strlen): %d\n" s (c_strlen s); (* This specific external might not work directly *)
+    c_puts s; (* This would call the C `puts` function *)
+  *)
+  print_endline "  (Actual FFI calls require linking with C code)";
+  print_endline "  The `ctypes` library is commonly used for safer and easier FFI."
+
+let () = use_ffi (); print_newline ()
+*)
+let () =
+  print_endline "OCaml can interface with C code seamlessly.";
+  print_endline "This is useful for system calls, performance-critical sections, or using C libraries.";
+  print_endline "The `ctypes` library provides a more abstract and type-safe way to do this.";
+  print_newline ()
+
+
+(* ## 10. Rich Ecosystem and Tooling 🛠️
+
+   OCaml has a growing ecosystem supported by:
+   - OPAM: A flexible package manager.
+   - Dune: A powerful and widely used build system.
+   - Merlin: A tool for editor integration (autocompletion, type information).
+   - Utop: An improved interactive toplevel.
+   - Many libraries for various tasks: web development (Dream, Opium),
+     data science (Owl), systems programming, etc.
+*)
+let () = print_endline "-- 10. Rich Ecosystem and Tooling --"
+let () =
+  print_endline "Key tools include:";
+  print_endline "  - OPAM (Package Manager)";
+  print_endline "  - Dune (Build System)";
+  print_endline "  - Merlin (Editor Support)";
+  print_endline "  - Utop (Enhanced Toplevel)";
+  print_endline "Libraries exist for web development, numerical computing, and much more.";
+  print_newline ()
+
+(* ## Summary of Unique Strengths:
+
+   - **Safety and Speed**: Combines strong static typing with compilation to efficient native code.
+   - **Expressiveness**: Powerful features like pattern matching, algebraic data types,
+     and functors allow for concise and elegant code.
+   - **Pragmatism**: Supports multiple paradigms (functional, imperative, OO) allowing
+     developers to choose the best tool for the job.
+   - **Mature Module System**: Excellent for building large, maintainable systems.
+   - **Modern Concurrency/Parallelism**: OCaml 5+ brings robust support for multi-core programming.
+*)
+let () = print_endline "-- Summary of Unique Strengths --"
+let () =
+  print_endline "OCaml excels in areas requiring reliability, performance, and complex logic, such as:";
+  print_endline "  - Compilers and language tooling (e.g., Rust's first compiler, Flow, Coq)";
+  print_endline "  - Formal verification and theorem provers";
+  print_endline "  - Financial systems and trading platforms";
+  print_endline "  - High-performance network applications and systems programming";
+  print_endline "  - Desktop applications (e.g., Unison File Synchronizer)";
+  print_newline ()
+
+let () = print_endline "=== End of OCaml Overview ==="
\ No newline at end of file
nt-weight: bold } /* Literal.Number.Integer.Long */
#
#
#           The Nim Compiler
#        (c) Copyright 2015 Andreas Rumpf
#
#    See the file "copying.txt", included in this
#    distribution, for details about the copyright.
#

# included from sem.nim

discard """
  hygienic templates:

    template `||` (a, b: untyped): untyped =
      let aa = a
      if aa: aa else: b

    var
      a, b: T

    echo a || b || a

  Each evaluation context has to be different and we need to perform
  some form of preliminary symbol lookup in template definitions. Hygiene is
  a way to achieve lexical scoping at compile time.
"""

const
  errImplOfXNotAllowed = "implementation of '$1' is not allowed"

type
  TSymBinding = enum
    spNone, spGenSym, spInject

proc symBinding(n: PNode): TSymBinding =
  for i in 0..<n.len:
    var it = n[i]
    var key = if it.kind == nkExprColonExpr: it[0] else: it
    if key.kind == nkIdent:
      case whichKeyword(key.ident)
      of wGensym: return spGenSym
      of wInject: return spInject
      else: discard

type
  TSymChoiceRule = enum
    scClosed, scOpen, scForceOpen

proc symChoice(c: PContext, n: PNode, s: PSym, r: TSymChoiceRule;
               isField = false): PNode =
  var
    a: PSym
    o: TOverloadIter
  var i = 0
  a = initOverloadIter(o, c, n)
  while a != nil:
    if a.kind != skModule:
      inc(i)
      if i > 1: break
    a = nextOverloadIter(o, c, n)
  let info = getCallLineInfo(n)
  if i <= 1 and r != scForceOpen:
    # XXX this makes more sense but breaks bootstrapping for now:
    # (s.kind notin routineKinds or s.magic != mNone):
    # for instance 'nextTry' is both in tables.nim and astalgo.nim ...
    if not isField or sfGenSym notin s.flags:
      result = newSymNode(s, info)
      markUsed(c, info, s)
      onUse(info, s)
    else:
      result = n
  else:
    # semantic checking requires a type; ``fitNode`` deals with it
    # appropriately
    let kind = if r == scClosed or n.kind == nkDotExpr: nkClosedSymChoice
               else: nkOpenSymChoice
    result = newNodeIT(kind, info, newTypeS(tyNone, c))
    a = initOverloadIter(o, c, n)
    while a != nil:
      if a.kind != skModule and (not isField or sfGenSym notin s.flags):
        incl(a.flags, sfUsed)
        markOwnerModuleAsUsed(c, a)
        result.add newSymNode(a, info)
        onUse(info, a)
      a = nextOverloadIter(o, c, n)

proc semBindStmt(c: PContext, n: PNode, toBind: var IntSet): PNode =
  result = copyNode(n)
  for i in 0..<n.len:
    var a = n[i]
    # If 'a' is an overloaded symbol, we used to use the first symbol
    # as a 'witness' and use the fact that subsequent lookups will yield
    # the same symbol!
    # This is however not true anymore for hygienic templates as semantic
    # processing for them changes the symbol table...
    let s = qualifiedLookUp(c, a, {checkUndeclared})
    if s != nil:
      # we need to mark all symbols:
      let sc = symChoice(c, n, s, scClosed)
      if sc.kind == nkSym:
        toBind.incl(sc.sym.id)
        result.add sc
      else:
        for x in items(sc):
          toBind.incl(x.sym.id)
          result.add x
    else:
      illFormedAst(a, c.config)

proc semMixinStmt(c: PContext, n: PNode, toMixin: var IntSet): PNode =
  result = copyNode(n)
  var count = 0
  for i in 0..<n.len:
    toMixin.incl(considerQuotedIdent(c, n[i]).id)
    let x = symChoice(c, n[i], nil, scForceOpen)
    inc count, x.len
    result.add x
  if count == 0:
    result = newNodeI(nkEmpty, n.info)

proc replaceIdentBySym(c: PContext; n: var PNode, s: PNode) =
  case n.kind
  of nkPostfix: replaceIdentBySym(c, n[1], s)
  of nkPragmaExpr: replaceIdentBySym(c, n[0], s)
  of nkIdent, nkAccQuoted, nkSym: n = s
  else: illFormedAst(n, c.config)

type
  TemplCtx = object
    c: PContext
    toBind, toMixin, toInject: IntSet
    owner: PSym
    cursorInBody: bool # only for nimsuggest
    scopeN: int
    noGenSym: int
    inTemplateHeader: int

proc getIdentNode(c: var TemplCtx, n: PNode): PNode =
  case n.kind
  of nkPostfix: result = getIdentNode(c, n[1])
  of nkPragmaExpr: result = getIdentNode(c, n[0])
  of nkIdent:
    result = n
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil:
      if s.owner == c.owner and s.kind == skParam:
        result = newSymNode(s, n.info)
  of nkAccQuoted, nkSym: result = n
  else:
    illFormedAst(n, c.c.config)
    result = n

proc isTemplParam(c: TemplCtx, n: PNode): bool {.inline.} =
  result = n.kind == nkSym and n.sym.kind == skParam and
           n.sym.owner == c.owner and sfTemplateParam in n.sym.flags

proc semTemplBody(c: var TemplCtx, n: PNode): PNode

proc openScope(c: var TemplCtx) =
  openScope(c.c)

proc closeScope(c: var TemplCtx) =
  closeScope(c.c)

proc semTemplBodyScope(c: var TemplCtx, n: PNode): PNode =
  openScope(c)
  result = semTemplBody(c, n)
  closeScope(c)

proc onlyReplaceParams(c: var TemplCtx, n: PNode): PNode =
  result = n
  if n.kind == nkIdent:
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil:
      if s.owner == c.owner and s.kind == skParam:
        incl(s.flags, sfUsed)
        result = newSymNode(s, n.info)
        onUse(n.info, s)
  else:
    for i in 0..<n.safeLen:
      result[i] = onlyReplaceParams(c, n[i])

proc newGenSym(kind: TSymKind, n: PNode, c: var TemplCtx): PSym =
  result = newSym(kind, considerQuotedIdent(c.c, n), nextSymId c.c.idgen, c.owner, n.info)
  incl(result.flags, sfGenSym)
  incl(result.flags, sfShadowed)

proc addLocalDecl(c: var TemplCtx, n: var PNode, k: TSymKind) =
  # locals default to 'gensym':
  if n.kind == nkPragmaExpr and symBinding(n[1]) == spInject:
    # even if injected, don't produce a sym choice here:
    #n = semTemplBody(c, n)
    var x = n[0]
    while true:
      case x.kind
      of nkPostfix: x = x[1]
      of nkPragmaExpr: x = x[0]
      of nkIdent: break
      of nkAccQuoted:
        # consider:  type `T TemplParam` {.inject.}
        # it suffices to return to treat it like 'inject':
        n = onlyReplaceParams(c, n)
        return
      else:
        illFormedAst(x, c.c.config)
    let ident = getIdentNode(c, x)
    if not isTemplParam(c, ident):
      c.toInject.incl(x.ident.id)
    else:
      replaceIdentBySym(c.c, n, ident)
  else:
    if (n.kind == nkPragmaExpr and n.len >= 2 and n[1].kind == nkPragma):
      let pragmaNode = n[1]
      for i in 0..<pragmaNode.len:
        let ni = pragmaNode[i]
        # see D20210801T100514
        var found = false
        if ni.kind == nkIdent:
          for a in templatePragmas:
            if ni.ident == getIdent(c.c.cache, $a):
              found = true
              break
        if not found:
          openScope(c)
          pragmaNode[i] = semTemplBody(c, pragmaNode[i])
          closeScope(c)
    let ident = getIdentNode(c, n)
    if not isTemplParam(c, ident):
      if n.kind != nkSym:
        let local = newGenSym(k, ident, c)
        addPrelimDecl(c.c, local)
        styleCheckDef(c.c.config, n.info, local)
        onDef(n.info, local)
        replaceIdentBySym(c.c, n, newSymNode(local, n.info))
        if k == skParam and c.inTemplateHeader > 0:
          local.flags.incl sfTemplateParam
    else:
      replaceIdentBySym(c.c, n, ident)

proc semTemplSymbol(c: PContext, n: PNode, s: PSym; isField: bool): PNode =
  incl(s.flags, sfUsed)
  # bug #12885; ideally sem'checking is performed again afterwards marking
  # the symbol as used properly, but the nfSem mechanism currently prevents
  # that from happening, so we mark the module as used here already:
  markOwnerModuleAsUsed(c, s)
  # we do not call onUse here, as the identifier is not really
  # resolved here. We will fixup the used identifiers later.
  case s.kind
  of skUnknown:
    # Introduced in this pass! Leave it as an identifier.
    result = n
  of OverloadableSyms-{skEnumField}:
    result = symChoice(c, n, s, scOpen, isField)
  of skGenericParam:
    if isField and sfGenSym in s.flags: result = n
    else: result = newSymNodeTypeDesc(s, c.idgen, n.info)
  of skParam:
    result = n
  of skType:
    if isField and sfGenSym in s.flags: result = n
    else: result = newSymNodeTypeDesc(s, c.idgen, n.info)
  else:
    if s.kind == skEnumField and overloadableEnums in c.features:
      result = symChoice(c, n, s, scOpen, isField)
    elif isField and sfGenSym in s.flags:
      result = n
    else:
      result = newSymNode(s, n.info)
    # Issue #12832
    when defined(nimsuggest):
      suggestSym(c.graph, n.info, s, c.graph.usageSym, false)
    # field access (dot expr) will be handled by builtinFieldAccess
    if not isField and {optStyleHint, optStyleError} * c.config.globalOptions != {}:
      styleCheckUse(c.config, n.info, s)

proc semRoutineInTemplName(c: var TemplCtx, n: PNode): PNode =
  result = n
  if n.kind == nkIdent:
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil:
      if s.owner == c.owner and (s.kind == skParam or sfGenSym in s.flags):
        incl(s.flags, sfUsed)
        result = newSymNode(s, n.info)
        onUse(n.info, s)
  else:
    for i in 0..<n.safeLen:
      result[i] = semRoutineInTemplName(c, n[i])

proc semRoutineInTemplBody(c: var TemplCtx, n: PNode, k: TSymKind): PNode =
  result = n
  checkSonsLen(n, bodyPos + 1, c.c.config)
  # routines default to 'inject':
  if n.kind notin nkLambdaKinds and symBinding(n[pragmasPos]) == spGenSym:
    let ident = getIdentNode(c, n[namePos])
    if not isTemplParam(c, ident):
      var s = newGenSym(k, ident, c)
      s.ast = n
      addPrelimDecl(c.c, s)
      styleCheckDef(c.c.config, n.info, s)
      onDef(n.info, s)
      n[namePos] = newSymNode(s, n[namePos].info)
    else:
      n[namePos] = ident
  else:
    n[namePos] = semRoutineInTemplName(c, n[namePos])
  # open scope for parameters
  openScope(c)
  for i in patternPos..paramsPos-1:
    n[i] = semTemplBody(c, n[i])

  if k == skTemplate: inc(c.inTemplateHeader)
  n[paramsPos] = semTemplBody(c, n[paramsPos])
  if k == skTemplate: dec(c.inTemplateHeader)

  for i in paramsPos+1..miscPos:
    n[i] = semTemplBody(c, n[i])
  # open scope for locals
  inc c.scopeN
  openScope(c)
  n[bodyPos] = semTemplBody(c, n[bodyPos])
  # close scope for locals
  closeScope(c)
  dec c.scopeN
  # close scope for parameters
  closeScope(c)

proc semTemplSomeDecl(c: var TemplCtx, n: PNode, symKind: TSymKind; start = 0) =
  for i in start..<n.len:
    var a = n[i]
    case a.kind:
    of nkCommentStmt: continue
    of nkIdentDefs, nkVarTuple, nkConstDef:
      checkMinSonsLen(a, 3, c.c.config)
      when defined(nimsuggest):
        inc c.c.inTypeContext
      a[^2] = semTemplBody(c, a[^2])
      when defined(nimsuggest):
        dec c.c.inTypeContext
      a[^1] = semTemplBody(c, a[^1])
      for j in 0..<a.len-2:
        addLocalDecl(c, a[j], symKind)
    else:
      illFormedAst(a, c.c.config)


proc semPattern(c: PContext, n: PNode; s: PSym): PNode

proc semTemplBodySons(c: var TemplCtx, n: PNode): PNode =
  result = n
  for i in 0..<n.len:
    result[i] = semTemplBody(c, n[i])

proc semTemplBody(c: var TemplCtx, n: PNode): PNode =
  result = n
  semIdeForTemplateOrGenericCheck(c.c.config, n, c.cursorInBody)
  case n.kind
  of nkIdent:
    if n.ident.id in c.toInject: return n
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil:
      if s.owner == c.owner and s.kind == skParam and sfTemplateParam in s.flags:
        incl(s.flags, sfUsed)
        result = newSymNode(s, n.info)
        onUse(n.info, s)
      elif contains(c.toBind, s.id):
        result = symChoice(c.c, n, s, scClosed, c.noGenSym > 0)
      elif contains(c.toMixin, s.name.id):
        result = symChoice(c.c, n, s, scForceOpen, c.noGenSym > 0)
      elif s.owner == c.owner and sfGenSym in s.flags and c.noGenSym == 0:
        # template tmp[T](x: var seq[T]) =
        # var yz: T
        incl(s.flags, sfUsed)
        result = newSymNode(s, n.info)
        onUse(n.info, s)
      else:
        result = semTemplSymbol(c.c, n, s, c.noGenSym > 0)
  of nkBind:
    result = semTemplBody(c, n[0])
  of nkBindStmt:
    result = semBindStmt(c.c, n, c.toBind)
  of nkMixinStmt:
    if c.scopeN > 0: result = semTemplBodySons(c, n)
    else: result = semMixinStmt(c.c, n, c.toMixin)
  of nkEmpty, nkSym..nkNilLit, nkComesFrom:
    discard
  of nkIfStmt:
    for i in 0..<n.len:
      var it = n[i]
      if it.len == 2:
        openScope(c)
        it[0] = semTemplBody(c, it[0])
        it[1] = semTemplBody(c, it[1])
        closeScope(c)
      else:
        n[i] = semTemplBodyScope(c, it)
  of nkWhileStmt:
    openScope(c)
    for i in 0..<n.len:
      n[i] = semTemplBody(c, n[i])
    closeScope(c)
  of nkCaseStmt:
    openScope(c)
    n[0] = semTemplBody(c, n[0])
    for i in 1..<n.len:
      var a = n[i]
      checkMinSonsLen(a, 1, c.c.config)
      for j in 0..<a.len-1:
        a[j] = semTemplBody(c, a[j])
      a[^1] = semTemplBodyScope(c, a[^1])
    closeScope(c)
  of nkForStmt, nkParForStmt:
    openScope(c)
    n[^2] = semTemplBody(c, n[^2])
    for i in 0..<n.len - 2:
      if n[i].kind == nkVarTuple:
        for j in 0..<n[i].len-1:
          addLocalDecl(c, n[i][j], skForVar)
      else:
        addLocalDecl(c, n[i], skForVar)
    openScope(c)
    n[^1] = semTemplBody(c, n[^1])
    closeScope(c)
    closeScope(c)
  of nkBlockStmt, nkBlockExpr, nkBlockType:
    checkSonsLen(n, 2, c.c.config)
    openScope(c)
    if n[0].kind != nkEmpty:
      addLocalDecl(c, n[0], skLabel)
      when false:
        # labels are always 'gensym'ed:
        let s = newGenSym(skLabel, n[0], c)
        addPrelimDecl(c.c, s)
        styleCheckDef(c.c.config, s)
        onDef(n[0].info, s)
        n[0] = newSymNode(s, n[0].info)
    n[1] = semTemplBody(c, n[1])
    closeScope(c)
  of nkTryStmt, nkHiddenTryStmt:
    checkMinSonsLen(n, 2, c.c.config)
    n[0] = semTemplBodyScope(c, n[0])
    for i in 1..<n.len:
      var a = n[i]
      checkMinSonsLen(a, 1, c.c.config)
      openScope(c)
      for j in 0..<a.len-1:
        if a[j].isInfixAs():
          addLocalDecl(c, a[j][2], skLet)
          a[j][1] = semTemplBody(c, a[j][1])
        else:
          a[j] = semTemplBody(c, a[j])
      a[^1] = semTemplBodyScope(c, a[^1])
      closeScope(c)
  of nkVarSection: semTemplSomeDecl(c, n, skVar)
  of nkLetSection: semTemplSomeDecl(c, n, skLet)
  of nkFormalParams:
    checkMinSonsLen(n, 1, c.c.config)
    semTemplSomeDecl(c, n, skParam, 1)
    n[0] = semTemplBody(c, n[0])
  of nkConstSection: semTemplSomeDecl(c, n, skConst)
  of nkTypeSection:
    for i in 0..<n.len:
      var a = n[i]
      if a.kind == nkCommentStmt: continue
      if (a.kind != nkTypeDef): illFormedAst(a, c.c.config)
      checkSonsLen(a, 3, c.c.config)
      addLocalDecl(c, a[0], skType)
    for i in 0..<n.len:
      var a = n[i]
      if a.kind == nkCommentStmt: continue
      if (a.kind != nkTypeDef): illFormedAst(a, c.c.config)
      checkSonsLen(a, 3, c.c.config)
      if a[1].kind != nkEmpty:
        openScope(c)
        a[1] = semTemplBody(c, a[1])
        a[2] = semTemplBody(c, a[2])
        closeScope(c)
      else:
        a[2] = semTemplBody(c, a[2])
  of nkProcDef, nkLambdaKinds:
    result = semRoutineInTemplBody(c, n, skProc)
  of nkFuncDef:
    result = semRoutineInTemplBody(c, n, skFunc)
  of nkMethodDef:
    result = semRoutineInTemplBody(c, n, skMethod)
  of nkIteratorDef:
    result = semRoutineInTemplBody(c, n, skIterator)
  of nkTemplateDef:
    result = semRoutineInTemplBody(c, n, skTemplate)
  of nkMacroDef:
    result = semRoutineInTemplBody(c, n, skMacro)
  of nkConverterDef:
    result = semRoutineInTemplBody(c, n, skConverter)
  of nkPragmaExpr:
    result[0] = semTemplBody(c, n[0])
  of nkPostfix:
    result[1] = semTemplBody(c, n[1])
  of nkPragma:
    for x in n:
      if x.kind == nkExprColonExpr:
        x[1] = semTemplBody(c, x[1])
  of nkBracketExpr:
    result = newNodeI(nkCall, n.info)
    result.add newIdentNode(getIdent(c.c.cache, "[]"), n.info)
    for i in 0..<n.len: result.add(n[i])
    result = semTemplBodySons(c, result)
  of nkCurlyExpr:
    result = newNodeI(nkCall, n.info)
    result.add newIdentNode(getIdent(c.c.cache, "{}"), n.info)
    for i in 0..<n.len: result.add(n[i])
    result = semTemplBodySons(c, result)
  of nkAsgn, nkFastAsgn:
    checkSonsLen(n, 2, c.c.config)
    let a = n[0]
    let b = n[1]

    let k = a.kind
    case k
    of nkBracketExpr:
      result = newNodeI(nkCall, n.info)
      result.add newIdentNode(getIdent(c.c.cache, "[]="), n.info)
      for i in 0..<a.len: result.add(a[i])
      result.add(b)
      let a0 = semTemplBody(c, a[0])
      result = semTemplBodySons(c, result)
    of nkCurlyExpr:
      result = newNodeI(nkCall, n.info)
      result.add newIdentNode(getIdent(c.c.cache, "{}="), n.info)
      for i in 0..<a.len: result.add(a[i])
      result.add(b)
      result = semTemplBodySons(c, result)
    else:
      result = semTemplBodySons(c, n)
  of nkCallKinds-{nkPostfix}:
    # do not transform runnableExamples (bug #9143)
    if not isRunnableExamples(n[0]):
      result = semTemplBodySons(c, n)
  of nkDotExpr, nkAccQuoted:
    # dotExpr is ambiguous: note that we explicitly allow 'x.TemplateParam',
    # so we use the generic code for nkDotExpr too
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil:
      # do not symchoice a quoted template parameter (bug #2390):
      if s.owner == c.owner and s.kind == skParam and
          n.kind == nkAccQuoted and n.len == 1:
        incl(s.flags, sfUsed)
        onUse(n.info, s)
        return newSymNode(s, n.info)
      elif contains(c.toBind, s.id):
        return symChoice(c.c, n, s, scClosed, c.noGenSym > 0)
      elif contains(c.toMixin, s.name.id):
        return symChoice(c.c, n, s, scForceOpen, c.noGenSym > 0)
      else:
        return symChoice(c.c, n, s, scOpen, c.noGenSym > 0)
    if n.kind == nkDotExpr:
      result = n
      result[0] = semTemplBody(c, n[0])
      inc c.noGenSym
      result[1] = semTemplBody(c, n[1])
      dec c.noGenSym
    else:
      result = semTemplBodySons(c, n)
  of nkExprColonExpr, nkExprEqExpr:
    if n.len == 2:
      inc c.noGenSym
      result[0] = semTemplBody(c, n[0])
      dec c.noGenSym
      result[1] = semTemplBody(c, n[1])
    else:
      result = semTemplBodySons(c, n)
  of nkTableConstr:
    # also transform the keys (bug #12595)
    for i in 0..<n.len:
      result[i] = semTemplBodySons(c, n[i])
  else:
    result = semTemplBodySons(c, n)

proc semTemplBodyDirty(c: var TemplCtx, n: PNode): PNode =
  result = n
  semIdeForTemplateOrGenericCheck(c.c.config, n, c.cursorInBody)
  case n.kind
  of nkIdent:
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil:
      if s.owner == c.owner and s.kind == skParam:
        result = newSymNode(s, n.info)
      elif contains(c.toBind, s.id):
        result = symChoice(c.c, n, s, scClosed)
  of nkBind:
    result = semTemplBodyDirty(c, n[0])
  of nkBindStmt:
    result = semBindStmt(c.c, n, c.toBind)
  of nkEmpty, nkSym..nkNilLit, nkComesFrom:
    discard
  else:
    # dotExpr is ambiguous: note that we explicitly allow 'x.TemplateParam',
    # so we use the generic code for nkDotExpr too
    if n.kind == nkDotExpr or n.kind == nkAccQuoted:
      let s = qualifiedLookUp(c.c, n, {})
      if s != nil and contains(c.toBind, s.id):
        return symChoice(c.c, n, s, scClosed)
    result = n
    for i in 0..<n.len:
      result[i] = semTemplBodyDirty(c, n[i])

# in semstmts.nim:
proc semProcAnnotation(c: PContext, prc: PNode; validPragmas: TSpecialWords): PNode

proc semTemplateDef(c: PContext, n: PNode): PNode =
  result = semProcAnnotation(c, n, templatePragmas)
  if result != nil: return result
  result = n
  var s: PSym
  if isTopLevel(c):
    s = semIdentVis(c, skTemplate, n[namePos], {sfExported})
    incl(s.flags, sfGlobal)
  else:
    s = semIdentVis(c, skTemplate, n[namePos], {})
  assert s.kind == skTemplate

  if s.owner != nil:
    const names = ["!=", ">=", ">", "incl", "excl", "in", "notin", "isnot"]
    if sfSystemModule in s.owner.flags and s.name.s in names or
       s.owner.name.s == "vm" and s.name.s == "stackTrace":
      incl(s.flags, sfCallsite)

  styleCheckDef(c.config, s)
  onDef(n[namePos].info, s)
  # check parameter list:
  #s.scope = c.currentScope
  pushOwner(c, s)
  openScope(c)
  n[namePos] = newSymNode(s)
  pragmaCallable(c, s, n, templatePragmas)
  implicitPragmas(c, s, n.info, templatePragmas)

  setGenericParamsMisc(c, n)
  # process parameters:
  var allUntyped = true
  if n[paramsPos].kind != nkEmpty:
    semParamList(c, n[paramsPos], n[genericParamsPos], s)
    # a template's parameters are not gensym'ed even if that was originally the
    # case as we determine whether it's a template parameter in the template
    # body by the absence of the sfGenSym flag:
    for i in 1..<s.typ.n.len:
      let param = s.typ.n[i].sym
      param.flags.incl sfTemplateParam
      param.flags.excl sfGenSym
      if param.typ.kind != tyUntyped: allUntyped = false
  else:
    s.typ = newTypeS(tyProc, c)
    # XXX why do we need tyTyped as a return type again?
    s.typ.n = newNodeI(nkFormalParams, n.info)
    rawAddSon(s.typ, newTypeS(tyTyped, c))
    s.typ.n.add newNodeIT(nkType, n.info, s.typ[0])
  if n[genericParamsPos].safeLen == 0:
    # restore original generic type params as no explicit or implicit were found
    n[genericParamsPos] = n[miscPos][1]
    n[miscPos] = c.graph.emptyNode
  if allUntyped: incl(s.flags, sfAllUntyped)

  if n[patternPos].kind != nkEmpty:
    n[patternPos] = semPattern(c, n[patternPos], s)

  var ctx: TemplCtx
  ctx.toBind = initIntSet()
  ctx.toMixin = initIntSet()
  ctx.toInject = initIntSet()
  ctx.c = c
  ctx.owner = s
  if sfDirty in s.flags:
    n[bodyPos] = semTemplBodyDirty(ctx, n[bodyPos])
  else:
    n[bodyPos] = semTemplBody(ctx, n[bodyPos])
  # only parameters are resolved, no type checking is performed
  semIdeForTemplateOrGeneric(c, n[bodyPos], ctx.cursorInBody)
  closeScope(c)
  popOwner(c)

  # set the symbol AST after pragmas, at least. This stops pragma that have
  # been pushed (implicit) to be explicitly added to the template definition
  # and misapplied to the body. see #18113
  s.ast = n

  if sfCustomPragma in s.flags:
    if n[bodyPos].kind != nkEmpty:
      localError(c.config, n[bodyPos].info, errImplOfXNotAllowed % s.name.s)
  elif n[bodyPos].kind == nkEmpty:
    localError(c.config, n.info, "implementation of '$1' expected" % s.name.s)
  var (proto, comesFromShadowscope) = searchForProc(c, c.currentScope, s)
  if proto == nil:
    addInterfaceOverloadableSymAt(c, c.currentScope, s)
  elif not comesFromShadowscope:
    symTabReplace(c.currentScope.symbols, proto, s)
  if n[patternPos].kind != nkEmpty:
    c.patterns.add(s)

proc semPatternBody(c: var TemplCtx, n: PNode): PNode =
  template templToExpand(s: untyped): untyped =
    s.kind == skTemplate and (s.typ.len == 1 or sfAllUntyped in s.flags)

  proc newParam(c: var TemplCtx, n: PNode, s: PSym): PNode =
    # the param added in the current scope is actually wrong here for
    # macros because they have a shadowed param of type 'PNimNode' (see
    # semtypes.addParamOrResult). Within the pattern we have to ensure
    # to use the param with the proper type though:
    incl(s.flags, sfUsed)
    onUse(n.info, s)
    let x = c.owner.typ.n[s.position+1].sym
    assert x.name == s.name
    result = newSymNode(x, n.info)

  proc handleSym(c: var TemplCtx, n: PNode, s: PSym): PNode =
    result = n
    if s != nil:
      if s.owner == c.owner and s.kind == skParam:
        result = newParam(c, n, s)
      elif contains(c.toBind, s.id):
        result = symChoice(c.c, n, s, scClosed)
      elif templToExpand(s):
        result = semPatternBody(c, semTemplateExpr(c.c, n, s, {efNoSemCheck}))
      else:
        discard
        # we keep the ident unbound for matching instantiated symbols and
        # more flexibility

  proc expectParam(c: var TemplCtx, n: PNode): PNode =
    let s = qualifiedLookUp(c.c, n, {})
    if s != nil and s.owner == c.owner and s.kind == skParam:
      result = newParam(c, n, s)
    else:
      localError(c.c.config, n.info, "invalid expression")
      result = n

  result = n
  case n.kind
  of nkIdent:
    let s = qualifiedLookUp(c.c, n, {})
    result = handleSym(c, n, s)
  of nkBindStmt:
    result = semBindStmt(c.c, n, c.toBind)
  of nkEmpty, nkSym..nkNilLit: discard
  of nkCurlyExpr:
    # we support '(pattern){x}' to bind a subpattern to a parameter 'x';
    # '(pattern){|x}' does the same but the matches will be gathered in 'x'
    if n.len != 2:
      localError(c.c.config, n.info, "invalid expression")
    elif n[1].kind == nkIdent:
      n[0] = semPatternBody(c, n[0])
      n[1] = expectParam(c, n[1])
    elif n[1].kind == nkPrefix and n[1][0].kind == nkIdent:
      let opr = n[1][0]
      if opr.ident.s == "|":
        n[0] = semPatternBody(c, n[0])
        n[1][1] = expectParam(c, n[1][1])
      else:
        localError(c.c.config, n.info, "invalid expression")
    else:
      localError(c.c.config, n.info, "invalid expression")
  of nkStmtList, nkStmtListExpr:
    if stupidStmtListExpr(n):
      result = semPatternBody(c, n.lastSon)
    else:
      for i in 0..<n.len:
        result[i] = semPatternBody(c, n[i])
  of nkCallKinds:
    let s = qualifiedLookUp(c.c, n[0], {})
    if s != nil:
      if s.owner == c.owner and s.kind == skParam: discard
      elif contains(c.toBind, s.id): discard
      elif templToExpand(s):
        return semPatternBody(c, semTemplateExpr(c.c, n, s, {efNoSemCheck}))

    if n.kind == nkInfix and (let id = considerQuotedIdent(c.c, n[0]); id != nil):
      # we interpret `*` and `|` only as pattern operators if they occur in
      # infix notation, so that '`*`(a, b)' can be used for verbatim matching:
      if id.s == "*" or id.s == "**":
        result = newNodeI(nkPattern, n.info, n.len)
        result[0] = newIdentNode(id, n.info)
        result[1] = semPatternBody(c, n[1])
        result[2] = expectParam(c, n[2])
        return
      elif id.s == "|":
        result = newNodeI(nkPattern, n.info, n.len)
        result[0] = newIdentNode(id, n.info)
        result[1] = semPatternBody(c, n[1])
        result[2] = semPatternBody(c, n[2])
        return

    if n.kind == nkPrefix and (let id = considerQuotedIdent(c.c, n[0]); id != nil):
      if id.s == "~":
        result = newNodeI(nkPattern, n.info, n.len)
        result[0] = newIdentNode(id, n.info)
        result[1] = semPatternBody(c, n[1])
        return

    for i in 0..<n.len:
      result[i] = semPatternBody(c, n[i])
  else:
    # dotExpr is ambiguous: note that we explicitly allow 'x.TemplateParam',
    # so we use the generic code for nkDotExpr too
    case n.kind
    of nkDotExpr, nkAccQuoted:
      let s = qualifiedLookUp(c.c, n, {})
      if s != nil:
        if contains(c.toBind, s.id):
          return symChoice(c.c, n, s, scClosed)
        else:
          return newIdentNode(s.name, n.info)
    of nkPar:
      if n.len == 1: return semPatternBody(c, n[0])
    else: discard
    for i in 0..<n.len:
      result[i] = semPatternBody(c, n[i])

proc semPattern(c: PContext, n: PNode; s: PSym): PNode =
  openScope(c)
  var ctx: TemplCtx
  ctx.toBind = initIntSet()
  ctx.toMixin = initIntSet()
  ctx.toInject = initIntSet()
  ctx.c = c
  ctx.owner = getCurrOwner(c)
  result = flattenStmts(semPatternBody(ctx, n))
  if result.kind in {nkStmtList, nkStmtListExpr}:
    if result.len == 1:
      result = result[0]
    elif result.len == 0:
      localError(c.config, n.info, "a pattern cannot be empty")
  closeScope(c)
  addPattern(c, LazySym(sym: s))