package carton-git

  1. Overview
  2. Docs
Legend:
Page
Library
Module
Module type
Parameter
Class
Class type
Source

Source file carton_git.ml

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
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
module type STORE = sig
  type 'a rd = < rd : unit ; .. > as 'a
  type 'a wr = < wr : unit ; .. > as 'a

  type 'a mode =
    | Rd : < rd : unit > mode
    | Wr : < wr : unit > mode
    | RdWr : < rd : unit ; wr : unit > mode

  type t
  type uid
  type 'a fd
  type error
  type +'a fiber

  val pp_error : error Fmt.t

  val create :
    ?trunc:bool -> mode:'a mode -> t -> uid -> ('a fd, error) result fiber

  val map : t -> 'm rd fd -> pos:int64 -> int -> Bigstringaf.t
  val close : t -> 'm fd -> (unit, error) result fiber
  val list : t -> uid list fiber
  val length : 'm fd -> int64 fiber
end

let src = Logs.Src.create "carton-git" ~doc:"logs git's carton event"

module Log = (val Logs.src_log src : Logs.LOG)

module type IO = sig
  type +'a t

  val catch : (unit -> 'a t) -> (exn -> 'a t) -> 'a t
  val bind : 'a t -> ('a -> 'b t) -> 'b t
  val return : 'a -> 'a t
end

type ('fd, 'uid) pack = {
  pack : ('fd * int64, 'uid) Carton.Dec.t;
  index : 'uid Carton.Dec.Idx.idx;
  z : Bigstringaf.t;
  w : De.window;
}

type ('path, 'fd, 'uid) t = { tbl : ('path, ('fd, 'uid) pack) Hashtbl.t }
[@@unbox]

type 'fd buffers = {
  z : Bigstringaf.t;
  allocate : int -> De.window;
  w : 'fd Carton.Dec.W.t;
}

module Make
    (Scheduler : Carton.SCHEDULER)
    (IO : IO with type +'a t = 'a Scheduler.s)
    (Store : STORE with type +'a fiber = 'a Scheduler.s)
    (Uid : Carton.UID) =
struct
  let ( >>= ) = IO.bind
  let return = IO.return
  let ( >>? ) x f = x >>= function Ok x -> f x | Error _ as err -> return err
  let ( >>| ) x f = x >>= fun x -> return (f x)

  let idx (root : Store.t) acc path =
    Store.create ~trunc:false ~mode:Store.Rd root path >>? fun fd ->
    Store.length fd >>= fun length ->
    let payload = Store.map root fd ~pos:0L (Int64.to_int length) in
    Store.close root fd >>? fun () ->
    let idx =
      Carton.Dec.Idx.make payload ~uid_ln:Uid.length ~uid_rw:Uid.to_raw_string
        ~uid_wr:Uid.of_raw_string
    in
    return (Ok (idx :: acc))

  let pack (root : Store.t) acc (index, pack) =
    Store.create ~trunc:false ~mode:Store.Rd root pack >>? fun fd ->
    Store.length fd >>= fun length ->
    let z = Bigstringaf.create De.io_buffer_size in
    let w = De.make_window ~bits:15 in
    let pack =
      Carton.Dec.make (fd, length) ~z
        ~allocate:(fun _ -> w)
        ~uid_ln:Uid.length ~uid_rw:Uid.of_raw_string
        (fun uid ->
          match Carton.Dec.Idx.find index uid with
          | Some (_, offset) -> offset
          | None -> Fmt.invalid_arg "Object %a does not exist" Uid.pp uid)
    in
    return (Ok ({ pack; index; z; w } :: acc))

  let fold_left_r ?(err = fun _ -> return ()) f a l =
    let rec go a = function
      | [] -> return a
      | x :: r -> (
          f a x >>= function
          | Ok a -> go a r
          | Error x -> err x >>= fun () -> go a r)
    in
    go a l

  let ( <.> ) f g x = f (g x)

  (* XXX(dinosaure): about design, I think that a listing of PACK files should be done
     outside the scope of this module (or more generally outside the scope of the Git's core). *)
  let make :
      Store.t ->
      uid_of_major_uid:(Store.uid -> 'uid) ->
      idx_major_uid_of_uid:(Store.t -> 'uid -> Store.uid) ->
      (Store.uid, < rd : unit > Store.fd, Uid.t) t IO.t =
   fun root ~uid_of_major_uid ~idx_major_uid_of_uid ->
    Store.list root >>= fun pcks ->
    let idxs = List.map (idx_major_uid_of_uid root <.> uid_of_major_uid) pcks in
    fold_left_r (idx root) [] idxs >>| List.rev >>= fun idxs ->
    fold_left_r (pack root) [] (List.combine idxs pcks) >>| List.rev
    >>= fun vs ->
    let tbl = Hashtbl.create 10 in
    List.iter (fun (k, v) -> Hashtbl.add tbl k v) (List.combine pcks vs);
    return { tbl }

  let map root (fd, top) ~pos len =
    let max = Int64.sub top pos in
    let len = min (Int64.of_int len) max in
    let len = Int64.to_int len in
    Store.map root fd ~pos len

  let add :
      Store.t ->
      (Store.uid, < rd : unit > Store.fd, Uid.t) t ->
      idx:Store.uid ->
      Store.uid ->
      (< rd : unit > Store.fd * int64, Store.error) result IO.t =
   fun root p ~idx:idx_uid pck ->
    idx root [] idx_uid >>? fun idxs ->
    let[@warning "-8"] [ idx ] = idxs in
    pack root [] (idx, pck) >>? fun vs ->
    List.iter (fun (k, v) -> Hashtbl.add p.tbl k v) (List.combine [ pck ] vs);
    let[@warning "-8"] [ v ] = vs in
    return (Ok (Carton.Dec.fd v.pack))

  let with_resources root pack uid buffers =
    IO.catch
      (fun () ->
        let map fd ~pos len = map root fd ~pos len in
        let pack = Carton.Dec.with_z buffers.z pack in
        let pack = Carton.Dec.with_allocate ~allocate:buffers.allocate pack in
        let pack = Carton.Dec.with_w buffers.w pack in
        let weight =
          Carton.Dec.weight_of_uid ~map pack ~weight:Carton.Dec.null uid
        in
        let raw = Carton.Dec.make_raw ~weight in
        let v = Carton.Dec.of_uid ~map pack raw uid in
        return v)
      (fun exn ->
        Printexc.print_backtrace stderr;
        raise exn)

  let get :
      Store.t ->
      resources:('fd -> ('fd buffers -> 'a IO.t) -> 'a IO.t) ->
      (Store.uid, < rd : unit > Store.fd, Uid.t) t ->
      Uid.t ->
      (Carton.Dec.v, [> `Msg of string ]) result IO.t =
   fun root ~resources p uid ->
    let res = ref None in
    Hashtbl.iter
      (fun _ ({ index; _ } as x) ->
        let v = Carton.Dec.Idx.exists index uid in
        Log.debug (fun m -> m "%a exists into the *.idx file? %b" Uid.pp uid v);
        if v then res := Some x)
      p.tbl;
    match !res with
    | Some { pack; _ } ->
        Log.debug (fun m -> m "Start to load the object from the PACK file.");
        resources (Carton.Dec.fd pack) (with_resources root pack uid)
        >>= fun v ->
        Log.debug (fun m -> m "Object %a loaded." Uid.pp uid);
        return (Ok v)
    | None -> return (Error (`Not_found uid))

  let list : Store.t -> (Store.uid, 'm Store.fd, Uid.t) t -> Uid.t list =
   fun _ p ->
    let fold _ { index; _ } a =
      let res = ref [] in
      Carton.Dec.Idx.iter
        ~f:(fun ~uid ~offset:_ ~crc:_ -> res := uid :: !res)
        index;
      List.rev_append !res a
    in
    Hashtbl.fold fold p.tbl []

  let exists : Store.t -> (Store.uid, 'm Store.fd, Uid.t) t -> Uid.t -> bool =
   fun _ p uid ->
    let res = ref false in
    Hashtbl.iter
      (fun _ { index; _ } ->
        if Carton.Dec.Idx.exists index uid then res := true)
      p.tbl;
    !res

  let fds : (Store.uid, 'm Store.fd, Uid.t) t -> ('m Store.fd * int64) list =
   fun { tbl } ->
    let fold _ { pack; _ } a = Carton.Dec.fd pack :: a in
    Hashtbl.fold fold tbl []
end
OCaml

Innovation. Community. Security.