Skip to content

Commit 3871ee1

Browse files
committed
Documentation: Sequences #791
Commit 5305db6 Author: Cuihtlauac ALVARADO <[email protected]> Some more edits
1 parent a87d028 commit 3871ee1

File tree

3 files changed

+400
-0
lines changed

3 files changed

+400
-0
lines changed

data/problems/diag.md

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
---
2+
title: Diagonal of a Sequence of Sequences
3+
number: "101"
4+
difficulty: intermediate
5+
tags: [ "seq" ]
6+
---
7+
8+
# Solution
9+
10+
```ocaml
11+
let rec diag seq_seq () =
12+
let hds, tls = Seq.filter_map Seq.uncons seq_seq |> Seq.split in
13+
let hd, tl = Seq.uncons hds |> Option.map fst, Seq.uncons tls |> Option.map snd in
14+
let d = Option.fold ~none:Seq.empty ~some:diag tl in
15+
Option.fold ~none:Fun.id ~some:Seq.cons hd d ()
16+
```
17+
18+
# Statement
19+
20+
Write a function `diag : 'a Seq.t Seq.t -> 'a Seq` that returns the _diagonal_
21+
of a sequence of sequences. The returned sequence is formed as follows:
22+
The first element of the returned sequence is the first element of the first
23+
sequence; the second element of the returned sequence is the second element of
24+
the second sequence; the third element of the returned sequence is the third
25+
element of the third sequence; and so on.

data/problems/stream.md

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,61 @@
1+
---
2+
title: Never-Ending Sequences
3+
number: "100"
4+
difficulty: beginner
5+
tags: [ "seq" ]
6+
---
7+
8+
# Solution
9+
10+
```ocaml
11+
type 'a cons = Cons of 'a * 'a stream
12+
and 'a stream = unit -> 'a cons
13+
14+
let hd (seq : 'a stream) = let (Cons (x, _)) = seq () in x
15+
let tl (seq : 'a stream) = let (Cons (_, seq)) = seq () in seq
16+
let rec take n seq = if n = 0 then [] else let (Cons (x, seq)) = seq () in x :: take (n - 1) seq
17+
let rec unfold f x () = let (y, x) = f x in Cons (y, unfold f x)
18+
let bang x = unfold (fun x -> (x, x)) x
19+
let ints x = unfold (fun x -> (x, x + 1)) x
20+
let rec map f seq () = let (Cons (x, seq)) = seq () in Cons (f x, map f seq)
21+
let rec filter p seq () = let (Cons (x, seq)) = seq () in let seq = filter p seq in if p x then Cons (x, seq) else seq ()
22+
let rec iter f seq = let (Cons (x, seq)) = seq () in f x; iter f seq
23+
let to_seq seq = Seq.unfold (fun seq -> Some (hd seq, tl seq)) seq
24+
let rec of_seq seq () = match seq () with
25+
| Seq.Nil -> failwith "Not a infinite sequence"
26+
| Seq.Cons (x, seq) -> Cons (x, of_seq seq)
27+
```
28+
29+
# Statement
30+
31+
Lists are finite, meaning they always contain a finite number of elements. Sequences may
32+
be finite or infinite.
33+
34+
The goal of this exercise is to define a type `'a stream` which only contains
35+
infinite sequences. Using this type, define the following functions:
36+
```ocaml
37+
val hd : 'a stream -> 'a
38+
(** Returns the first element of a stream *)
39+
val tl : 'a stream -> 'a stream
40+
(** Removes the first element of a stream *)
41+
val take : int -> 'a stream -> 'a list
42+
(** [take n seq] returns the n first values of [seq] *)
43+
val unfold : ('a -> 'b * 'a) -> 'a -> 'b stream
44+
(** Similar to Seq.unfold *)
45+
val bang : 'a -> 'a stream
46+
(** [bang x] produces an infinitely repeating sequence of [x] values. *)
47+
val ints : int -> int stream
48+
(* Similar to Seq.ints *)
49+
val map : ('a -> 'b) -> 'a stream -> 'b stream
50+
(** Similar to List.map and Seq.map *)
51+
val filter: ('a -> bool) -> 'a stream -> 'a stream
52+
(** Similar to List.filter and Seq.filter *)
53+
val iter : ('a -> unit) -> 'a stream -> 'b
54+
(** Similar to List.iter and Seq.iter *)
55+
val to_seq : 'a stream -> 'a Seq.t
56+
(** Translates an ['a stream] into an ['a Seq.t] *)
57+
val of_seq : 'a Seq.t -> 'a stream
58+
(** Translates an ['a Seq.t] into an ['a stream]
59+
@raise Failure if the input sequence is finite. *)
60+
```
61+
**Tip:** Use `let ... =` patterns.

0 commit comments

Comments
 (0)