Skip to content

Commit

Permalink
refactor: re-implement bit bector properly
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Mar 30, 2024
1 parent fe0a0a0 commit 88f8bf7
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 12 deletions.
4 changes: 1 addition & 3 deletions lib/automata.ml
Original file line number Diff line number Diff line change
Expand Up @@ -330,8 +330,6 @@ let create_working_area () = ref (Bit_vector.singleton false)

let index_count w = Bit_vector.length !w

let reset_table a = Bit_vector.set_all a false

let rec mark_used_indices tbl =
List.iter (function
| E.TSeq (l, _, _) -> mark_used_indices tbl l
Expand All @@ -345,7 +343,7 @@ let rec find_free tbl idx len =

let free_index tbl_ref l =
let tbl = !tbl_ref in
reset_table tbl;
Bit_vector.reset_zero tbl;
mark_used_indices tbl l;
let len = Bit_vector.length tbl in
let idx = find_free tbl 0 len in
Expand Down
49 changes: 41 additions & 8 deletions lib/bit_vector.ml
Original file line number Diff line number Diff line change
@@ -1,14 +1,47 @@
type t = bool array
type t =
{ len : int
; bits : Bytes.t
}
let byte s i = Char.code (Bytes.unsafe_get s i)

let singleton v = [| v |]
let low_mask = Array.init 9 (fun i -> (1 lsl i) - 1)
let set_byte s i x = Bytes.unsafe_set s i (Char.chr x)

let length t = Array.length t
let create len b =
let initv = if b then 255 else 0 in
let q = len lsr 3 in
let r = len land 7 in
if r = 0 then
{ len ; bits = Bytes.make q (Char.chr initv) }
else begin
let s = Bytes.make (q + 1) (Char.chr initv) in
set_byte s q (initv land low_mask.(r));
{ len ; bits = s }
end

let set t i a = t.(i) <- a
let singleton v = create 1 v

let get t i = t.(i)
let length t = t.len

let create len v = Array.make len v
let unsafe_set v n b =
let i = n lsr 3 in
let c = byte v.bits i in
let mask = 1 lsl (n land 7) in
set_byte v.bits i (if b then c lor mask else c land (lnot mask))

let set_all t v =
Array.fill t 0 (length t) v
let set v n b =
if n < 0 || n >= v.len then invalid_arg "Bitv.set";
unsafe_set v n b

let unsafe_get v n =
let i = n lsr 3 in
(byte v.bits i) land (1 lsl (n land 7)) > 0

let get v n =
if n < 0 || n >= v.len then invalid_arg "Bitv.get";
unsafe_get v n

let reset_zero t =
for i = 0 to Bytes.length t.bits - 1 do
Bytes.set t.bits i '\000'
done
2 changes: 1 addition & 1 deletion lib/bit_vector.mli
Original file line number Diff line number Diff line change
Expand Up @@ -10,4 +10,4 @@ val create : int -> bool -> t

val get : t -> int -> bool

val set_all : t -> bool -> unit
val reset_zero : t -> unit

0 comments on commit 88f8bf7

Please sign in to comment.