Giter VIP home page Giter VIP logo

c-cube / ocaml-containers Goto Github PK

View Code? Open in Web Editor NEW
479.0 17.0 85.0 21.63 MB

A lightweight, modular standard library extension, string library, and interfaces to various libraries (unix, threads, etc.) BSD license.

Home Page: https://c-cube.github.io/ocaml-containers/

License: BSD 2-Clause "Simplified" License

Makefile 0.07% OCaml 99.58% Standard ML 0.09% Shell 0.26%
ocaml stdlib data-structure portable permissive-license modular lightweight

ocaml-containers's Introduction

OCaml-containers πŸ“¦ Build and test

A modular, clean and powerful extension of the OCaml standard library.

(Jump to the current API documentation)

Containers is an extension of OCaml's standard library (under BSD license) focused on data structures, combinators and iterators, without dependencies on unix, str or num. Every module is independent and is prefixed with 'CC' in the global namespace. Some modules extend the stdlib (e.g. CCList provides safe map/fold_right/append, and additional functions on lists). Alternatively, open Containers will bring enhanced versions of the standard modules into scope.

Quick Summary

Containers is:

  • A usable, reasonably well-designed library that extends OCaml's standard library (in 'src/core/', packaged under containers in ocamlfind. Modules are totally independent and are prefixed with CC (for "containers-core" or "companion-cube" because I'm a megalomaniac). This part should be usable and should work. For instance, CCList contains functions and lists including safe versions of map and append. It also provides a drop-in replacement to the standard library, in the module Containers (intended to be opened, replaces some stdlib modules with extended ones), and a small S-expression printer and parser that can be functorized over the representation of values.
  • Some sub-libraries with a specific focus each:
    • Utilities around the unix library in containers.unix (mainly to spawn sub-processes easily and deal with resources safely)
    • A bencode codec in containers.bencode. This is a tiny json-like serialization format that is extremely simple. It comes from bittorrent files.
    • A CBOR codec in containers.cbor. This is a compact binary serialization format.
    • The Strongly Connected Component algorithm, functorized, in containers.scc
  • A separate library containers-data with additional data structures that don't have an equivalent in the standard library, typically not as thoroughly maintained. This is now in its own package since 3.0.

Some of the modules have been moved to their own repository (e.g. sequence (now iter), gen, qcheck) and are on opam for great fun and profit.

Containers-thread has been removed in favor of Moonpool.

Migration Guide

To 3.0

The changelog's breaking section contains a list of the breaking changes in this release.

  1. The biggest change is that some sub-libraries have been either turned into their own packages (containers-data), deleted (containers.iter),or merged elsewhere (containers.sexp). This means that if use these libraries you will have to edit your dune/_oasis/opam files.
  • if you use containers.sexp (i.e. the CCSexp module), it now lives in containers itself.
  • if you used anything in containers.data, you need to depend on the containers-data package now.
  1. Another large change is the removal (at last!) of functions deprecated in 2.8, related to the spread of Seq.t as the standard iterator type. Functions like CCVector.of_seq now operate on this standard Seq.t type, and old-time iteration based on iter is now named of_iter, to_iter, etc.

Here you need to change your code, possibly using search and replace. Thankfully, the typechecker should guide you.

  1. Array_slice and String.Sub have been removed to simplify the code and String more lightweight. There is no replacement at the moment. Please tell us if you need this to be turned into a sub-library.

  2. Renaming of some functions into more explicit/clear names. Examples:

  • CCVector.shrink is now CCVector.truncate
  • CCVector.remove is now CCVector.remove_unordered, to be contrasted with the new CCVector.remove_and_shift.
  • CCPair.map_fst and map_snd now transform a tuple into another tuple by modify the first (resp. second) element.
  1. All the collection pretty-printers now take their separator/start/stop optional arguments as unit printer (i.e. Format.formatter -> unit -> unit functions) rather than strings. This gives the caller better control over the formatting of lists, arrays, queues, tables, etc.

  2. Removal of many deprecated functions.

To 2.0

  • The type system should detect issues related to print renamed into pp easily. If you are lucky, a call to sed -i 's/print/pp/g' on the concerned files might help rename all the calls properly.

  • many optional arguments have become mandatory, because their default value would be a polymorphic "magic" operator such as (=) or (>=). Now these have to be specified explicitly, but during the transition you can use Stdlib.(=) and Stdlib.(>=) as explicit arguments.

  • if your code contains open Containers, the biggest hurdle you face might be that operators have become monomorphic by default. We believe this is a useful change that prevents many subtle bugs. However, during migration and until you use proper combinators for equality (CCEqual), comparison (CCOrd), and hashing (CCHash), you might want to add open Stdlib just after the open Containers. See the section on monomorphic operators for more details.

Monomorphic operators: why, and how?

Why shadow polymorphic operators by default?

To quote @bluddy in #196:

The main problem with polymorphic comparison is that many data structures will give one result for structural comparison, and a different result for semantic comparison. The classic example is comparing maps. If you have a list of maps and try to use comparison to sort them, you'll get the wrong result: multiple map structures can represent the same semantic mapping from key to value, and comparing them in terms of structure is simply wrong. A far more pernicious bug occurs with hashtables. Identical hashtables will seem to be identical for a while, as before they've had a key clash, the outer array is likely to be the same. Once you get a key clash though, you start getting lists inside the arrays (or maps inside the arrays if you try to make a smarter hashtable) and that will cause comparison errors ie. identical hashtables will be seen as different or vice versa.

Every time you use a polymorphic comparison where you're using a data type where structural comparison != semantic comparison, it's a bug. And every time you use polymorphic comparison where the type of data being compared may vary (e.g. it's an int now, but it may be a map later), you're planting a bug for the future.

See also:

Sometimes polymorphic operators still make sense!

If you just want to use polymorphic operators, it's fine! You can access them easily by using Stdlib.(=), Stdlib.max, etc.

When migrating a module, you can add open Stdlib on top of it to restore the default behavior. It is, however, recommended to export an equal function (and compare, and hash) for all the public types, even if their internal definition is just the corresponding polymorphic operator. This way, other modules can refer to Foo.equal and will not have to be updated the day Foo.equal is no longer just polymorphic equality. Another bonus is that Hashtbl.Make(Foo) or Map.Make(Foo) will just workβ„’.

Further discussions

See issues #196, #197

Debugging with ocamldebug

To print values with types defined in containers in the bytecode debugger, you first have to load the appropriate bytecode archives. After starting a session, e.g. ocamldebug your_program.bc,

# #load_printer containers_monomorphic.cma;;
# #load_printer containers.cma;;

For these archives to be found, you may have to run the program first. Now printing functions that have the appropriate type Format.formatter -> 'a -> unit can be installed. For example,

# #install_printer Containers.Int.pp;;

However, printer combinators are not easily handled by ocamldebug. For instance # install_printer Containers.(List.pp Int.pp) will not work out of the box. You can make this work by writing a short module which defines ready-made combined printing functions, and loading that in ocamldebug. For instance

module M = struct
	let pp_int_list = Containers.(List.pp Int.pp)
end;;

loaded via # load_printer m.cmo and installed as # install_printer M.pp_int_list.

Change Log

See this file.

Finding help

Use

You might start with the tutorial to get a picture of how to use the library.

You can either build and install the library (see build), or just copy files to your own project. The last solution has the benefits that you don't have additional dependencies nor build complications (and it may enable more inlining). Since modules have a friendly license and are mostly independent, both options are easy.

In a toplevel, using ocamlfind:

# #use "topfind";;
...
# #require "containers";;
# #require "containers-data";;
# CCList.flat_map;;
- : ('a -> 'b list) -> 'a list -> 'b list = <fun>
# open Containers (* optional *);;
# List.flat_map ;;
- : ('a -> 'b list) -> 'a list -> 'b list = <fun>

If you have comments, requests, or bugfixes, please share them! :-)

License

This code is free, under the BSD license.

Contents

See the documentation and the tutorial below for a gentle introduction.

Documentation

In general, see http://c-cube.github.io/ocaml-containers/last/ for the API documentation.

Some examples can be found there, per-version doc there.

Build

You will need OCaml >= 4.03.0.

Via opam

The preferred way to install is through opam.

$ opam install containers

From Sources

You need dune (formerly jbuilder).

$ make

To build and run tests (requires qcheck-core, gen, iter):

$ opam install qcheck-core
$ make test

To build the small benchmarking suite (requires benchmark):

$ opam install benchmark batteries
$ make bench
$ ./benchs/run_benchs.sh

Contributing

PRs on github are very welcome (patches by email too, if you prefer so).

how to contribute (click to unfold)

List of authors

The list of contributors can be seen on github.

Alternatively, git authors from git-extras can be invoked from within the repo to list authors based on the git commits.

First-Time Contributors

Assuming your are in a clone of the repository:

  1. Some dependencies are required, you'll need opam install benchmark qcheck-core iter gen mdx uutf yojson.
  2. run make all to enable everything (including tests).
  3. make your changes, commit, push, and open a PR.
  4. use make test without moderation! It must pass before a PR is merged. There are around 1150 tests right now, and new features should come with their own tests.

If you feel like writing new tests, that is totally worth a PR (and my gratefulness).

General Guidelines

A few guidelines to follow the philosophy of containers:

  • no dependencies between basic modules (even just for signatures);
  • add @since tags for new functions;
  • add tests if possible (see tests/ dir) There are numerous inline tests already, to see what it looks like search for comments starting with (*$ in source files.

For Total Beginners

Thanks for wanting to contribute! To contribute a change, here are the steps (roughly):

  1. click "fork" on https://github.com/c-cube/ocaml-containers on the top right of the page. This will create a copy of the repository on your own github account.

  2. click the big green "clone or download" button, with "SSH". Copy the URL (which should look like [email protected]:<your username>/ocaml-containers.git) into a terminal to enter the command:

    $ git clone [email protected]:<your username>/ocaml-containers.git
    
  3. then, cd into the newly created directory.

  4. make the changes you want. See <#first-time-contributors> for more details about what to do in particular.

  5. use git add and git commit to commit these changes.

  6. git push origin master to push the new change(s) onto your copy of the repository

  7. on github, open a "pull request" (PR). Et voilΓ  !

Tutorial

This tutorial contains a few examples to illustrate the features and usage of containers.

an introduction to containers (click to unfold)

We assume containers is installed and that the library is loaded, e.g. with:

# #require "containers";;
# Format.set_margin 50 (* for readability here *);;
- : unit = ()

Basics

We will start with a few list helpers, then look at other parts of the library, including printers, maps, etc.

# (|>) (* quick reminder of this awesome standard operator *);;
- : 'a -> ('a -> 'b) -> 'b = <fun>
# 10 |> succ;;
- : int = 11

# open CCList.Infix;;

# let l = 1 -- 100;;
val l : int list =
  [1; 2; 3; 4; 5; 6; 7; 8; 9; 10; 11; 12; 13; 14; 15; 16; 17; 18; 19; 20; 21;
   22; 23; 24; 25; 26; 27; 28; 29; 30; 31; 32; 33; 34; 35; 36; 37; 38; 39;
   40; 41; 42; 43; 44; 45; 46; 47; 48; 49; 50; 51; 52; 53; 54; 55; 56; 57;
   58; 59; 60; 61; 62; 63; 64; 65; 66; 67; 68; 69; 70; 71; 72; 73; 74; 75;
   76; 77; 78; 79; 80; 81; 82; 83; 84; 85; 86; 87; 88; 89; 90; 91; 92; 93;
   94; 95; 96; 97; 98; 99; 100]

# (* transform a list, dropping some elements *)
  l
  |> CCList.filter_map
     (fun x-> if x mod 3=0 then Some (float x) else None)
  |> CCList.take 5 ;;
- : float list = [3.; 6.; 9.; 12.; 15.]

# let l2 = l |> CCList.take_while (fun x -> x<10) ;;
val l2 : int list = [1; 2; 3; 4; 5; 6; 7; 8; 9]
(* an extension of Map.Make, compatible with Map.Make(CCInt) *)
module IntMap = CCMap.Make(CCInt);;
# (* conversions using the "iter" type, fast iterators that are
   pervasively used in containers. Combinators can be found
   in the opam library "iter". *)
  let map : string IntMap.t =
    l2
    |> List.map (fun x -> x, string_of_int x)
    |> CCList.to_iter
    |> IntMap.of_iter;;
val map : string IntMap.t = <abstr>

# CCList.to_iter (* check the type *);;
- : 'a list -> 'a CCList.iter = <fun>
# IntMap.of_iter ;;
- : (int * 'a) CCMap.iter -> 'a IntMap.t = <fun>

# (* we can print, too *)
  Format.printf "@[<2>map =@ @[<hov>%a@]@]@."
    (IntMap.pp CCFormat.int CCFormat.string_quoted)
    map;;
map =
  1 -> "1", 2 -> "2", 3 -> "3", 4 -> "4", 5
  -> "5", 6 -> "6", 7 -> "7", 8 -> "8", 9 -> "9"
- : unit = ()

# (* options are good *)
  IntMap.get 3 map |> CCOption.map (fun s->s ^ s);;
- : string option = Some "33"

New types: CCVector, CCHeap, CCResult, CCSexp, CCByte_buffer

Containers also contains (!) a few datatypes that are not from the standard library but that are useful in a lot of situations:

  • CCVector: A resizable array, with a mutability parameter. A value of type ('a, CCVector.ro) CCVector.t is an immutable vector of values of type 'a, whereas a ('a, CCVector.rw) CCVector.t is a mutable vector that can be modified. This way, vectors can be used in a quite functional way, using operations such as map or flat_map, or in a more imperative way.
  • CCHeap: A priority queue (currently, leftist heaps) functorized over a module sig val t val leq : t -> t -> bool that provides a type t and a partial order leq on t.
  • CCResult An error type for making error handling more explicit (an error monad, really, if you're not afraid of the "M"-word). Subsumes and replaces the old CCError. It uses the new result type from the standard library (or from the retrocompatibility package on opam) and provides many combinators for dealing with result.
  • CCSexp and CCCanonical_sexp: functorized printer and parser for S-expressions, respectively as actual S-expressions (like sexplib) and as canonical binary-safe S-expressions (like csexp)
  • CCByte_buffer: a better version of the standard Buffer.t which cannot be extended and prevents access to its internal byte array. This type is designed for (blocking) IOs and to produce complex strings incrementally in an efficient way.

Now for a few examples:

# (* create a new empty vector. It is mutable, for otherwise it would
   not be very useful. *)
  CCVector.create;;
- : unit -> ('a, CCVector.rw) CCVector.t = <fun>

# (* init, similar to Array.init, can be used to produce a
   vector that is mutable OR immutable (see the 'mut parameter?) *)
  CCVector.init ;;
- : int -> (int -> 'a) -> ('a, 'mut) CCVector.t = <fun>
# (* use the infix (--) operator for creating a range. Notice
   that v is a vector of integer but its mutability is not
   decided yet. *)
  let v = CCVector.(1 -- 10);;
val v : (int, '_a) CCVector.t = <abstr>
# Format.printf "v = @[%a@]@." (CCVector.pp CCInt.pp) v;;
v = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10
- : unit = ()
# CCVector.push v 42;;
- : unit = ()

# v (* now v is a mutable vector *);;
- : (int, CCVector.rw) CCVector.t = <abstr>

# (* functional combinators! *)
  let v2 : _ CCVector.ro_vector = v
  |> CCVector.map (fun x-> x+1)
  |> CCVector.filter (fun x-> x mod 2=0)
  |> CCVector.rev ;;
val v2 : int CCVector.ro_vector = <abstr>

# Format.printf "v2 = @[%a@]@." (CCVector.pp CCInt.pp) v2;;
v2 = 10, 8, 6, 4, 2
- : unit = ()
(* let's transfer to a heap *)
module IntHeap = CCHeap.Make(struct type t = int let leq = (<=) end);;
# let h = v2 |> CCVector.to_iter |> IntHeap.of_iter ;;
val h : IntHeap.t = <abstr>

# (* We can print the content of h
  (printing is not necessarily in order, though) *)
  Format.printf "h = [@[%a@]]@." (IntHeap.pp CCInt.pp) h;;
h = [2,4,6,8,10]
- : unit = ()

# (* we can remove the first element, which also returns a new heap
   that does not contain it β€” CCHeap is a functional data structure *)
  IntHeap.take h;;
- : (IntHeap.t * int) option = Some (<abstr>, 2)

# let h', x = IntHeap.take_exn h ;;
val h' : IntHeap.t = <abstr>
val x : int = 2

# IntHeap.to_list h' (* see, 2 is removed *);;
- : int list = [4; 6; 8; 10]

IO helpers

The core library contains a module called CCIO that provides useful functions for reading and writing files. It provides functions that make resource handling easy, following the pattern with_resource : resource -> (access -> 'a) -> 'a where the type access is a temporary handle to the resource (e.g., imagine resource is a file name and access a file descriptor). Calling with_resource r f will access r, give the result to f, compute the result of f and, whether f succeeds or raises an error, it will free the resource.

Consider for instance:

# CCIO.with_out "./foobar"
    (fun out_channel ->
      CCIO.write_lines_l out_channel ["hello"; "world"]);;
- : unit = ()

This just opened the file 'foobar', creating it if it didn't exist, and wrote two lines in it. We did not have to close the file descriptor because with_out took care of it. By the way, the type signatures are:

val with_out :
  ?mode:int -> ?flags:open_flag list ->
  string -> (out_channel -> 'a) -> 'a

val write_lines_l : out_channel -> string list -> unit

So we see the pattern for with_out (which opens a function in write mode and gives its functional argument the corresponding file descriptor).

NOTE: you should never let the resource escape the scope of the with_resource call, because it will not be valid outside. OCaml's type system doesn't make it easy to forbid that so we rely on convention here (it would be possible, but cumbersome, using a record with an explicitly quantified function type).

Now we can read the file again:

# let lines : string list = CCIO.with_in "./foobar" CCIO.read_lines_l ;;
val lines : string list = ["hello"; "world"]

There are some other functions in CCIO that return generators instead of lists. The type of generators in containers is type 'a gen = unit -> 'a option (combinators can be found in the opam library called "gen"). A generator is to be called to obtain successive values, until it returns None (which means it has been exhausted). In particular, python users might recognize the function

# CCIO.File.walk ;;
- : string -> walk_item gen = <fun>;;

where type walk_item = [ ``Dir | ``File ] * string is a path paired with a flag distinguishing files from directories.

To go further: containers-data

There is also a library called containers-data, with lots of more specialized data-structures. The documentation contains the API for all the modules; they also provide interface to iter and, as the rest of containers, minimize dependencies over other modules. To use containers-data you need to link it, either in your build system or by #require containers-data;;

A quick example based on purely functional double-ended queues:

# #require "containers-data";;
# #install_printer CCFQueue.pp  (* better printing of queues! *);;

# let q = CCFQueue.of_list [2;3;4] ;;
val q : int CCFQueue.t = queue {2; 3; 4}

# let q2 = q |> CCFQueue.cons 1 |> CCFQueue.cons 0 ;;
val q2 : int CCFQueue.t = queue {0; 1; 2; 3; 4}

# (* remove first element *)
  CCFQueue.take_front q2;;
- : (int * int CCFQueue.t) option = Some (0, queue {1; 2; 3; 4})

# (* q was not changed *)
  CCFQueue.take_front q;;
- : (int * int CCFQueue.t) option = Some (2, queue {3; 4})

# (* take works on both ends of the queue *)
  CCFQueue.take_back_l 2 q2;;
- : int CCFQueue.t * int list = (queue {0; 1; 2}, [3; 4])

Common Type Definitions

Some structural types are used throughout the library:

  • gen: 'a gen = unit -> 'a option is an iterator type. Many combinators are defined in the opam library gen

  • iter: 'a iter = (unit -> 'a) -> unit is also an iterator type, formerly named sequence. It is easier to define on data structures than gen, but it a bit less powerful. The opam library iter can be used to consume and produce values of this type.

    It was renamed from 'a sequence to 'a iter to distinguish it better from Core.Sequence and the standard seq.

  • error: 'a or_error = ('a, string) result = Error of string | Ok of 'a using the standard result type, supported in CCResult.

  • printer: 'a printer = Format.formatter -> 'a -> unit is a pretty-printer to be used with the standard module Format. In particular, in many cases, "foo: %a" Foo.print foo will type-check.

Extended Documentation

See the extended documentation for more examples.

HOWTO (for contributors)

Make a release

Beforehand, check grep deprecated -r src to see whether some functions can be removed.

  • make all
  • update version in containers.opam
  • make update_next_tag (to update @since comments; be careful not to change symlinks)
  • check status of modules ({b status: foo}) and update if required; removed deprecated functions, etc.
  • update CHANGELOG.md (see its end to find the right git command)
  • commit the changes
  • make test doc
  • export VERSION=<tag here>; git tag -f $VERSION; git push origin :$VERSION; git push origin $VERSION
  • new opam package: opam publish https://github.com/c-cube/ocaml-containers/archive/<tag>.tar.gz
  • re-generate doc: make doc and put it into gh-pages

List Authors

git log --format='%aN' | sort -u

ocaml-containers's People

Contributors

bikallem avatar bluddy avatar bridgethemasterbuilder avatar bronsa avatar c-cube avatar copy avatar darrenldl avatar drup avatar emillon avatar emm avatar fardalem avatar favonia avatar fourchaux avatar gbury avatar glennsl avatar grayswandyr avatar jberdine avatar julow avatar kit-ty-kate avatar kwshi avatar loxs avatar mookid avatar nbraud avatar nilsbecker avatar octachron avatar rand00 avatar rleonid avatar shym avatar struktured avatar vbmithr avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

ocaml-containers's Issues

bind in CCOpt

is there a reason that bind is only present in infix form in CCOpt? i'm asking since i just came across a situation where the normal bind with signature (a -> b t) -> a t -> b t would have been handy because of the argument order.

print function in Hashtbl.Make

the print combinator function contains this line (164):

Format.pp_print_string fmt "@[<hov2>tbl {@,";

which for me seems to result in literal output of the control characters. it should probably be fprintf or similar?

lwt functional streams

module Stream : sig
  type 'a t = [`Nil | `Cons of 'a * 'a t] Lwt.t

  val push : 'a t -> 'a -> unit Lwt.t
  val next : 'a t -> ('a * 'a t) option
  val iter_s : ('a -> unit Lwt.t) -> 'a t -> unit Lwt.t

  (* etc. *)
end

should make it easier to work with streams.

monadic input for CCSexp

experiment with parametrizing the parser of CCSexp with something like:

module type INPUT = sig
  type 'a m  (* IO monad *)
  type t  (* input *)

  val return : 'a -> 'a m
  val (>>=) : 'a m -> ('a -> 'b m) -> 'b m

  val input : t -> Bytes.t -> int -> int -> int m
  (* input into this bytes buffer *)
end

This can be used with Lwt or with a blocking monad (type 'a m = 'a). Also, allows to read quite easily from bigarrays, channels, strings, etc.

merlin can't locate definition or signature of containers functions

if i try MerlinLocate on e.g. Containers.List.random_choose i get 'CCList.random_choose' seems to originate from 'CCList' whose ML file could not be found. it would be great if this could get me to the function definition or signature to find the doc string. as it is i always have to navigate to the containers docs on the internet to have access to documentation. this may also be a merlin shortcoming, i'm not sure!

Prepare for 1.0: big cleanup/simplification

Preparing version 1.0, with some breaking changes. The goal of this release is not to add significant new features, but to improve consistency and focus on the core features and modules (in particular, droping or reducing the scope of some of the experimental modules).

The working branch is prepare-1.0 .

NOTE: please ask if you want something changed/added to the list!

Todo list

  • more consistent labels (in particular, replace ~or_ by ~default)
  • label functions (iter', map', …) for CCList and the others?
  • doc (#85)
  • remove int_, bool_, etc. in CCOrd
  • make CCIO.File.walk work properly with symlinks, even broken
    • deal with errors and files that do not actually exist
    • [ ] add CCIO.File.is_symlink
    • [ ] add CCIO.File.deref : ?recursive:bool -> string -> string
    • [ ] make CCIO.File.walk_item = [Dir | File | Symlink] (breaking compat)
  • much simpler S-expression library using Lexing (see nunchaku)
  • rewrite bitfield (much simpler version, almost functor-free, Bit_set)
  • improve CCFormat (see #82)
    • CCFormat.of_to_string : ('a -> string) -> 'a t
    • CCFormat.const : 'a t -> 'a -> unit t (to hide the type 'a)
    • CCFormat.text to mimick Format.pp_print_text
    • CCFormat.return : (unit,…) format4 -> unit (for strings without arguments)
    • CCFormat.some : 'a t -> 'a option t (prints nothing if None, same as arg if Some x)
    • remove start/stop arguments?
    • make sep a argument-free formatter, default ",@ ", using Format.fprint out "%(%)" sep
      to print it in combinators
      OR use unit t with return: arg-free formatter -> unit t and sp = return ",@ " or sth
  • add CCOrd.Infix
  • remove CCPrint (just use format)
    • use pp as pretty-printer everywhere, and remove Buffer.t printers
  • remove containers.advanced (refer to olinq)
  • remove bigarray library:
    • remove Array1 (point to oml or similar instead)
    • remove CCBigstring (point to bigstring library instead)
  • improve CCUnix
    • adding simple functions such as popen (already with_process_*)
    • functions returning lists of lines?
  • remove threads library and make it into its own repo/package (if anyone uses it β€” need more tests)
  • CCList:
    • flatten CCList.Set
    • flatten CCList.Idx
    • [ ] flatten CCList.Assoc
    • move CCList.Zipper into its own module (in containers.data)
    • what about CCList.Ref? can keep it, probably
  • move CCArray.Sub into its own module (in containers.data), add many tests
  • [ ] move CCString.Sub into its own module (in containers.data)
  • remove containers.string, merging useful functionality into CCString
    • add edit_distance to CCString, from CCLevenshtein
    • [ ] add submodule Edit_distance_automaton (with compiled automaton + index, maybe)
    • just remove CCKMP, make CCString.Find public (provides same functionality)
    • remove App_parse
    • move CCParse into core
    • use parser combinators from oasis-parser for CCParse (string input only!) + update tests
  • use result everwhere, drop the polymorphic variants that remain
  • remove CCError in favor of CCResult
  • use Hashtbl.seeded_hash for implementing better hash combinators in CCHash (from smbc)
  • improve CCGraph (functor designed for local def?)

before pre-release:

  • [ ] remove all @since annotations
  • remove deprecated functions
  • apply ocp-indent

feature request: analog of argsort in numpy

i was looking for a function ('a -> 'a -> int) -> 'a array -> int array that gives the indices that successive array elements would have in a sorted array (sorted by the compare function given first). i.e. the ranking of the elements. something like that is useful for all kinds of rank statistics.

containers v0.16 requires oasis

I installed containers from opam and it picked version 0.16. This version requires oasis to be installed. Oasis requires a lot of dependencies and it's hard to install in windows (MSVC port). My guess is that the static version of the build system (oasis setup) was no created before making the release.

0.7 failed compile in OPAM on OS X

I had containers 0.4.1 installed. It worked great. I did opam update. I did opam upgrade. containers was just plain gone. I did opam install containers. I got a long error.

#=== ERROR while installing containers.0.7 ====================================#
# opam-version 1.2.0
# os           darwin
# command      make build
# path         /Users/mcc/.opam/4.02.1/build/containers.0.7
# compiler     4.02.1
# exit-code    2
# env-file     /Users/mcc/.opam/4.02.1/build/containers.0.7/containers-96695-5f1023.env
# stdout-file  /Users/mcc/.opam/4.02.1/build/containers.0.7/containers-96695-5f1023.out
# stderr-file  /Users/mcc/.opam/4.02.1/build/containers.0.7/containers-96695-5f1023.err
### stdout ###
# ...[truncated]
# /Users/mcc/.opam/4.02.1/bin/ocamlfind ocamlopt -c -g -annot -bin-annot -no-alias-deps -w A -w -4 -w -44 -for-pack Containers_string -I src/string -o src/string/KMP.cmx src/string/KMP.ml
# /Users/mcc/.opam/4.02.1/bin/ocamlfind ocamlopt -c -g -annot -bin-annot -no-alias-deps -w A -w -4 -w -44 -for-pack Containers_string -I src/string -o src/string/levenshtein.cmx src/string/levenshtein.ml
# touch src/string/containers_string.mli  ; if  /Users/mcc/.opam/4.02.1/bin/ocamlfind ocamlopt -pack -g -annot -bin-annot -I src/string src/string/KMP.cmx src/string/levenshtein.cmx -o src/string/containers_string.cmx  ; then  rm -f src/string/containers_string.mli  ; else  rm -f src/string/containers_string.mli  ; exit 1; fi
# /Users/mcc/.opam/4.02.1/bin/ocamlfind ocamlopt -a src/string/containers_string.cmx -o src/string/containers_string.cmxa
# + /Users/mcc/.opam/4.02.1/bin/ocamlfind ocamlopt -a src/string/containers_string.cmx -o src/string/containers_string.cmxa
# /usr/bin/ranlib: object: src/string/containers_string.a(containers_string.o) malformed object (unknown load command 4)
# ar: internal ranlib command failed
# File "_none_", line 1:
# Error: Error while creating the library src/string/containers_string.a
# Command exited with code 2.
### stderr ###
# W: Cannot find source file matching module 'containers_misc' in library containers_misc
# W: Cannot find source file matching module 'containers_string' in library containers_string
# E: Failure("Command ''/Users/mcc/.opam/4.02.1/bin/ocamlbuild' src/core/containers.cma src/core/containers.cmxa src/core/containers.a src/core/containers.cmxs src/io/containers_io.cma src/io/containers_io.cmxa src/io/containers_io.a src/io/containers_io.cmxs src/sexp/containers_sexp.cma src/sexp/containers_sexp.cmxa src/sexp/containers_sexp.a src/sexp/containers_sexp.cmxs src/data/containers_data.c...[truncated]
# make: *** [build] Error 1


=-=- containers.0.7 troubleshooting -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=  🐫 
=> containers is now split into finer-grained sub-libraries, including
       `containers.io`, `containers.iter`, `containers.sexp`, `containers.data`.
       CCGen and CCSequence have been removed, consider using the libraries
       `gen` and `sequence` on opam.
Andis-Macbook:emily-ocaml mcc$ 

I mentioned this on #ocaml freenode and Whitequark mentioned:

 <whitequark> the problem is that os x is a [redacted]. their ar can't create empty archives, they know about it since, like, 2007, and they do not give a [redacted]
[snip]
 <whitequark> mcc: http://caml.inria.fr/mantis/view.php?id=6550#c12345

(Whitequark said a cuss!)

Can't install 0.22

(sequence is installed with 0.9)

> opam install containers
The following actions will be performed:
  βˆ—  install containers 0.22

=-=- Gathering sources =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=  🐫 
[containers] Archive in cache

=-=- Processing actions -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=  🐫 
[ERROR] The compilation of containers failed at "make build".
Processing  1/1: [containers: ocamlfind remove]
#=== ERROR while installing containers.0.22 ===================================#
# opam-version 1.2.2
# os           darwin
# command      make build
# path         /Users/dbuenzli/.opam/4.03.0/build/containers.0.22
# compiler     4.03.0
# exit-code    2
# env-file     /Users/dbuenzli/.opam/4.03.0/build/containers.0.22/containers-92685-d2c37b.env
# stdout-file  /Users/dbuenzli/.opam/4.03.0/build/containers.0.22/containers-92685-d2c37b.out
# stderr-file  /Users/dbuenzli/.opam/4.03.0/build/containers.0.22/containers-92685-d2c37b.err
### stdout ###
# [...]
# /Users/dbuenzli/.opam/4.03.0/bin/ocamlfind ocamldep -package bytes -package sequence -package result -modules src/advanced/CCCat.ml > src/advanced/CCCat.ml.depends
# cppo -D 'OCAML_MAJOR 4' -D 'OCAML_MINOR 3' -o src/advanced/CCMonadIO.ml src/advanced/CCMonadIO.cppo.ml
# /Users/dbuenzli/.opam/4.03.0/bin/ocamlfind ocamldep -package bytes -package sequence -package result -modules src/advanced/CCMonadIO.ml > src/advanced/CCMonadIO.ml.depends
# /Users/dbuenzli/.opam/4.03.0/bin/ocamlfind ocamlc -c -g -annot -bin-annot -safe-string -short-paths -no-alias-deps -w A -I src/core -w -4 -w -44 -package bytes -package sequence -package result -I src/advanced -I src/core -o src/advanced/containers_advanced.cmo src/advanced/containers_advanced.ml
# /Users/dbuenzli/.opam/4.03.0/bin/ocamlfind ocamlc -c -g -annot -bin-annot -safe-string -short-paths -no-alias-deps -w A -I src/core -w -4 -w -44 -package bytes -package sequence -package result -I src/advanced -I src/core -o src/advanced/CCLinq.cmo src/advanced/CCLinq.ml
# + /Users/dbuenzli/.opam/4.03.0/bin/ocamlfind ocamlc -c -g -annot -bin-annot -safe-string -short-paths -no-alias-deps -w A -I src/core -w -4 -w -44 -package bytes -package sequence -package result -I src/advanced -I src/core -o src/advanced/CCLinq.cmo src/advanced/CCLinq.ml
# File "src/advanced/CCLinq.ml", line 215, characters 14-30:
# Error: Unbound value Sequence.flatMap
# Hint: Did you mean flat_map?
# Command exited with code 2.
### stderr ###
# E: Failure("Command ''/Users/dbuenzli/.opam/4.03.0/bin/ocamlbuild' src/core/containers.cma src/core/containers.cmxa src/core/containers.a src/core/containers.cmxs src/io/containers_io.cma src/io/containers_io.cmxa src/io/containers_io.a src/io/containers_io.cmxs src/unix/containers_unix.cma src/unix/containers_unix.cmxa src/unix/containers_unix.a src/unix/containers_unix.cmxs src/sexp/containers_sexp.cma src/sexp/containers_sexp.cmxa src/sexp/containers_sexp.a src/sexp/containers_sexp.cmxs src/data/containers_data.cma src/data/containers_data.cmxa src/data/containers_data.a src/data/containers_data.cmxs src/iter/containers_iter.cma src/iter/containers_iter.cmxa src/iter/containers_iter.a src/iter/containers_iter.cmxs src/string/containers_string.cma src/string/containers_string.cmxa src/string/containers_string.a src/string/containers_string.cmxs src/advanced/containers_advanced.cma src/advanced/containers_advanced.cmxa src/advanced/containers_advanced.a src/advanced/containers_advanced.cmxs src/bigarray/containers_bigarray.cma src/bigarray/containers_bigarray.cmxa src/bigarray/containers_bigarray.a src/bigarray/containers_bigarray.cmxs src/threads/containers_thread.cma src/threads/containers_thread.cmxa src/threads/containers_thread.a src/threads/containers_thread.cmxs src/top/containers_top.cma src/top/containers_top.cmxa src/top/containers_top.a src/top/containers_top.cmxs examples/id_sexp.native -use-ocamlfind -j 1 -tag debug' terminated with error code 10")
# make: *** [build] Error 1



=-=- Error report -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=  🐫 
The following actions failed
  βˆ—  install containers 0.22
No changes have been performed

=-=- containers.0.22 troubleshooting =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=  🐫 
=> Small release of containers, making use of the new releases of
     qtest and qcheck.

Core style prefix/suffix functions

These are best explained through type signatures:

val chop_suffix : t -> suffix:t -> t option

val chop_prefix : t -> prefix:t -> t option

These are very useful and I often myself reaching them for them. Would be great if containers had them as well. Obviously the labels/names will need to be adjusted.

Apologies if containers already has them. I'm still learning the ropes.

introducing fold_until convenience function

Option 1:

let rec fold_until (f: 'b -> 'a -> 'b * bool) (acc:'b) = 
  function | [] -> acc | e::l -> let acc, cont = f acc e in if not cont then acc else 
   fold_until f acc l;;
val fold_until : ('b -> 'a -> 'b * bool) -> 'b -> 'a list -> 'b = <fun>                                                                             

Pros: can accumulate and terminate on last step.
Cons: more complicated return value of the accumulator function

Option 2:

 let rec fold_until (f: 'b -> 'a -> 'b option) (acc:'b) = 
   function | [] -> acc  
   | e::l -> match f acc e with None -> acc | Some acc -> fold_until f acc l;;
val fold_until : ('b -> 'a -> 'b option) -> 'b -> 'a list -> 'b = <fun>                                                                             

Pros: simple accumulator with use of options
Cons: can't accumulate on last step

In either case, I would like to add this function to CCList, CCArray, Gen, and where-ever else it makes sense. So, do you think this function merits an addition to the library? And which signature do you prefer?

Missing infix operators for half-open ranges

The new CCList.Infix.(--) is nice, but it would be even nicer to have an alternative operator more suitable for dealing in algorithms with dynamic input, where half-open ranges are often seen. I suggest using --< which communicates nicely the fact that the right end of the range is open, ie. 1 --< 3 = [1; 2].

The empty range would be produced if the left and right bounds are the same. 1 --< 1 = [].

--< should also not automatically choose to make a descending range, but instead require that the second argument is never less than the first argument. The Invalid_argument in this situations seems appropriate to me, if Containers doesn't make use of something else.

If the user desires to write a descending range, he may choose to use the non-infix functions for that, or possibly List.rev. In practice I find descending ranges be much more rare than ascending ones, and in particular there are basically zero cases where the same piece of code would deal with ranges going either way, depending on arguments. So it's best to signal about those cases, as they are likely indicative of an error.

The --< operator should be provided in all the modules that currently provide --.

extract conv.ml

I'm interested in using conv.ml in one of my project, but I don't want to depend on Unix. By any chance, do you plan to make a stand-alone library for conv ?

improve `CCFormat`

  • make start and stop empty by default in all printers (in 4ff174c)
  • add Dump sub-module with OCaml-like printing (in 0d9d17d)
  • something to change/enable/disable colors dynamically (in 9045fcc)
  • string-producing version of with_color{,f} (in 9045fcc)

Some cmx files are not installed

I'm seeing warning 58 in a project:

File "_none_", line 1:
Warning 58: no cmx file was found in path for module CCString, and its interface was not compiled with -opaque

From a quick look at .opam/4.04.0+flambda/lib/containers/, it seems that the cmx produces by cppo sources are not installed.

CCError generic printer

CCError.pp and CCError.print only accept a printer argument for the 'good type, not for 'bad:

val pp : 'a printer -> ('a, string) t printer
val print : 'a formatter -> ('a, string) t formatter

I'm using non-string types for errors, so a pp method that takes two printers (like CCMap.S.pp) would be useful.

Enable most of the flags in the Makefile

Since the Makefile is for developers β€” while the default _oasis setting is for the user/opam package β€” I think it would be useful that the configure in the Makefile uses the flags --enable-tests, --enable-bench, --enable-misc,...

file naming bug?

i just tried to use CCInt and got this:

Error: Wrong file naming: $HOME/.opam/4.02.3/lib/containers/cCint.cmi
contains the compiled interface for 
CCint when CCInt was expected
Command exited with code 2.

monad-building functor

In containers.advanced, a functor

module MakeMonad(M : sig
  type 'a t
  val return : 'a -> 'a t 
  val (>>=) : 'a t -> ('a -> 'b t) -> 'b t
  val map : [`Redefine | `Use of ('a t -> ('a -> 'b) -> 'b t)]
  (* etc. for other optional values *)
end) : sig
  (* copy monad stuff *)
  (* add applicative stuff *)
  (* add some sequence operators? *)
end

0.6.1 fails to build with OPAMBUILDDOC=1

Solver failed:
  Ocamlbuild knows of no rules that apply to a target named containers_lwt.odocl. This can happen if you ask Ocamlbuild to build a target with the wrong extension (e.g. .opt instead of .native) or if the source files live in directories that have not been specified as include directories.
Backtrace:
  - Failed to build the target containers_lwt.docdir/index.html
      - Building containers_lwt.docdir/index.html:
          - Failed to build all of these:
              - Building containers_lwt.odocl
              - Building containers_lwt.odocl
Makefile:10: recipe for target 'doc' failed

CCChar.{of,to}_int

The following functions would be useful:

  • CCChar.of_int : int -> char option
  • CCChar.of_int_exn : int -> char
  • CCChar.to_int : char -> int

Missing functions

I've developed a small application using containers, and found some functions that I missed:

  • CCFloat.round : float -> float – a version that returns an int would also be useful
  • CCVector.append_gen : 'a CCVector.vector -> 'a gen -> unit
  • CCList.{first, last} : 'a list -> 'a option
  • CCHashtbl.{to_gen, values_gen, keys_gen} – I guess these can't be implemented without using an intermediate list. They would still be nice to have so that I don't need to update my code when the standard library provides a more efficient way to implement them

Provide a module CCPervasives

This module would shadow the standard List, etc modules.

Would be great to also have a findlib library that adds "-open CCPervasives" to ocamlc invocations.

Clarify the use of sub libraries in the tutorial

The tutorial makes it clear how to get up and running with the core library by providing sample code. However, the "To go further" section is not detailed enough for a beginner how to get code compiling and linking using containers.data.

containers.bigarray

A sub-library that provides CCBigstring or something similar, with memory-mapping, iterators (on slices), etc.

Char.print ?

i stumbled upon the fact that there is no Char module and therefore also no Char.print (analogous to Int.print etc) might this be a worthwhile addition?

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    πŸ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. πŸ“ŠπŸ“ˆπŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❀️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.