Make interval a CLI argument.
[cellular-automata.git] / polymorphism / 001 / src / polymorphism.ml
CommitLineData
8c93b722
SK
1open Core.Std
2
3
a0d860e4
SK
4let (|-) g f x = f (g x)
5
6
ce139f1f
SK
7module Terminal : sig
8 type color = [ `green
9 | `red
39971ff4 10 | `white
ce139f1f
SK
11 ]
12
13 val string_with_color : string -> color -> string
14
15 val clear : unit -> unit
16
17 val reset : unit -> unit
18end = struct
19 type color = [ `green
20 | `red
39971ff4 21 | `white
ce139f1f
SK
22 ]
23
24 let ansi_code_clear = "\027[2J" (* Clear screen *)
25 let ansi_code_reset = "\027[1;1H" (* Reset cursor position *)
26
27 let string_of_color = function
28 | `green -> "\027[0;32m"
29 | `red -> "\027[1;31m"
39971ff4 30 | `white -> "\027[1;37m"
ce139f1f
SK
31
32 let string_with_color s c =
33 sprintf "%s%s\027[0m" (string_of_color c) s
34
35 let clear () =
36 print_string ansi_code_clear
37
38 let reset () =
39 print_string ansi_code_reset
40end
41
42
4d49c95e 43module type MATRIX = sig
7c363dd8
SK
44 module Point : sig
45 type t = {r : int; k : int}
46 end
47
4d49c95e
SK
48 type 'a t
49
a1665c92 50 val create : rs:int -> ks:int -> 'a -> 'a t
4d49c95e 51
7c363dd8 52 val get_neighbors : 'a t -> Point.t -> 'a list
4d49c95e 53
65dbef41
SK
54 val map : 'a t -> f:('a -> 'b) -> 'b t
55
a1665c92 56 val mapi : 'a t -> f:(Point.t -> 'a -> 'b) -> 'b t
4d49c95e 57
a1665c92 58 val iter : 'a t -> f:(Point.t -> 'a -> unit) -> unit
0ce0e798
SK
59
60 val print : 'a t -> to_string:('a -> string) -> unit
4d49c95e
SK
61end
62
63module Matrix : MATRIX = struct
7c363dd8
SK
64 module Point = struct
65 type t = {r : int; k : int}
66
67 let (+) p p' =
68 { r = p.r + p'.r
69 ; k = p.k + p'.k
70 }
71 end
72
394125ca
SK
73 module Direction = struct
74 type t = NW | N | NE
75 | W | E
76 | SW | S | SE
77
78 let all = [ NW ; N ; NE
79 ; W ; E
80 ; SW ; S ; SE
81 ]
82
7c363dd8
SK
83 let to_offset =
84 let open Point in
85 function
86 | NW -> {r = -1; k = -1}
87 | N -> {r = -1; k = 0}
88 | NE -> {r = -1; k = 1}
89 | W -> {r = 0; k = -1}
90 | E -> {r = 0; k = 1}
91 | SW -> {r = 1; k = -1}
92 | S -> {r = 1; k = 0}
93 | SE -> {r = 1; k = 1}
394125ca
SK
94 end
95
4d49c95e
SK
96 type 'a t = 'a array array
97
a1665c92
SK
98 let create ~rs ~ks x =
99 Array.make_matrix ~dimx:rs ~dimy:ks x
4d49c95e
SK
100
101 let iter t ~f =
102 Array.iteri t ~f:(
63fe855d
SK
103 fun r ks ->
104 Array.iteri ks ~f:(
a1665c92
SK
105 fun k x ->
106 f {Point.r; Point.k} x
4d49c95e
SK
107 )
108 )
109
0ce0e798
SK
110 let print t ~to_string =
111 Array.iter t ~f:(
63fe855d
SK
112 fun r ->
113 Array.iter r ~f:(fun x -> printf "%s" (to_string x));
0ce0e798
SK
114 print_newline ()
115 )
116
4d49c95e 117 let map t ~f =
65dbef41
SK
118 Array.map t ~f:(Array.map ~f:(fun x -> f x))
119
120 let mapi t ~f =
4d49c95e 121 Array.mapi t ~f:(
63fe855d
SK
122 fun r ks ->
123 Array.mapi ks ~f:(
a1665c92
SK
124 fun k x ->
125 f {Point.r; Point.k} x
4d49c95e
SK
126 )
127 )
128
7c363dd8 129 let get t {Point.r; Point.k} =
63fe855d 130 t.(r).(k)
394125ca 131
7c363dd8 132 let is_within_bounds t {Point.r; Point.k} =
394125ca
SK
133 match t with
134 | [||] -> assert false
135 | t ->
136 r >= 0 && r < Array.length t &&
137 k >= 0 && k < Array.length t.(0)
138
7c363dd8 139 let neighborhood t point =
394125ca 140 List.map Direction.all ~f:Direction.to_offset
7c363dd8
SK
141 |> List.map ~f:(fun offset_point -> Point.(point + offset_point))
142 |> List.filter ~f:(is_within_bounds t)
394125ca 143
7c363dd8
SK
144 let get_neighbors t point =
145 List.map (neighborhood t point) ~f:(get t)
4d49c95e
SK
146end
147
148
4b18b7df
SK
149module PhenoType : sig
150 type t
151
152 val create : char -> Terminal.color option -> t
153
154 val to_string : t -> string
155end = struct
156 type t = { color : Terminal.color option
157 ; character : char
158 }
159
160 let create character color =
161 {color; character}
162
163 let to_string = function
164 | {color=None; character} ->
165 String.of_char character
166 | {color=Some c; character} ->
167 Terminal.string_with_color (String.of_char character) c
a96702d3
SK
168end
169
da8f1674 170
a96702d3 171module Cell = struct
a0d860e4
SK
172 module State = struct
173 type t = Alive of char
174 | Dead
175 end
176
177 type t = { state : State.t
a96702d3 178 ; pheno : PhenoType.t
a96702d3
SK
179 }
180end
0ce0e798 181
0ce0e798 182
a96702d3
SK
183module type RULE = sig
184 val create : unit -> Cell.t
da8f1674 185
a0d860e4
SK
186 val transition : self:Cell.State.t
187 -> neighbors:Cell.State.t list
188 -> Cell.t
da8f1674
SK
189end
190
191
029c4a1f 192module Life : RULE = struct
a0d860e4
SK
193 module State : sig
194 type t = D | A
195
196 val of_int : int -> t
0d6f7833 197
a0d860e4 198 val to_int : t -> int
a96702d3 199
a0d860e4 200 val to_cell : t -> Cell.t
0ce0e798 201
a0d860e4
SK
202 val of_cell_state : Cell.State.t -> t
203 end = struct
204 type t = D | A
0d6f7833 205
a0d860e4
SK
206 let of_int = function
207 | 0 -> D
208 | 1 -> A
209 | _ -> assert false
a96702d3 210
a0d860e4
SK
211 let to_int = function
212 | D -> 0
213 | A -> 1
a96702d3 214
a0d860e4
SK
215 let to_pheno = function
216 | D -> PhenoType.create ' ' None
217 | A -> PhenoType.create 'o' (Some `white)
0ce0e798 218
a0d860e4
SK
219 let of_cell_state = function
220 | Cell.State.Dead -> D
221 | Cell.State.Alive 'A' -> A
222 | Cell.State.Alive _ -> D (* Foreign cell *)
223
224 let to_cell_state = function
225 | D -> Cell.State.Dead
226 | A -> Cell.State.Alive 'A'
227
228 let to_cell t =
229 { Cell.state = t |> to_cell_state
230 ; Cell.pheno = t |> to_pheno
231 }
232 end
0ce0e798 233
a96702d3
SK
234 let next state ~live_neighbors =
235 match state with
a0d860e4
SK
236 | State.A when live_neighbors < 2 -> State.D
237 | State.A when live_neighbors < 4 -> State.A
238 | State.A when live_neighbors > 3 -> State.D
239 | State.D when live_neighbors = 3 -> State.A
240 | State.A -> State.A
241 | State.D -> State.D
a96702d3
SK
242
243 let create () =
a0d860e4
SK
244 Random.int 2 |> State.of_int |> State.to_cell
245
246 let live_neighbors neighbors =
247 neighbors |> List.map ~f:(State.of_cell_state |- State.to_int)
248 |> List.fold_left ~init:0 ~f:(+)
249
250 let transition ~self ~neighbors =
251 self |> State.of_cell_state
252 |> next ~live_neighbors:(live_neighbors neighbors)
253 |> State.to_cell
0d6f7833
SK
254end
255
256
fd51b8fa 257module ForestFire : RULE = struct
a0d860e4
SK
258 module State : sig
259 type t = E | T | B
fd51b8fa 260
a0d860e4 261 val is_burning : t -> bool
fd51b8fa 262
a0d860e4 263 val of_int : int -> t
fd51b8fa 264
a0d860e4 265 val to_int : t -> int
fd51b8fa 266
a0d860e4
SK
267 val to_cell : t -> Cell.t
268
269 val of_cell_state : Cell.State.t -> t
270 end = struct
271 type t = E | T | B
272
273 let is_burning = function
274 | E -> false
275 | T -> false
276 | B -> true
fd51b8fa 277
a0d860e4
SK
278 let of_int = function
279 | 0 -> E
280 | 1 -> T
281 | 2 -> B
282 | _ -> assert false
fd51b8fa 283
a0d860e4
SK
284 let to_int = function
285 | E -> 0
286 | T -> 1
287 | B -> 2
288
289 let to_pheno = function
290 | E -> PhenoType.create ' ' None
291 | T -> PhenoType.create 'T' (Some `green)
292 | B -> PhenoType.create '#' (Some `red)
293
294 let of_cell_state = function
295 | Cell.State.Dead -> E
296 | Cell.State.Alive 'T' -> T
297 | Cell.State.Alive 'B' -> B
298 | Cell.State.Alive _ -> E (* Foreign cell *)
299
300 let to_cell_state = function
301 | E -> Cell.State.Dead
302 | T -> Cell.State.Alive 'T'
303 | B -> Cell.State.Alive 'B'
304
305 let to_cell t =
306 { Cell.state = t |> to_cell_state
307 ; Cell.pheno = t |> to_pheno
308 }
309 end
fd51b8fa
SK
310
311 let create () =
a0d860e4 312 Random.int 3 |> State.of_int |> State.to_cell
fd51b8fa
SK
313
314 let f = 0.000001 (* Probability of spontaneous ignition *)
3ac904c0 315 let p = 0.1 (* Probability of spontaneous growth *)
fd51b8fa 316
c30cad07
SK
317 let is_probable p =
318 (Random.float 1.0) <= p
fd51b8fa
SK
319
320 let next state ~burning_neighbors =
321 match state, burning_neighbors with
a0d860e4
SK
322 | State.E, _ when is_probable p -> State.T
323 | State.E, _ -> State.E
324 | State.T, 0 when is_probable f -> State.B
325 | State.T, _ when burning_neighbors > 0 -> State.B
326 | State.T, _ -> State.T
327 | State.B, _ -> State.E
328
329 let burning_neighbors neighbors =
330 neighbors |> List.map ~f:State.of_cell_state
331 |> List.filter ~f:State.is_burning
332 |> List.map ~f:State.to_int
333 |> List.fold_left ~init:0 ~f:(+)
334
335 let transition ~self ~neighbors =
336 self |> State.of_cell_state
337 |> next ~burning_neighbors:(burning_neighbors neighbors)
338 |> State.to_cell
fd51b8fa
SK
339end
340
341
d9fa5d46
SK
342module Automaton : sig
343 type t
aed335e3 344
a96702d3
SK
345 val create : rows:int
346 -> columns:int
347 -> interval:float
348 -> rules: (module RULE) list
349 -> t
aed335e3 350
d9fa5d46
SK
351 val loop : t -> unit
352end = struct
a96702d3
SK
353 type cell = { data : Cell.t
354 ; rule : (module RULE)
355 }
356
357 type t = { grid : cell Matrix.t
d9fa5d46
SK
358 ; interval : Time.Span.t
359 ; bar : string
360 }
aed335e3 361
a96702d3
SK
362 let create ~rows:rs ~columns:ks ~interval ~rules =
363 let n = List.length rules in
a96702d3 364 let init () =
fd51b8fa 365 let rule = List.nth_exn rules (Random.int n) in
a96702d3
SK
366 let module Rule = (val rule : RULE) in
367 { rule
368 ; data = Rule.create ()
369 }
370 in
21c4909c 371 Terminal.clear ();
a96702d3 372 { grid = Matrix.map ~f:init (Matrix.create ~rs ~ks ())
d9fa5d46
SK
373 ; interval = Time.Span.of_float interval
374 ; bar = String.make ks '-'
375 }
376
a96702d3 377 let cell_to_string cell =
4b18b7df 378 PhenoType.to_string cell.data.Cell.pheno
a96702d3 379
d9fa5d46 380 let print t =
21c4909c 381 Terminal.reset ();
d9fa5d46 382 print_endline t.bar;
a96702d3 383 Matrix.print t.grid ~to_string:cell_to_string;
d9fa5d46
SK
384 print_endline t.bar
385
386 let next t =
387 let grid =
388 Matrix.mapi t.grid ~f:(
a96702d3
SK
389 fun point {rule; data} ->
390 let module Rule = (val rule : RULE) in
d9fa5d46 391 let neighbors = Matrix.get_neighbors t.grid point in
a96702d3
SK
392 let data =
393 Rule.transition
a0d860e4
SK
394 ~self:data.Cell.state
395 ~neighbors:(List.map neighbors ~f:(fun c -> c.data.Cell.state))
a96702d3
SK
396 in
397 {rule; data}
d9fa5d46
SK
398 )
399 in
400 {t with grid}
401
402 let rec loop t =
403 print t;
404 Time.pause t.interval;
405 loop (next t)
406end
7707ff62
SK
407
408
5b98f452 409let main interval () =
7707ff62 410 Random.self_init ();
d9fa5d46 411 let rows, columns = Or_error.ok_exn Linux_ext.get_terminal_size () in
a96702d3 412 let rules =
029c4a1f 413 [ (module Life : RULE)
fd51b8fa 414 ; (module ForestFire : RULE)
a96702d3
SK
415 ]
416 in
8526e3e1 417 Automaton.loop (Automaton.create ~rows:(rows - 3) ~columns ~interval ~rules)
8c93b722
SK
418
419
7d89c037
SK
420let spec =
421 let summary = "Polymorphic Cellular Automata" in
5b98f452
SK
422 let spec = Command.Spec.(empty
423 +> flag "-i" (optional_with_default 0.1 float)
424 ~doc:" Induced interval between generations."
425 )
426 in
7d89c037
SK
427 Command.basic ~summary spec main
428
429
430let () = Command.run spec
This page took 0.076362 seconds and 4 git commands to generate.