~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to erts/include/internal/tile/atomic.h

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
24
24
#ifndef ETHREAD_TILE_ATOMIC_H
25
25
#define ETHREAD_TILE_ATOMIC_H
26
26
 
 
27
#define ETHR_HAVE_NATIVE_ATOMIC32 1
 
28
 
27
29
#include <atomic.h>
28
30
 
29
31
/* An atomic is an aligned int accessed via locked operations.
30
32
 */
31
33
typedef struct {
32
 
    volatile long counter;
33
 
} ethr_native_atomic_t;
34
 
 
35
 
#ifdef ETHR_TRY_INLINE_FUNCS
 
34
    volatile ethr_sint32_t counter;
 
35
} ethr_native_atomic32_t;
 
36
 
 
37
#define ETHR_MEMORY_BARRIER __insn_mf()
 
38
 
 
39
#if defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHR_ATOMIC_IMPL__)
 
40
 
 
41
static ETHR_INLINE ethr_sint32_t *
 
42
ethr_native_atomic32_addr(ethr_native_atomic32_t *var)
 
43
{
 
44
    return (ethr_sint32_t *) &var->counter;
 
45
}
36
46
 
37
47
static ETHR_INLINE void
38
 
ethr_native_atomic_init(ethr_native_atomic_t *var, long i)
 
48
ethr_native_atomic32_init(ethr_native_atomic32_t *var, ethr_sint32_t i)
39
49
{
40
50
    var->counter = i;
41
51
}
42
52
 
43
53
static ETHR_INLINE void
44
 
ethr_native_atomic_set(ethr_native_atomic_t *var, long i)
 
54
ethr_native_atomic32_set(ethr_native_atomic32_t *var, ethr_sint32_t i)
45
55
{
46
 
    __insn_mf();
47
56
    atomic_exchange_acq(&var->counter, i);
48
57
}
49
58
 
50
 
static ETHR_INLINE long
51
 
ethr_native_atomic_read(ethr_native_atomic_t *var)
 
59
static ETHR_INLINE ethr_sint32_t
 
60
ethr_native_atomic32_read(ethr_native_atomic32_t *var)
52
61
{
53
62
    return var->counter;
54
63
}
55
64
 
56
65
static ETHR_INLINE void
57
 
ethr_native_atomic_add(ethr_native_atomic_t *var, long incr)
 
66
ethr_native_atomic32_add(ethr_native_atomic32_t *var, ethr_sint32_t incr)
58
67
{
59
 
    __insn_mf();
60
68
    atomic_add(&var->counter, incr);
61
69
}      
62
70
       
63
71
static ETHR_INLINE void
64
 
ethr_native_atomic_inc(ethr_native_atomic_t *var)
 
72
ethr_native_atomic32_inc(ethr_native_atomic32_t *var)
65
73
{
66
 
    __insn_mf();
67
74
    atomic_increment(&var->counter);
68
75
}
69
76
 
70
77
static ETHR_INLINE void
71
 
ethr_native_atomic_dec(ethr_native_atomic_t *var)
 
78
ethr_native_atomic32_dec(ethr_native_atomic32_t *var)
72
79
{
73
 
    __insn_mf();
74
80
    atomic_decrement(&var->counter);
75
81
}
76
82
 
77
 
static ETHR_INLINE long
78
 
ethr_native_atomic_add_return(ethr_native_atomic_t *var, long incr)
 
83
static ETHR_INLINE ethr_sint32_t
 
84
ethr_native_atomic32_add_return(ethr_native_atomic32_t *var, ethr_sint32_t incr)
79
85
{
80
 
    __insn_mf();
81
86
    return atomic_exchange_and_add(&var->counter, incr) + incr;
82
87
}
83
88
 
84
 
static ETHR_INLINE long
85
 
ethr_native_atomic_inc_return(ethr_native_atomic_t *var)
86
 
{
87
 
    return ethr_native_atomic_add_return(&var->counter, 1);
88
 
}
89
 
 
90
 
static ETHR_INLINE long
91
 
ethr_native_atomic_dec_return(ethr_native_atomic_t *var)
92
 
{
93
 
    return ethr_native_atomic_add_return(&var->counter, -1);
94
 
}
95
 
 
96
 
static ETHR_INLINE long
97
 
ethr_native_atomic_and_retold(ethr_native_atomic_t *var, long mask)
98
 
{
99
 
    /* Implement a barrier suitable for a mutex unlock. */
100
 
    __insn_mf();
 
89
static ETHR_INLINE ethr_sint32_t
 
90
ethr_native_atomic32_inc_return(ethr_native_atomic32_t *var)
 
91
{
 
92
    return ethr_native_atomic32_add_return(var, 1);
 
93
}
 
94
 
 
95
static ETHR_INLINE ethr_sint32_t
 
96
ethr_native_atomic32_dec_return(ethr_native_atomic32_t *var)
 
97
{
 
98
    return ethr_native_atomic32_add_return(var, -1);
 
99
}
 
100
 
 
101
static ETHR_INLINE ethr_sint32_t
 
102
ethr_native_atomic32_and_retold(ethr_native_atomic32_t *var, ethr_sint32_t mask)
 
103
{
101
104
    return atomic_and_val(&var->counter, mask);
102
105
}
103
106
 
104
 
static ETHR_INLINE long
105
 
ethr_native_atomic_or_retold(ethr_native_atomic_t *var, long mask)
 
107
static ETHR_INLINE ethr_sint32_t
 
108
ethr_native_atomic32_or_retold(ethr_native_atomic32_t *var, ethr_sint32_t mask)
106
109
{
107
 
    __insn_mf();
108
110
    return atomic_or_val(&var->counter, mask);
109
111
}
110
112
 
111
 
static ETHR_INLINE long
112
 
ethr_native_atomic_xchg(ethr_native_atomic_t *var, long val)
 
113
static ETHR_INLINE ethr_sint32_t
 
114
ethr_native_atomic32_xchg(ethr_native_atomic32_t *var, ethr_sint32_t val)
113
115
{   
114
 
    __insn_mf();
115
116
    return atomic_exchange_acq(&var->counter, val);
116
117
117
118
 
118
 
static ETHR_INLINE long
119
 
ethr_native_atomic_cmpxchg(ethr_native_atomic_t *var, long new, long expected)
 
119
static ETHR_INLINE ethr_sint32_t
 
120
ethr_native_atomic32_cmpxchg(ethr_native_atomic32_t *var,
 
121
                             ethr_sint32_t new,
 
122
                             ethr_sint32_t expected)
120
123
{
121
 
    /* Implement a barrier suitable for a mutex unlock. */
122
 
    __insn_mf();
123
124
    return atomic_compare_and_exchange_val_acq(&var->counter, new, expected);
124
125
}
125
126
 
 
127
/*
 
128
 * Atomic ops with at least specified barriers.
 
129
 */
 
130
 
 
131
static ETHR_INLINE ethr_sint32_t
 
132
ethr_native_atomic32_read_acqb(ethr_native_atomic32_t *var)
 
133
{
 
134
    ethr_sint32_t res = ethr_native_atomic32_read(var);
 
135
    ETHR_MEMORY_BARRIER;
 
136
    return res;
 
137
}
 
138
 
 
139
static ETHR_INLINE ethr_sint32_t
 
140
ethr_native_atomic32_inc_return_acqb(ethr_native_atomic32_t *var)
 
141
{
 
142
    ethr_sint32_t res = ethr_native_atomic32_inc_return(var);
 
143
    ETHR_MEMORY_BARRIER;
 
144
    return res;
 
145
}
 
146
 
 
147
static ETHR_INLINE void
 
148
ethr_native_atomic32_set_relb(ethr_native_atomic32_t *var, ethr_sint32_t val)
 
149
{
 
150
    ETHR_MEMORY_BARRIER;
 
151
    ethr_native_atomic32_set(var, val);
 
152
}
 
153
 
 
154
static ETHR_INLINE void
 
155
ethr_native_atomic32_dec_relb(ethr_native_atomic32_t *var)
 
156
{
 
157
    ETHR_MEMORY_BARRIER;
 
158
    ethr_native_atomic32_dec(var);
 
159
}
 
160
 
 
161
static ETHR_INLINE ethr_sint32_t
 
162
ethr_native_atomic32_dec_return_relb(ethr_native_atomic32_t *var)
 
163
{
 
164
    ETHR_MEMORY_BARRIER;
 
165
    return ethr_native_atomic32_dec_return(var);
 
166
}
 
167
 
 
168
static ETHR_INLINE ethr_sint32_t
 
169
ethr_native_atomic32_cmpxchg_acqb(ethr_native_atomic32_t *var,
 
170
                                  ethr_sint32_t new,
 
171
                                  ethr_sint32_t exp)
 
172
{
 
173
    return ethr_native_atomic32_cmpxchg(var, new, exp);
 
174
}
 
175
 
 
176
static ETHR_INLINE ethr_sint32_t
 
177
ethr_native_atomic32_cmpxchg_relb(ethr_native_atomic32_t *var,
 
178
                                  ethr_sint32_t new,
 
179
                                  ethr_sint32_t exp)
 
180
{
 
181
    ETHR_MEMORY_BARRIER;
 
182
    return ethr_native_atomic32_cmpxchg(var, new, exp);
 
183
}
 
184
 
126
185
#endif /* ETHR_TRY_INLINE_FUNCS */
127
186
 
128
187
#endif /* ETHREAD_TILE_ATOMIC_H */