~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_db_util.h

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
79
79
    DbTerm* dbterm;
80
80
    void** bp;         /* {Hash|Tree}DbTerm** */
81
81
    Uint new_size;
82
 
    int mustFinalize;  /* Need to call db_finalize_update_element? */
 
82
    int mustResize;
 
83
    void* lck;
83
84
} DbUpdateHandle;
84
85
 
85
86
 
100
101
                   DbTable* tb, /* [in out] */
101
102
                   Eterm key, 
102
103
                   Eterm* ret);
103
 
    int (*db_put)(Process* p, 
104
 
                  DbTable* tb, /* [in out] */ 
105
 
                  Eterm obj, 
106
 
                  Eterm* ret);
 
104
    int (*db_put)(DbTable* tb, /* [in out] */ 
 
105
                  Eterm obj,
 
106
                  int key_clash_fail); /* DB_ERROR_BADKEY if key exists */ 
107
107
    int (*db_get)(Process* p, 
108
108
                  DbTable* tb, /* [in out] */ 
109
109
                  Eterm key, 
113
113
                          Eterm key, 
114
114
                          int index, 
115
115
                          Eterm* ret);
116
 
    int (*db_member)(Process* p, 
117
 
                     DbTable* tb, /* [in out] */ 
 
116
    int (*db_member)(DbTable* tb, /* [in out] */ 
118
117
                     Eterm key, 
119
118
                     Eterm* ret);
120
 
    int (*db_erase)(Process* p,
121
 
                    DbTable* tb,  /* [in out] */ 
 
119
    int (*db_erase)(DbTable* tb,  /* [in out] */ 
122
120
                    Eterm key, 
123
121
                    Eterm* ret);
124
 
    int (*db_erase_object)(Process* p,
125
 
                           DbTable* tb, /* [in out] */ 
 
122
    int (*db_erase_object)(DbTable* tb, /* [in out] */ 
126
123
                           Eterm obj,
127
124
                           Eterm* ret);
128
125
    int (*db_slot)(Process* p, 
133
130
                           DbTable* tb, /* [in out] */ 
134
131
                           Eterm pattern,
135
132
                           Sint chunk_size,
136
 
                           int reverse, 
 
133
                           int reverse,
137
134
                           Eterm* ret);
138
135
    int (*db_select)(Process* p, 
139
136
                     DbTable* tb, /* [in out] */ 
140
137
                     Eterm pattern,
141
 
                     int reverse, 
 
138
                     int reverse,
142
139
                     Eterm* ret);
143
140
    int (*db_select_delete)(Process* p, 
144
141
                            DbTable* tb, /* [in out] */ 
165
162
                                 DbTable* db /* [in out] */ );
166
163
 
167
164
    int (*db_free_table)(DbTable* db /* [in out] */ );
168
 
    int (*db_free_table_continue)(DbTable* db, /* [in out] */  
169
 
                                  int first);
 
165
    int (*db_free_table_continue)(DbTable* db); /* [in out] */  
170
166
    
171
167
    void (*db_print)(int to, 
172
168
                     void* to_arg, 
178
174
                               void *arg);
179
175
    void (*db_check_table)(DbTable* tb);
180
176
 
181
 
    /* Allocate and replace a dbterm with a new size.
182
 
     * The new DbTerm must be initialized by caller (from the old).
183
 
    */
184
 
    DbTerm* (*db_alloc_newsize)(DbTable* tb,
185
 
                                void** bp,  /* XxxDbTerm** */
186
 
                                Uint new_tpl_sz);
187
 
 
188
 
    /* Free a dbterm not in table.
189
 
    */
190
 
    void (*db_free_dbterm)(DbTable* tb, DbTerm* bp);
191
 
 
192
 
    /* Lookup a dbterm by key. Return false if not found.
 
177
    /* Lookup a dbterm for updating. Return false if not found.
193
178
    */
194
179
    int (*db_lookup_dbterm)(DbTable*, Eterm key, 
195
180
                            DbUpdateHandle* handle); /* [out] */
196
181
 
 
182
    /* Must be called for each db_lookup_dbterm that returned true,
 
183
    ** even if dbterm was not updated.
 
184
    */
 
185
    void (*db_finalize_dbterm)(DbUpdateHandle* handle);
 
186
 
197
187
} DbTableMethod;
198
188
 
199
189
/*
212
202
 
213
203
 
214
204
typedef struct db_table_common {
215
 
    erts_refc_t ref;    /* ref count ro prevent table deletion */
 
205
    erts_refc_t ref;
 
206
    erts_refc_t fixref;       /* fixation counter */
216
207
#ifdef ERTS_SMP
217
208
    erts_smp_rwmtx_t rwlock;  /* rw lock on table */
218
 
    Uint32 type;              /* hash or tree; *read only* after creation */
 
209
    erts_smp_mtx_t fixlock;   /* Protects fixations,megasec,sec,microsec */
 
210
    int is_thread_safe;       /* No fine locking inside table needed */
 
211
    Uint32 type;              /* hash or tree, private or not; *read only* after creation */
219
212
#endif
220
213
    Eterm owner;              /* Pid of the creator */
221
 
    Eterm the_name;           /* an atom   */
 
214
    Eterm heir;               /* Pid of the heir */
 
215
    Eterm heir_data;          /* To send in ETS-TRANSFER (is_immed or (DbTerm*) */
 
216
    SysTimeval heir_started;  /* To further identify the heir */
 
217
    Eterm the_name;           /* an atom */
222
218
    Eterm id;                 /* atom | integer */
223
219
    DbTableMethod* meth;      /* table methods */
224
 
    Uint nitems;               /* Total number of items */
 
220
    erts_smp_atomic_t nitems; /* Total number of items in table */
225
221
    erts_smp_atomic_t memory_size;/* Total memory size. NOTE: in bytes! */
226
222
    Uint megasec,sec,microsec; /* Last fixation time */
227
 
    DbFixation *fixations;   /* List of processes who have fixed 
228
 
                                 the table */
229
 
 
 
223
    DbFixation* fixations;    /* List of processes who have done safe_fixtable,
 
224
                                 "local" fixations not included. */ 
230
225
    /* All 32-bit fields */
231
226
    Uint32 status;            /* bit masks defined  below */
232
227
    int slot;                 /* slot index in meta_main_tab */
233
228
    int keypos;               /* defaults to 1 */
234
 
    int kept_items;           /* Number of kept elements due to fixation */
235
229
} DbTableCommon;
236
230
 
237
231
/* These are status bit patterns */
241
235
#define DB_PUBLIC        (1 << 3)
242
236
#define DB_BAG           (1 << 4)
243
237
#define DB_SET           (1 << 5)
244
 
#define DB_LHASH         (1 << 6)  /* not really used!!! */
245
 
#define DB_FIXED         (1 << 7)
 
238
/*#define DB_LHASH         (1 << 6)*/
 
239
#define DB_FINE_LOCKED   (1 << 7)  /* fine grained locking enabled */
246
240
#define DB_DUPLICATE_BAG (1 << 8)
247
241
#define DB_ORDERED_SET   (1 << 9)
248
242
#define DB_DELETE        (1 << 10) /* table is being deleted */
249
243
 
250
 
#define ERTS_ETS_TABLE_TYPES (DB_BAG|DB_SET|DB_DUPLICATE_BAG|DB_ORDERED_SET)
 
244
#define ERTS_ETS_TABLE_TYPES (DB_BAG|DB_SET|DB_DUPLICATE_BAG|DB_ORDERED_SET|DB_PRIVATE|DB_FINE_LOCKED)
251
245
 
252
246
#define IS_HASH_TABLE(Status) (!!((Status) & \
253
247
                                  (DB_BAG | DB_SET | DB_DUPLICATE_BAG)))
254
248
#define IS_TREE_TABLE(Status) (!!((Status) & \
255
249
                                  DB_ORDERED_SET))
256
 
     /*TT*/
 
250
#define NFIXED(T) (erts_refc_read(&(T)->common.fixref,0))
 
251
#define IS_FIXED(T) (NFIXED(T) != 0) 
257
252
 
258
253
Eterm erts_ets_copy_object(Eterm, Process*);
259
254
 
269
264
/* tb is an DbTableCommon and obj is an Eterm (tagged) */
270
265
#define TERM_GETKEY(tb, obj) db_getkey((tb)->common.keypos, (obj)) 
271
266
 
272
 
#define ONLY_WRITER(P,T) (((T)->common.status & DB_PRIVATE) || \
273
 
(((T)->common.status & DB_PROTECTED) && (T)->common.owner == (P)->id))
 
267
#define ONLY_WRITER(P,T) (((T)->common.status & (DB_PRIVATE|DB_PROTECTED)) \
 
268
                          && (T)->common.owner == (P)->id)
274
269
 
275
270
#define ONLY_READER(P,T) (((T)->common.status & DB_PRIVATE) && \
276
271
(T)->common.owner == (P)->id)
277
272
 
278
 
#define SOLE_LOCKER(P,Fixations) ((Fixations) != NULL && \
279
 
(Fixations)->next == NULL && (Fixations)->pid == (P)->id && \
280
 
(Fixations)->counter == 1)
281
 
 
282
273
/* Function prototypes */
283
274
Eterm db_get_trace_control_word_0(Process *p);
284
275
Eterm db_set_trace_control_word_1(Process *p, Eterm val);