Skip to content

Commit

Permalink
Merge branch 'resync-triangle' of github.com:marionebl/ocaml into res…
Browse files Browse the repository at this point in the history
…ync-triangle
  • Loading branch information
marionebl committed Jun 26, 2019
2 parents 16af972 + 0a1bf0f commit deb036a
Show file tree
Hide file tree
Showing 36 changed files with 430 additions and 290 deletions.
10 changes: 5 additions & 5 deletions .travis/.travis-ci.sh
Original file line number Diff line number Diff line change
Expand Up @@ -27,23 +27,23 @@ sudo git checkout -- exercises/difference-of-squares/test.ml
sudo git checkout -- exercises/dominoes/test.ml
sudo git checkout -- exercises/etl/test.ml
# sudo git checkout -- exercises/forth/test.ml
sudo git checkout -- exercises/hamming/test.ml
# sudo git checkout -- exercises/hamming/test.ml
sudo git checkout -- exercises/hello-world/test.ml
# sudo git checkout -- exercises/luhn/test.ml
# sudo git checkout -- exercises/leap/test.ml
# sudo git checkout -- exercises/minesweeper/test.ml
sudo git checkout -- exercises/palindrome-products/test.ml
# sudo git checkout -- exercises/palindrome-products/test.ml
sudo git checkout -- exercises/pangram/test.ml
sudo git checkout -- exercises/phone-number/test.ml
# sudo git checkout -- exercises/phone-number/test.ml
sudo git checkout -- exercises/prime-factors/test.ml
sudo git checkout -- exercises/raindrops/test.ml
sudo git checkout -- exercises/rectangles/test.ml
sudo git checkout -- exercises/roman-numerals/test.ml
sudo git checkout -- exercises/run-length-encoding/test.ml
sudo git checkout -- exercises/say/test.ml
# sudo git checkout -- exercises/say/test.ml
sudo git checkout -- exercises/space-age/test.ml
# sudo git checkout -- exercises/triangle/test.ml
sudo git checkout -- exercises/word-count/test.ml
# sudo git checkout -- exercises/word-count/test.ml

# if output=$(git status --porcelain -- "exercises/**/test.ml") && [ -z "$output" ]; then
# echo "Tests are in sync."
Expand Down
2 changes: 1 addition & 1 deletion .travis/Dockerfile
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
FROM ocaml/opam2:alpine-3.9-ocaml-4.07

RUN sudo apk add m4 linux-headers
RUN opam install dune ocamlfind core ounit qcheck react ppx_deriving yojson ounit ocp-indent
RUN opam install dune ocamlfind core ounit qcheck react ppx_deriving yojson ounit ocp-indent calendar
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ To run all the tests, type `make` from the top level ocaml directory.

To run tests for an individual exercise, `make test-assignment ASSIGNMENT=luhn`

The Makefile is a slim wrapper around [dune](https://github.com/ocaml/dune). Each exercise has a jbuild file which describes how to build it.
The Makefile is a slim wrapper around [dune](https://github.com/ocaml/dune). Each exercise has a dune file which describes how to build it.

## Adding an Exercise

Expand Down
5 changes: 3 additions & 2 deletions docs/TESTS.md
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
Because OCaml is a compiled language you need to compile your submission and the test code before you can run the tests.
We use [`jbuilder`](https://jbuilder.readthedocs.io/en/latest/) to build.
Each folder has a jbuild file specifying how to build and also a Makefile which delegates to jbuild.
We use [`dune`](https://dune.build/) to build.
Each folder has a dune file specifying how to build and also a Makefile which delegates to dune.

To compile and run the tests, simply type from the exercise folder:

```bash
make
```
Expand Down
3 changes: 1 addition & 2 deletions exercises/connect/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,7 @@ Your goal is to build a program that given a simple representation of a board
computes the winner (or lack thereof). Note that all games need not be "fair".
(For example, players may have mismatched piece counts.)

The boards look like this (with spaces added for readability, which won't be in
the representation passed to your code):
The boards look like this:

```text
. O . X .
Expand Down
15 changes: 11 additions & 4 deletions exercises/hamming/example.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
open Base
open List.Or_unequal_lengths

type nucleotide = A | C | G | T

Expand All @@ -10,7 +9,15 @@ let equal (x,y) = match (x, y) with
| (T, T) -> true
| _ -> false

let to_result (l: 'a List.Or_unequal_lengths.t): ('a, string) Result.t =
let open List.Or_unequal_lengths in
match l with
| Unequal_lengths -> Error "left and right strands must be of equal length"
| Ok x -> Ok x

let hamming_distance a b =
List.zip a b
|> function Unequal_lengths -> None | Ok l -> Some l
|> Option.map ~f:(List.count ~f:(Fn.non equal))
match (List.is_empty a, List.is_empty b) with
| (true, false) -> Error "left strand must not be empty"
| (false, true) -> Error "right strand must not be empty"
| _ -> List.zip a b |> to_result |> Result.map ~f:(List.count ~f:(Fn.non equal))

4 changes: 3 additions & 1 deletion exercises/hamming/hamming.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
open Base

type nucleotide = A | C | G | T

(** Compute the hamming distance between the two lists. *)
val hamming_distance : nucleotide list -> nucleotide list -> int option
val hamming_distance : nucleotide list -> nucleotide list -> (int, string) Result.t
46 changes: 17 additions & 29 deletions exercises/hamming/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@ open OUnit2
open Hamming

let printer = function
| None -> "None"
| Some x -> Int.to_string x
| Error m -> "Error \"" ^ m ^ "\""
| Ok x -> "Some " ^ (Int.to_string x)

let ae exp got _test_ctxt = assert_equal ~printer exp got

Expand All @@ -21,36 +21,24 @@ let hamdist a b = hamming_distance (dna_of_string a) (dna_of_string b)

let tests = [
"empty strands" >::
ae (Some 0) (hamdist "" "");
"identical strands" >::
ae (Some 0) (hamdist "A" "A");
ae (Ok 0) (hamdist "" "");
"single letter identical strands" >::
ae (Ok 0) (hamdist "A" "A");
"single letter different strands" >::
ae (Ok 1) (hamdist "G" "T");
"long identical strands" >::
ae (Some 0) (hamdist "GGACTGA" "GGACTGA");
"complete distance in single nucleotide strands" >::
ae (Some 1) (hamdist "A" "G");
"complete distance in small strands" >::
ae (Some 2) (hamdist "AG" "CT");
"small distance in small strands" >::
ae (Some 1) (hamdist "AT" "CT");
"small distance" >::
ae (Some 1) (hamdist "GGACG" "GGTCG");
"small distance in long strands" >::
ae (Some 2) (hamdist "ACCAGGG" "ACTATGG");
"non-unique character in first strand" >::
ae (Some 1) (hamdist "AAG" "AAA");
"non-unique character in second strand" >::
ae (Some 1) (hamdist "AAA" "AAG");
"same nucleotides in different positions" >::
ae (Some 2) (hamdist "TAG" "GAT");
"large distance" >::
ae (Some 4) (hamdist "GATACA" "GCATAA");
"large distance in off-by-one strand" >::
ae (Some 9) (hamdist "GGACGGATTCTG" "AGGACGGATTCT");
ae (Ok 0) (hamdist "GGACTGAAATCTG" "GGACTGAAATCTG");
"long different strands" >::
ae (Ok 9) (hamdist "GGACGGATTCTG" "AGGACGGATTCT");
"disallow first strand longer" >::
ae None (hamdist "AATG" "AAA");
ae (Error "left and right strands must be of equal length") (hamdist "AATG" "AAA");
"disallow second strand longer" >::
ae None (hamdist "ATA" "AGTG");
ae (Error "left and right strands must be of equal length") (hamdist "ATA" "AGTG");
"disallow left empty strand" >::
ae (Error "left strand must not be empty") (hamdist "" "G");
"disallow right empty strand" >::
ae (Error "right strand must not be empty") (hamdist "G" "");
]

let () =
run_test_tt_main ("hamming tests" >::: tests)
run_test_tt_main ("hamming tests" >::: tests)
2 changes: 2 additions & 0 deletions exercises/meetup/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,8 @@ descriptor calculate the date of the actual meetup. For example, if given

3. For library documentation, follow [Useful OCaml resources](https://exercism.io/tracks/ocaml/resources).

4. For `CalendarLib` documentation, see [Calendar](http://calendar.forge.ocamlcore.org/)

## Running Tests
A `Makefile` is provided with a default target to compile your solution and run the tests. At the command line, type:

Expand Down
2 changes: 1 addition & 1 deletion exercises/meetup/dune
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
(executable
(name test)
(libraries core_kernel oUnit))
(libraries base calendar oUnit))

(alias
(name runtest)
Expand Down
32 changes: 11 additions & 21 deletions exercises/meetup/example.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
open Core_kernel
open Base
open CalendarLib

type schedule = First | Second | Third | Fourth | Teenth | Last

Expand All @@ -18,7 +19,7 @@ let diff_days (d1: weekday) (d2: weekday): int =
| Sunday -> 6 in
(weekday_to_int d1 - weekday_to_int d2) % 7

let day_of_week (d: Date.t): weekday = let open Day_of_week in
let day_of_week (d: Date.t): weekday =
match Date.day_of_week d with
| Sun -> Sunday
| Mon -> Monday
Expand All @@ -36,28 +37,17 @@ let schedule_to_int = function
| Teenth -> 4
| Last -> 5

let is_leap_year y =
let divides n = y % n = 0 in
divides 4 && (not @@ divides 100 || divides 400)

let month_length y = let open Month in function
| Feb -> if is_leap_year y then 29 else 28
| Apr -> 30
| Jun -> 30
| Sep -> 30
| Nov -> 30
| _ -> 31
let add_days base days =
Date.Period.day days |> Date.add base

let meetup_day schedule weekday ~year ~month =
let month = Month.of_int_exn month in
let base = Date.create_exn ~y:year ~m:month ~d:1 in
let calc_offset start = start + diff_days weekday
(Date.add_days base start |> day_of_week) in
let base = Date.make year month 1 in
let calc_offset start = start + diff_days weekday (add_days base start |> day_of_week) in
let day = calc_offset @@ match schedule with
| Teenth -> 12
| Last -> 21 + max 0 (month_length year month - 28)
| Last -> 21 + max 0 (Date.days_in_month base - 28)
| _ -> 7 * schedule_to_int schedule in
let core_date = Date.add_days base day
let core_date = add_days base day
in (Date.year core_date,
Date.month core_date |> Month.to_int,
Date.day core_date)
Date.month core_date |> Date.int_of_month,
Date.day_of_month core_date)
53 changes: 53 additions & 0 deletions exercises/meetup/meetup.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
open Base
open CalendarLib

type schedule = First | Second | Third | Fourth | Teenth | Last

type weekday = Monday | Tuesday | Wednesday | Thursday
| Friday | Saturday | Sunday

type date = (int * int * int)

let diff_days (d1: weekday) (d2: weekday): int =
let weekday_to_int = function
| Monday -> 0
| Tuesday -> 1
| Wednesday -> 2
| Thursday -> 3
| Friday -> 4
| Saturday -> 5
| Sunday -> 6 in
(weekday_to_int d1 - weekday_to_int d2) % 7

let day_of_week (d: Date.t): weekday =
match Date.day_of_week d with
| Sun -> Sunday
| Mon -> Monday
| Tue -> Tuesday
| Wed -> Wednesday
| Thu -> Thursday
| Fri -> Friday
| Sat -> Saturday

let schedule_to_int = function
| First -> 0
| Second -> 1
| Third -> 2
| Fourth -> 3
| Teenth -> 4
| Last -> 5

let add_days base days =
Date.Period.day days |> Date.add base

let meetup_day schedule weekday ~year ~month =
let base = Date.make year month 1 in
let calc_offset start = start + diff_days weekday (add_days base start |> day_of_week) in
let day = calc_offset @@ match schedule with
| Teenth -> 12
| Last -> 21 + max 0 (Date.days_in_month base - 28)
| _ -> 7 * schedule_to_int schedule in
let core_date = add_days base day
in (Date.year core_date,
Date.month core_date |> Date.int_of_month,
Date.day_of_month core_date)
4 changes: 2 additions & 2 deletions exercises/meetup/test.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
open OUnit2
open Meetup
open Core_kernel
open Base

type case = {
description: string;
Expand All @@ -12,7 +12,7 @@ type case = {
}

let ae exp got _test_ctxt = assert_equal
~printer:(fun (y, m, d) -> sprintf "%d-%02d-%02d" y m d) exp got
~printer:(fun (y, m, d) -> Printf.sprintf "%d-%02d-%02d" y m d) exp got

let make_test (c: case) =
c.description >::
Expand Down
4 changes: 2 additions & 2 deletions exercises/palindrome-products/Makefile
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
default: clean test

test:
jbuilder runtest
dune runtest

clean:
jbuilder clean
dune clean

.PHONY: clean
36 changes: 25 additions & 11 deletions exercises/palindrome-products/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,33 +36,47 @@ Given the range `[10, 99]` (both inclusive)...
The smallest palindrome product is `121`. Its factors are `(11, 11)`.
The largest palindrome product is `9009`. Its factors are `(91, 99)`.


## Getting Started
1. [Install the Exercism CLI](https://exercism.io/cli-walkthrough).
For installation and learning resources, refer to the
[exercism help page](http://exercism.io/languages/ocaml).

## Installation
To work on the exercises, you will need `Opam` and `Base`. Consult [opam](https://opam.ocaml.org) website for instructions on how to install `opam` for your OS. Once `opam` is installed open a terminal window and run the following command to install base:

2. [Install OCaml](https://exercism.io/tracks/ocaml/installation).
```bash
opam install base
```

3. For library documentation, follow [Useful OCaml resources](https://exercism.io/tracks/ocaml/resources).
To run the tests you will need `OUnit`. Install it using `opam`:

```bash
opam install ounit
```

## Running Tests
A `Makefile` is provided with a default target to compile your solution and run the tests. At the command line, type:
A Makefile is provided with a default target to compile your solution and run the tests. At the command line, type:

```bash
make
```

## Submitting Incomplete Solutions
It's possible to submit an incomplete solution so you can see how others have completed the exercise.
## Interactive Shell
`utop` is a command line program which allows you to run Ocaml code interactively. The easiest way to install it is via opam:
```bash
opam install utop
```
Consult [utop](https://github.com/diml/utop/blob/master/README.md) for more detail.

## Feedback, Issues, Pull Requests
The [exercism/ocaml](https://github.com/exercism/ocaml) repository on GitHub is
the home for all of the Ocaml exercises.
The [exercism/ocaml](https://github.com/exercism/ocaml) repository on
GitHub is the home for all of the Ocaml exercises.

If you have feedback about an exercise, or want to help implementing a new
one, head over there and create an issue or submit a PR. We welcome new
contributors!
one, head over there and create an issue. We'll do our best to help you!

## Source

Problem 4 at Project Euler [http://projecteuler.net/problem=4](http://projecteuler.net/problem=4)

## 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/palindrome-products/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
(executable
(name test)
(libraries base oUnit)
(preprocess
(pps ppx_deriving.eq ppx_deriving.show)))

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

(env
(dev
(flags (:standard -warn-error -A))))
1 change: 1 addition & 0 deletions exercises/palindrome-products/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.0)
Loading

0 comments on commit deb036a

Please sign in to comment.