Improve description.
[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
4b18b7df
SK
153module PhenoType : sig
154 type t
155
156 val create : char -> Terminal.color option -> t
157
158 val to_string : t -> string
159end = struct
160 type t = { color : Terminal.color option
161 ; character : char
162 }
163
164 let create character color =
165 {color; character}
166
167 let to_string = function
168 | {color=None; character} ->
169 String.of_char character
170 | {color=Some c; character} ->
171 Terminal.string_with_color (String.of_char character) c
a96702d3
SK
172end
173
da8f1674 174
a96702d3
SK
175module Cell = struct
176 type t = { msg : Msg.t
177 ; pheno : PhenoType.t
178 ; state : State.t
179 }
180end
0ce0e798 181
0ce0e798 182
a96702d3
SK
183module type RULE = sig
184 val create : unit -> Cell.t
da8f1674 185
a96702d3 186 val transition : state:State.t -> inputs:Msg.t list -> Cell.t
da8f1674
SK
187end
188
189
a96702d3
SK
190module Conway : RULE = struct
191 type state = D | A
0d6f7833 192
a96702d3
SK
193 let state_of_string : (string -> state) = function
194 | "D" -> D
195 | "A" -> A
196 | _ -> assert false
197
198 let state_of_int : (int -> state) = function
0ce0e798
SK
199 | 0 -> D
200 | 1 -> A
201 | _ -> assert false
202
a96702d3 203 let int_of_state : (state -> int) = function
0d6f7833
SK
204 | D -> 0
205 | A -> 1
206
a96702d3
SK
207 let string_of_state : (state -> string) = function
208 | D -> "D"
209 | A -> "A"
210
211 let msg_of_state : (state -> Msg.t) =
212 string_of_state
213
214 let pheno_of_state : (state -> PhenoType.t) = function
4b18b7df
SK
215 | D -> PhenoType.create ' ' None
216 | A -> PhenoType.create 'o' None
0ce0e798 217
a96702d3
SK
218 let int_of_msg msg =
219 msg |> state_of_string |> int_of_state
0ce0e798 220
a96702d3
SK
221 let next state ~live_neighbors =
222 match state with
0d6f7833
SK
223 | A when live_neighbors < 2 -> D
224 | A when live_neighbors < 4 -> A
225 | A when live_neighbors > 3 -> D
226 | D when live_neighbors = 3 -> A
b36c0aef
SK
227 | A -> A
228 | D -> D
a96702d3
SK
229
230 let cell_of_state s =
231 { Cell.msg = s |> msg_of_state
232 ; Cell.pheno = s |> pheno_of_state
233 ; Cell.state = s |> string_of_state
234 }
235
236 let create () =
237 Random.int 2 |> state_of_int |> cell_of_state
238
239 let live_neighbors inputs =
240 inputs |> List.map ~f:int_of_msg |> List.fold_left ~init:0 ~f:(+)
241
242 let transition ~state ~inputs =
243 state
244 |> state_of_string
245 |> next ~live_neighbors:(live_neighbors inputs)
246 |> cell_of_state
0d6f7833
SK
247end
248
249
d9fa5d46
SK
250module Automaton : sig
251 type t
aed335e3 252
a96702d3
SK
253 val create : rows:int
254 -> columns:int
255 -> interval:float
256 -> rules: (module RULE) list
257 -> t
aed335e3 258
d9fa5d46
SK
259 val loop : t -> unit
260end = struct
a96702d3
SK
261 type cell = { data : Cell.t
262 ; rule : (module RULE)
263 }
264
265 type t = { grid : cell Matrix.t
d9fa5d46
SK
266 ; interval : Time.Span.t
267 ; bar : string
268 }
aed335e3 269
a96702d3
SK
270 let create ~rows:rs ~columns:ks ~interval ~rules =
271 let n = List.length rules in
272 let i = Random.int n in
273 let init () =
274 let rule = List.nth_exn rules i in
275 let module Rule = (val rule : RULE) in
276 { rule
277 ; data = Rule.create ()
278 }
279 in
21c4909c 280 Terminal.clear ();
a96702d3 281 { grid = Matrix.map ~f:init (Matrix.create ~rs ~ks ())
d9fa5d46
SK
282 ; interval = Time.Span.of_float interval
283 ; bar = String.make ks '-'
284 }
285
a96702d3 286 let cell_to_string cell =
4b18b7df 287 PhenoType.to_string cell.data.Cell.pheno
a96702d3 288
d9fa5d46 289 let print t =
21c4909c 290 Terminal.reset ();
d9fa5d46 291 print_endline t.bar;
a96702d3 292 Matrix.print t.grid ~to_string:cell_to_string;
d9fa5d46
SK
293 print_endline t.bar
294
295 let next t =
296 let grid =
297 Matrix.mapi t.grid ~f:(
a96702d3
SK
298 fun point {rule; data} ->
299 let module Rule = (val rule : RULE) in
d9fa5d46 300 let neighbors = Matrix.get_neighbors t.grid point in
a96702d3
SK
301 let data =
302 Rule.transition
303 ~state:data.Cell.state
304 ~inputs:(List.map neighbors ~f:(fun cell -> cell.data.Cell.msg))
305 in
306 {rule; data}
d9fa5d46
SK
307 )
308 in
309 {t with grid}
310
311 let rec loop t =
312 print t;
313 Time.pause t.interval;
314 loop (next t)
315end
7707ff62
SK
316
317
318let main () =
319 Random.self_init ();
d9fa5d46 320 let rows, columns = Or_error.ok_exn Linux_ext.get_terminal_size () in
a96702d3
SK
321 let interval = 0.1 in
322 let rules =
323 [ (module Conway : RULE)
324 ]
325 in
8526e3e1 326 Automaton.loop (Automaton.create ~rows:(rows - 3) ~columns ~interval ~rules)
8c93b722
SK
327
328
7d89c037
SK
329let spec =
330 let summary = "Polymorphic Cellular Automata" in
7707ff62 331 let spec = Command.Spec.empty in
7d89c037
SK
332 Command.basic ~summary spec main
333
334
335let () = Command.run spec
This page took 0.059954 seconds and 4 git commands to generate.