Skip to content

Commit

Permalink
binary-search-tree: port exercise (#370)
Browse files Browse the repository at this point in the history
Canonical version 1.0.0 from exercism/problem-specifications#940

This commit does not contain a test generator for the exercise.
  • Loading branch information
voila authored and sshine committed Oct 17, 2019
1 parent 15fbc72 commit 7cbe850
Show file tree
Hide file tree
Showing 9 changed files with 216 additions and 0 deletions.
12 changes: 12 additions & 0 deletions config.json
Original file line number Diff line number Diff line change
Expand Up @@ -447,6 +447,18 @@
"difficulty": 0,
"topics": null,
"deprecated": true
},
{
"slug": "binary-search-tree",
"uuid": "ce05137f-d4e5-40f2-ae6b-6c43e00d458f",
"core": false,
"unlocked_by": null,
"difficulty": 3,
"topics": [
"recursion",
"searching",
"trees"
]
}
]
}
9 changes: 9 additions & 0 deletions exercises/binary-search-tree/Makefile
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
default: clean test

test:
dune runtest

clean:
dune clean

.PHONY: clean
60 changes: 60 additions & 0 deletions exercises/binary-search-tree/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
# Binary Search Tree

Insert and search for numbers in a binary tree.

When we need to represent sorted data, an array does not make a good
data structure.

Say we have the array `[1, 3, 4, 5]`, and we add 2 to it so it becomes
`[1, 3, 4, 5, 2]` now we must sort the entire array again! We can
improve on this by realizing that we only need to make space for the new
item `[1, nil, 3, 4, 5]`, and then adding the item in the space we
added. But this still requires us to shift many elements down by one.

Binary Search Trees, however, can operate on sorted data much more
efficiently.

A binary search tree consists of a series of connected nodes. Each node
contains a piece of data (e.g. the number 3), a variable named `left`,
and a variable named `right`. The `left` and `right` variables point at
`nil`, or other nodes. Since these other nodes in turn have other nodes
beneath them, we say that the left and right variables are pointing at
subtrees. All data in the left subtree is less than or equal to the
current node's data, and all data in the right subtree is greater than
the current node's data.

For example, if we had a node containing the data 4, and we added the
data 2, our tree would look like this:

4
/
2

If we then added 6, it would look like this:

4
/ \
2 6

If we then added 3, it would look like this

4
/ \
2 6
\
3

And if we then added 1, 5, and 7, it would look like this

4
/ \
/ \
2 6
/ \ / \
1 3 5 7
## Source

Josh Cheek [https://twitter.com/josh_cheek](https://twitter.com/josh_cheek)

## Submitting Incomplete Solutions
It's possible to submit an incomplete solution so you can see how others have completed the exercise.
16 changes: 16 additions & 0 deletions exercises/binary-search-tree/binary_search_tree.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
open Base

type bst

let empty = failwith "'empty' is missing"

let value _ = failwith "'value' is missing"

let left _ = failwith "'left' is missing"

let right _ = failwith "'right' is missing"

let insert _ _ = failwith "'insert' is missing"

let to_list _ = failwith "'to_list' is missing"

16 changes: 16 additions & 0 deletions exercises/binary-search-tree/binary_search_tree.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
open Base

type bst

val empty : bst

val value : bst -> (int, string) Result.t

val left : bst -> (bst, string) Result.t

val right : bst -> (bst, string) Result.t

val insert : int -> bst -> bst

val to_list : bst -> int list

16 changes: 16 additions & 0 deletions exercises/binary-search-tree/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
(executable
(name test)
(libraries base oUnit))

(alias
(name runtest)
(deps (:x test.exe))
(action (run %{x})))

(alias
(name buildtest)
(deps (:x test.exe)))

(env
(dev
(flags (:standard -warn-error -A))))
2 changes: 2 additions & 0 deletions exercises/binary-search-tree/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(lang dune 1.1)
(version 1.0.0)
26 changes: 26 additions & 0 deletions exercises/binary-search-tree/example.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
open Base

type bst = Leaf | Node of bst * int * bst

let empty = Leaf

let value = function
| Leaf -> Error "empty tree"
| Node(_, v, _) -> Ok v

let left = function
| Leaf -> Error "empty tree"
| Node(l, _, _) -> Ok l

let right = function
| Leaf -> Error "empty tree"
| Node(_, _, r) -> Ok r

let rec insert v = function
| Leaf -> Node(Leaf, v, Leaf)
| Node(l, v', r) when v <= v' -> Node(insert v l, v', r)
| Node(l, v', r) -> Node(l, v', insert v r)

let rec to_list = function
| Leaf -> []
| Node(l, v, r) -> to_list(l) @ [v] @ to_list(r)
59 changes: 59 additions & 0 deletions exercises/binary-search-tree/test.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
(* binary-search-tree - 1.0.0 *)
open Base
open OUnit2
open Binary_search_tree

let result_to_string f = function
| Error m -> Printf.sprintf "Error \"%s\"" m
| Ok x -> f x |> Printf.sprintf "Some %s"

let ae exp got _test_ctxt =
assert_equal ~printer:(result_to_string Int.to_string) exp got

let intlist_to_string l =
List.map l ~f:Int.to_string
|> List.intersperse ~sep:"; "
|> List.fold ~init:"" ~f:(^)
|> fun s -> "[" ^ s ^ "]"

let ael exp got _test_ctxt =
assert_equal ~printer:intlist_to_string exp got

let tests =
let t4 = empty |> insert 4 in
let t42 = t4 |> insert 2 in
let l2 = t42 |> left in
let t44 = t4 |> insert 4 in
let l4 = t44 |> left in
let t45 = t4 |> insert 5 in
let r5 = t45 |> right in
let t4261357 = t42 |> insert 6 |> insert 1 |> insert 3 |> insert 5 |> insert 7 in
let t2 = empty |> insert 2 in
let t21 = t2 |> insert 1 in
let t22 = t2 |> insert 2 in
let t23 = t2 |> insert 3 in
let t213675 = t21 |> insert 3 |> insert 6 |> insert 7 |> insert 5 in
[
"data is retained" >:: ae (Ok 4) (value t4);
"smaller number at left node 1" >:: ae (Ok 4) (value t42);
"smaller number at left node 2" >:: ae (Ok 2) (Result.bind l2 ~f:value);
"same number at left node 1" >:: ae (Ok 4) (value t44);
"same number at left node 2" >:: ae (Ok 4) (Result.bind l4 ~f:value);
"greater number at right node 1" >:: ae (Ok 4) (value t45);
"greater number at right node 2" >:: ae (Ok 5) (Result.bind r5 ~f:value);
"can create complex tree 1" >:: ae (Ok 4) (value t4261357);
"can create complex tree 2" >:: ae (Ok 2) (Result.bind (t4261357 |> left) ~f:value);
"can create complex tree 3" >:: ae (Ok 1) (Result.bind (Result.bind (t4261357 |> left) ~f:left) ~f:value);
"can create complex tree 4" >:: ae (Ok 3) (Result.bind (Result.bind (t4261357 |> left) ~f:right) ~f:value);
"can create complex tree 5" >:: ae (Ok 6) (Result.bind (t4261357 |> right) ~f:value);
"can create complex tree 6" >:: ae (Ok 5) (Result.bind (Result.bind (t4261357 |> right) ~f:left) ~f:value);
"can create complex tree 7" >:: ae (Ok 7) (Result.bind (Result.bind (t4261357 |> right) ~f:right) ~f:value);
"can sort single number" >:: ael [2] (to_list t2);
"can sort if second number is smaller than first" >:: ael [1;2] (to_list t21);
"can sort if second number is same as first" >:: ael [2;2] (to_list t22);
"can sort if second number is greater than first" >:: ael [2;3] (to_list t23);
"can sort complex tree" >:: ael [1; 2; 3; 5; 6; 7] (to_list t213675);
]

let () =
run_test_tt_main ("binary-search-tree tests" >::: tests)

0 comments on commit 7cbe850

Please sign in to comment.