about summary refs log tree commit diff stats
path: root/ocaml/matt
diff options
context:
space:
mode:
authorelioat <elioat@tilde.institute>2025-05-24 13:37:30 -0400
committerelioat <elioat@tilde.institute>2025-05-24 13:37:30 -0400
commit2f06e04ca52254518e081be5ca217c1b2fe523cb (patch)
treee21281c932e6a8d5596db64db036e37a7872c2f8 /ocaml/matt
parentc7e7eed11e48a4eb665a9ca0b4371794aa57c55e (diff)
downloadtour-2f06e04ca52254518e081be5ca217c1b2fe523cb.tar.gz
*
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.ml411
4 files changed, 411 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..2ed07f3
--- /dev/null
+++ b/ocaml/matt/tour.ml
@@ -0,0 +1,411 @@
+(* OCaml Overview and Unique Features
+
+   This file provides a high-level overview of the OCaml programming language,
+   highlighting its key characteristics and unique features.
+
+   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.
+*)
+let () = print_endline "-- 1. Strong Static Typing & Type Inference --"
+
+let an_integer = 42 (* Inferred as type `int` *)
+let a_float = 3.14 (* 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.
+*)
+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.
+*)
+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.
+*)
+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 y =
+  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.
+*)
+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