/usr/lib/ocaml/ocsigenserver/ocsigen_cache.mli is in libocsigenserver-ocaml-dev 2.2.0-3.
This file is owned by root:root, with mode 0o644.
The actual contents of the file can be viewed below.
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 | (* Ocsigen
* Copyright (C) 2009
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU Lesser General Public License as published by
* the Free Software Foundation, with linking exception;
* either version 2.1 of the License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
(**
Cache.
Association tables (from any kind of database)
that keep the most recently used values in memory.
It is also possible to set a maximum lifetime for data in the cache.
It is based on a structure of doubly linked lists with maximum size,
that keeps only the mostly recently used values first, if you call the [up]
function each time you use a value.
(Insertion, remove and "up" in time 1).
This structure is exported, so that it can be used in other cases.
Not (preemptive) thread safe.
@author Vincent Balat
@author Raphaƫl Proust (adding timers)
*)
module Make :
functor (A : sig type key type value end) ->
sig
(** [new cache finder ?timer size] creates a cache object where [finder]
is the function responsible for retrieving non-cached data, [timer]
(if any) is the life span of cached values (in seconds) (values in the
cache are removed after their time is up) and [size] is the upper
bound to the number of simultaneoulsy cached elements.
Whenever a value is found (using [find] method), it's lifespan is set
to [timer] (or not if the cache is not time bounded). If the value was
already cached, it's lifespan is reset to [timer].
Using [timer] allow one to create a cache
bounded both in space and time. It is to be noted that real lifespan
of values is always slightly greater than [timer]. *)
class cache : (A.key -> A.value Lwt.t) -> ?timer:float -> int ->
object
(** Find the cached value associated to the key, or binds this
value in the cache using the function [finder] passed as argument
to [create], and returns this value *)
method find : A.key -> A.value Lwt.t
(** Find the cached value associated to the key. Raises [Not_found]
if the key is not present in the cache *)
method find_in_cache : A.key -> A.value
method remove : A.key -> unit
method add : A.key -> A.value -> unit
method clear : unit -> unit
method size : int
end
end
(** Clear the contents of all the existing caches *)
val clear_all_caches : unit -> unit
(** Doubly-linked lists with maximum number of entries and limited lifespan for
entries. *)
module Dlist : sig
type 'a t
type 'a node
val create : ?timer:float -> int -> 'a t
(** Adds an element to the list,
and possibly returns the element that has been removed if the maximum
size was exceeded. *)
val add : 'a -> 'a t -> 'a option
(** Removes an element from its list.
If it is not in a list, it does nothing.
If it is in a list, it calls the finaliser, then removes the element.
If the finaliser fails with an exception,
the element is removed and the exception is raised again.
*)
val remove : 'a node -> unit
(** Removes the element from its list without finalising,
then adds it as newest. *)
val up : 'a node -> unit
val newest : 'a t -> 'a node option
val oldest : 'a t -> 'a node option
val size : 'a t -> int
val maxsize : 'a t -> int
val value : 'a node -> 'a
(** returns the timer of the Dlist *)
val get_timer : 'a t -> float option
(** The list to which the node belongs *)
val list_of : 'a node -> 'a t option
(** remove the n oldest values (or less if the list is not long enough) ;
returns the list of removed values *)
val remove_n_oldest : 'a t -> int -> 'a list
(** fold over the elements from the cache starting from the newest
to the oldest *)
val fold : ('b -> 'a -> 'b) -> 'b -> 'a t -> 'b
(** fold over the elements from the cache starting from the oldest
to the newest *)
val fold_back : ('b -> 'a -> 'b) -> 'b -> 'a t -> 'b
(** lwt version of fold *)
val lwt_fold : ('b -> 'a -> 'b Lwt.t) -> 'b -> 'a t -> 'b Lwt.t
(** lwt version of fold_back *)
val lwt_fold_back : ('b -> 'a -> 'b Lwt.t) -> 'b -> 'a t -> 'b Lwt.t
(** Move a node from one dlist to another one, without finalizing.
If one value is removed from the destination list (because its
maximum size is reached), it is returned (after finalisation). *)
val move : 'a node -> 'a t -> 'a option
(** change the maximum size ;
returns the list of removed values, if any.
*)
val set_maxsize : 'a t -> int -> 'a list
(** set a function to be called automatically on a piece of data
just before it disappears from the list
(either by explicit removal or because the maximum size is exceeded) *)
val set_finaliser_before : ('a node -> unit) -> 'a t -> unit
val get_finaliser_before : 'a t -> ('a node -> unit)
(** set a function to be called automatically on a piece of data
just after it disappears from the list
(either by explicit removal or because the maximum size is exceeded) *)
val set_finaliser_after : ('a node -> unit) -> 'a t -> unit
val get_finaliser_after : 'a t -> ('a node -> unit)
end
|