update headers; reindent

This commit is contained in:
Simon Cruanes 2017-07-04 13:13:07 +02:00
parent 296cdc8748
commit aab19f6a50
16 changed files with 98 additions and 142 deletions

View file

@ -77,7 +77,7 @@ let text out (s:string): unit =
(*$= & ~printer:(fun s->CCFormat.sprintf "%S" s)
"a\nb\nc" (sprintf_no_color "@[<v>%a@]%!" text "a b c")
"a b\nc" (sprintf_no_color "@[<h>%a@]%!" text "a b\nc")
*)
*)
let list ?(sep=return ",@ ") pp fmt l =
let rec pp_list l = match l with

View file

@ -366,7 +366,7 @@ let combine l1 l2 =
if List.length l1=List.length l2 \
then CCList.combine l1 l2 = List.combine l1 l2 \
else Q.assume_fail() )
*)
*)
let combine_gen l1 l2 =
let l1 = ref l1 in
@ -385,7 +385,7 @@ let combine_gen l1 l2 =
let res1 = combine (take n l1) (take n l2) in \
let res2 = combine_gen l1 l2 |> of_gen in \
res1 = res2)
*)
*)
let split l =
let rec direct i l = match l with

View file

@ -129,7 +129,7 @@ let fold_ok f acc r = match r with
(*$=
42 (fold_ok (+) 2 (Ok 40))
40 (fold_ok (+) 40 (Error "foo"))
*)
*)
let is_ok = function
| Ok _ -> true

View file

@ -375,7 +375,7 @@ val rtrim : t -> t
Q.(printable_string) (fun s -> \
let s' = rtrim s in \
if s'="" then Q.assume_fail() else s'.[String.length s'-1] <> ' ')
*)
*)
(** {2 Operations on 2 strings} *)

View file

@ -269,7 +269,7 @@ let iter bv f =
let bv = create ~size:n true in \
let l = iter bv |> Sequence.zip |> Sequence.to_list in \
List.length l = n && List.for_all (fun (_,b) -> b) l)
*)
*)
let iter_true bv f =
iter bv (fun i b -> if b then f i else ())

View file

@ -86,7 +86,7 @@ val first : t -> int option
changed type at 1.2 *)
val first_exn : t -> int
(** First set bit, or
(** First set bit, or
@raise Not_found if all bits are 0
@since 1.2 *)

View file

@ -1,27 +1,5 @@
(*
Copyright (c) 2013, Simon Cruanes
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:
Redistributions of source code must retain the above copyright notice, this
list of conditions and the following disclaimer. Redistributions in binary
form must reproduce the above copyright notice, this list of conditions and the
following disclaimer in the documentation and/or other materials provided with
the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*)
(* This file is free software, part of containers. See file "license" for more details. *)
(** {1 Caches} *)

View file

@ -1,27 +1,5 @@
(*
Copyright (c) 2013, Simon Cruanes
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:
Redistributions of source code must retain the above copyright notice, this
list of conditions and the following disclaimer. Redistributions in binary
form must reproduce the above copyright notice, this list of conditions and the
following disclaimer in the documentation and/or other materials provided with
the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*)
(* This file is free software, part of containers. See file "license" for more details. *)
(** {1 Caches}

View file

@ -544,7 +544,7 @@ let print pp_x out m =
(* Some thorough tests from Jan Midtgaar
https://github.com/jmid/qc-ptrees
*)
*)
(*$inject
let test_count = 2_500
@ -684,14 +684,14 @@ let print pp_x out m =
(fun (t,k,v) ->
let s = interpret t in
abstract (add k v s) = add_m k v (abstract s))
*)
*)
(*$QR & ~count:test_count
(pair arb_tree arb_int)
(fun (t,n) ->
let s = interpret t in
abstract (remove n s) = remove_m n (abstract s))
*)
*)
(*$QR & ~count:test_count
(pair arb_tree arb_tree)
@ -699,7 +699,7 @@ let print pp_x out m =
let s = interpret t in
let s' = interpret t' in
abstract (union merge_f s s') = union_m (abstract s) (abstract s'))
*)
*)
(*$QR & ~count:test_count
Q.(pair arb_tree arb_tree)

View file

@ -201,7 +201,7 @@ end
let g_char = map Char.chr (Char.code 'A' -- Char.code 'z')
let g_str = string_size ~gen:g_char (0--10)
let a_str = {Q.string with Q.gen=g_str}
*)
*)
module MakeFromArray(A:Array.S) : S with module Array = A = struct
module Array = A
@ -638,9 +638,9 @@ module Make(Elt:sig
*)
(*$inject
module BS = CCRingBuffer.Byte
module BS = CCRingBuffer.Byte
type op =
type op =
| Push_back of char
| Take_front
| Take_back
@ -652,7 +652,7 @@ type op =
| Blit of string * int * int
| Z_if_full
let str_of_op = function
let str_of_op = function
| Push_back c -> Printf.sprintf "push_back(%C)" c
| Take_front -> Printf.sprintf "take_front"
| Take_back -> Printf.sprintf "take_back"
@ -664,15 +664,15 @@ let str_of_op = function
| Blit (s,i,len) -> Printf.sprintf "blit(%S,%d,%d)" s i len
| Z_if_full -> "zero_if_full"
let push_back c = Push_back c
let skip n = assert (n>=0); Skip n
let blit s i len =
let push_back c = Push_back c
let skip n = assert (n>=0); Skip n
let blit s i len =
if i<0 || len<0 || i+len > String.length s then (
failwith ("wrong blit: " ^ str_of_op (Blit (s,i,len)));
);
Blit (s,i,len)
let shrink_op =
let shrink_op =
let open Q.Iter in
function
| Push_back c -> Q.Shrink.char c >|= push_back
@ -695,14 +695,14 @@ let shrink_op =
in
append s_i (append s_len s_s)
let rec len_op size acc = function
let rec len_op size acc = function
| Push_back _ -> min size (acc + 1)
| Take_front | Take_back | Junk_front | Junk_back -> max (acc-1) 0
| Skip n -> if acc >= n then acc-n else acc
| Z_if_full | Peek_front | Peek_back -> acc
| Blit (_,_,len) -> min size (acc + len)
let apply_op b = function
let apply_op b = function
| Push_back c -> BS.push_back b c; None
| Take_front -> BS.take_front b
| Take_back -> BS.take_back b
@ -716,7 +716,7 @@ let apply_op b = function
BS.blit_from b (Bytes.unsafe_of_string s) i len; None
| Z_if_full -> if BS.is_full b then Some '0' else None
let gen_op =
let gen_op =
let open Q.Gen in
let g_blit =
string_size ~gen:g_char (5--20) >>= fun s ->
@ -738,15 +738,15 @@ let gen_op =
1, return Z_if_full;
]
let arb_op =
let arb_op =
Q.make
~shrink:shrink_op
~print:str_of_op
gen_op
let arb_ops = Q.list arb_op
let arb_ops = Q.list arb_op
module L_impl = struct
module L_impl = struct
type t = {
size: int;
mutable l: char list;
@ -796,7 +796,7 @@ module L_impl = struct
| Z_if_full -> if b.size = List.length b.l then Some '0' else None
let to_list b = b.l
end
end
*)

View file

@ -53,7 +53,7 @@ let pop q =
Q.(list small_int) (fun l -> \
let q = of_list l in \
equal CCInt.equal (Gen.unfold pop q |> of_gen) q)
*)
*)
let junk q =
try
@ -180,7 +180,7 @@ let append q1 q2 =
equal CCInt.equal \
(append (of_list l1)(of_list l2)) \
(of_list (List.append l1 l2)))
*)
*)
module Infix = struct
let (>|=) q f = map f q

View file

@ -17,7 +17,7 @@ let to_rev_list (l,r) = List.rev_append r l
(*$inject
let zip_gen = Q.(pair (small_list int)(small_list int))
*)
*)
(*$Q
zip_gen (fun z -> \