Moved Terminal module to the top.
[cellular-automata.git] / polymorphism / 001 / src / polymorphism.ml
CommitLineData
8c93b722
SK
1open Core.Std
2
3
ce139f1f
SK
4module Terminal : sig
5 type color = [ `green
6 | `red
7 ]
8
9 val string_with_color : string -> color -> string
10
11 val clear : unit -> unit
12
13 val reset : unit -> unit
14end = struct
15 type color = [ `green
16 | `red
17 ]
18
19 let ansi_code_clear = "\027[2J" (* Clear screen *)
20 let ansi_code_reset = "\027[1;1H" (* Reset cursor position *)
21
22 let string_of_color = function
23 | `green -> "\027[0;32m"
24 | `red -> "\027[1;31m"
25
26 let string_with_color s c =
27 sprintf "%s%s\027[0m" (string_of_color c) s
28
29 let clear () =
30 print_string ansi_code_clear
31
32 let reset () =
33 print_string ansi_code_reset
34end
35
36
4d49c95e 37module type MATRIX = sig
7c363dd8
SK
38 module Point : sig
39 type t = {r : int; k : int}
40 end
41
4d49c95e
SK
42 type 'a t
43
a1665c92 44 val create : rs:int -> ks:int -> 'a -> 'a t
4d49c95e 45
7c363dd8 46 val get_neighbors : 'a t -> Point.t -> 'a list
4d49c95e 47
65dbef41
SK
48 val map : 'a t -> f:('a -> 'b) -> 'b t
49
a1665c92 50 val mapi : 'a t -> f:(Point.t -> 'a -> 'b) -> 'b t
4d49c95e 51
a1665c92 52 val iter : 'a t -> f:(Point.t -> 'a -> unit) -> unit
0ce0e798
SK
53
54 val print : 'a t -> to_string:('a -> string) -> unit
4d49c95e
SK
55end
56
57module Matrix : MATRIX = struct
7c363dd8
SK
58 module Point = struct
59 type t = {r : int; k : int}
60
61 let (+) p p' =
62 { r = p.r + p'.r
63 ; k = p.k + p'.k
64 }
65 end
66
394125ca
SK
67 module Direction = struct
68 type t = NW | N | NE
69 | W | E
70 | SW | S | SE
71
72 let all = [ NW ; N ; NE
73 ; W ; E
74 ; SW ; S ; SE
75 ]
76
7c363dd8
SK
77 let to_offset =
78 let open Point in
79 function
80 | NW -> {r = -1; k = -1}
81 | N -> {r = -1; k = 0}
82 | NE -> {r = -1; k = 1}
83 | W -> {r = 0; k = -1}
84 | E -> {r = 0; k = 1}
85 | SW -> {r = 1; k = -1}
86 | S -> {r = 1; k = 0}
87 | SE -> {r = 1; k = 1}
394125ca
SK
88 end
89
4d49c95e
SK
90 type 'a t = 'a array array
91
a1665c92
SK
92 let create ~rs ~ks x =
93 Array.make_matrix ~dimx:rs ~dimy:ks x
4d49c95e
SK
94
95 let iter t ~f =
96 Array.iteri t ~f:(
63fe855d
SK
97 fun r ks ->
98 Array.iteri ks ~f:(
a1665c92
SK
99 fun k x ->
100 f {Point.r; Point.k} x
4d49c95e
SK
101 )
102 )
103
0ce0e798
SK
104 let print t ~to_string =
105 Array.iter t ~f:(
63fe855d
SK
106 fun r ->
107 Array.iter r ~f:(fun x -> printf "%s" (to_string x));
0ce0e798
SK
108 print_newline ()
109 )
110
4d49c95e 111 let map t ~f =
65dbef41
SK
112 Array.map t ~f:(Array.map ~f:(fun x -> f x))
113
114 let mapi t ~f =
4d49c95e 115 Array.mapi t ~f:(
63fe855d
SK
116 fun r ks ->
117 Array.mapi ks ~f:(
a1665c92
SK
118 fun k x ->
119 f {Point.r; Point.k} x
4d49c95e
SK
120 )
121 )
122
7c363dd8 123 let get t {Point.r; Point.k} =
63fe855d 124 t.(r).(k)
394125ca 125
7c363dd8 126 let is_within_bounds t {Point.r; Point.k} =
394125ca
SK
127 match t with
128 | [||] -> assert false
129 | t ->
130 r >= 0 && r < Array.length t &&
131 k >= 0 && k < Array.length t.(0)
132
7c363dd8 133 let neighborhood t point =
394125ca 134 List.map Direction.all ~f:Direction.to_offset
7c363dd8
SK
135 |> List.map ~f:(fun offset_point -> Point.(point + offset_point))
136 |> List.filter ~f:(is_within_bounds t)
394125ca 137
7c363dd8
SK
138 let get_neighbors t point =
139 List.map (neighborhood t point) ~f:(get t)
4d49c95e
SK
140end
141
142
a96702d3
SK
143module Msg = struct
144 type t = string
145end
146
147
148module State = struct
149 type t = string
150end
151
152
153module PhenoType = struct
154 type t = string
155end
156
da8f1674 157
a96702d3
SK
158module Cell = struct
159 type t = { msg : Msg.t
160 ; pheno : PhenoType.t
161 ; state : State.t
162 }
163end
0ce0e798 164
0ce0e798 165
a96702d3
SK
166module type RULE = sig
167 val create : unit -> Cell.t
da8f1674 168
a96702d3 169 val transition : state:State.t -> inputs:Msg.t list -> Cell.t
da8f1674
SK
170end
171
172
a96702d3
SK
173module Conway : RULE = struct
174 type state = D | A
0d6f7833 175
a96702d3
SK
176 let state_of_string : (string -> state) = function
177 | "D" -> D
178 | "A" -> A
179 | _ -> assert false
180
181 let state_of_int : (int -> state) = function
0ce0e798
SK
182 | 0 -> D
183 | 1 -> A
184 | _ -> assert false
185
a96702d3 186 let int_of_state : (state -> int) = function
0d6f7833
SK
187 | D -> 0
188 | A -> 1
189
a96702d3
SK
190 let string_of_state : (state -> string) = function
191 | D -> "D"
192 | A -> "A"
193
194 let msg_of_state : (state -> Msg.t) =
195 string_of_state
196
197 let pheno_of_state : (state -> PhenoType.t) = function
0ce0e798
SK
198 | D -> " "
199 | A -> "o"
200
a96702d3
SK
201 let int_of_msg msg =
202 msg |> state_of_string |> int_of_state
0ce0e798 203
a96702d3
SK
204 let next state ~live_neighbors =
205 match state with
0d6f7833
SK
206 | A when live_neighbors < 2 -> D
207 | A when live_neighbors < 4 -> A
208 | A when live_neighbors > 3 -> D
209 | D when live_neighbors = 3 -> A
b36c0aef
SK
210 | A -> A
211 | D -> D
a96702d3
SK
212
213 let cell_of_state s =
214 { Cell.msg = s |> msg_of_state
215 ; Cell.pheno = s |> pheno_of_state
216 ; Cell.state = s |> string_of_state
217 }
218
219 let create () =
220 Random.int 2 |> state_of_int |> cell_of_state
221
222 let live_neighbors inputs =
223 inputs |> List.map ~f:int_of_msg |> List.fold_left ~init:0 ~f:(+)
224
225 let transition ~state ~inputs =
226 state
227 |> state_of_string
228 |> next ~live_neighbors:(live_neighbors inputs)
229 |> cell_of_state
0d6f7833
SK
230end
231
232
d9fa5d46
SK
233module Automaton : sig
234 type t
aed335e3 235
a96702d3
SK
236 val create : rows:int
237 -> columns:int
238 -> interval:float
239 -> rules: (module RULE) list
240 -> t
aed335e3 241
d9fa5d46
SK
242 val loop : t -> unit
243end = struct
a96702d3
SK
244 type cell = { data : Cell.t
245 ; rule : (module RULE)
246 }
247
248 type t = { grid : cell Matrix.t
d9fa5d46
SK
249 ; interval : Time.Span.t
250 ; bar : string
251 }
aed335e3 252
a96702d3
SK
253 let create ~rows:rs ~columns:ks ~interval ~rules =
254 let n = List.length rules in
255 let i = Random.int n in
256 let init () =
257 let rule = List.nth_exn rules i in
258 let module Rule = (val rule : RULE) in
259 { rule
260 ; data = Rule.create ()
261 }
262 in
21c4909c 263 Terminal.clear ();
a96702d3 264 { grid = Matrix.map ~f:init (Matrix.create ~rs ~ks ())
d9fa5d46
SK
265 ; interval = Time.Span.of_float interval
266 ; bar = String.make ks '-'
267 }
268
a96702d3
SK
269 let cell_to_string cell =
270 cell.data.Cell.pheno
271
d9fa5d46 272 let print t =
21c4909c 273 Terminal.reset ();
d9fa5d46 274 print_endline t.bar;
a96702d3 275 Matrix.print t.grid ~to_string:cell_to_string;
d9fa5d46
SK
276 print_endline t.bar
277
278 let next t =
279 let grid =
280 Matrix.mapi t.grid ~f:(
a96702d3
SK
281 fun point {rule; data} ->
282 let module Rule = (val rule : RULE) in
d9fa5d46 283 let neighbors = Matrix.get_neighbors t.grid point in
a96702d3
SK
284 let data =
285 Rule.transition
286 ~state:data.Cell.state
287 ~inputs:(List.map neighbors ~f:(fun cell -> cell.data.Cell.msg))
288 in
289 {rule; data}
d9fa5d46
SK
290 )
291 in
292 {t with grid}
293
294 let rec loop t =
295 print t;
296 Time.pause t.interval;
297 loop (next t)
298end
7707ff62
SK
299
300
301let main () =
302 Random.self_init ();
d9fa5d46 303 let rows, columns = Or_error.ok_exn Linux_ext.get_terminal_size () in
a96702d3
SK
304 let interval = 0.1 in
305 let rules =
306 [ (module Conway : RULE)
307 ]
308 in
8526e3e1 309 Automaton.loop (Automaton.create ~rows:(rows - 3) ~columns ~interval ~rules)
8c93b722
SK
310
311
7d89c037
SK
312let spec =
313 let summary = "Polymorphic Cellular Automata" in
7707ff62 314 let spec = Command.Spec.empty in
7d89c037
SK
315 Command.basic ~summary spec main
316
317
318let () = Command.run spec
This page took 0.047776 seconds and 4 git commands to generate.