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

« back to all changes in this revision

Viewing changes to erts/example/matrix_nif.c

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
/*
 
2
 * %CopyrightBegin%
 
3
 *
 
4
 * Copyright Ericsson AB 2010. All Rights Reserved.
 
5
 *
 
6
 * The contents of this file are subject to the Erlang Public License,
 
7
 * Version 1.1, (the "License"); you may not use this file except in
 
8
 * compliance with the License. You should have received a copy of the
 
9
 * Erlang Public License along with this software. If not, it can be
 
10
 * retrieved online at http://www.erlang.org/.
 
11
 *
 
12
 * Software distributed under the License is distributed on an "AS IS"
 
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
 * the License for the specific language governing rights and limitations
 
15
 * under the License.
 
16
 *
 
17
 * %CopyrightEnd%
 
18
 */
 
19
/*
 
20
 * Purpose: Simple example of NIFs using resource objects to implement functions
 
21
 *          for matrix calculations.
 
22
 */
 
23
 
 
24
#include "erl_nif.h"
 
25
 
 
26
#include <stddef.h>
 
27
#include <assert.h>
 
28
 
 
29
typedef struct
 
30
{
 
31
    unsigned nrows;
 
32
    unsigned ncols;
 
33
    double* data;
 
34
}Matrix;
 
35
 
 
36
#define POS(MX, ROW, COL) ((MX)->data[(ROW)* (MX)->ncols + (COL)])
 
37
 
 
38
static int get_number(ErlNifEnv* env, ERL_NIF_TERM term, double* dp);
 
39
static Matrix* alloc_matrix(ErlNifEnv* env, unsigned nrows, unsigned ncols);
 
40
static void matrix_dtor(ErlNifEnv* env, void* obj);
 
41
 
 
42
 
 
43
static ErlNifResourceType* resource_type = NULL;
 
44
 
 
45
static int load(ErlNifEnv* env, void** priv_data, ERL_NIF_TERM load_info)
 
46
{
 
47
    ErlNifResourceType* rt = enif_open_resource_type(env, "matrix_nif_example",
 
48
                                                     matrix_dtor, 
 
49
                                                     ERL_NIF_RT_CREATE, NULL);
 
50
    if (rt == NULL) {
 
51
        return -1;
 
52
    }
 
53
    assert(resource_type == NULL);
 
54
    resource_type = rt;
 
55
    return 0;
 
56
}
 
57
 
 
58
static ERL_NIF_TERM create(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 
59
{
 
60
    /* create(Nrows, Ncolumns, [[first row],[second row],...,[last row]]) -> Matrix */
 
61
    unsigned nrows, ncols;
 
62
    unsigned i, j;
 
63
    ERL_NIF_TERM list, row, ret;
 
64
    Matrix* mx = NULL;
 
65
 
 
66
    if (!enif_get_uint(env, argv[0], &nrows) || nrows < 1 ||
 
67
        !enif_get_uint(env, argv[1], &ncols) || ncols < 1) {
 
68
 
 
69
        goto badarg;
 
70
    }
 
71
    mx = alloc_matrix(env, nrows, ncols);
 
72
    list = argv[2];
 
73
    for (i = 0; i<nrows; i++) {
 
74
        if (!enif_get_list_cell(env, list, &row, &list)) {
 
75
            goto badarg;
 
76
        }
 
77
        for (j = 0; j<ncols; j++) {
 
78
            ERL_NIF_TERM v;
 
79
            if (!enif_get_list_cell(env, row, &v, &row) ||
 
80
                !get_number(env, v, &POS(mx,i,j))) { 
 
81
                goto badarg;
 
82
            }       
 
83
        }
 
84
        if (!enif_is_empty_list(env, row)) {
 
85
            goto badarg;
 
86
        }
 
87
    }
 
88
    if (!enif_is_empty_list(env, list)) {
 
89
        goto badarg;
 
90
    }
 
91
 
 
92
    ret = enif_make_resource(env, mx);
 
93
    enif_release_resource(env, mx);
 
94
    return ret;
 
95
 
 
96
badarg:
 
97
    if (mx != NULL) {
 
98
        enif_release_resource(env,mx);
 
99
    }
 
100
    return enif_make_badarg(env);
 
101
}
 
102
 
 
103
 
 
104
static ERL_NIF_TERM pos(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 
105
{
 
106
    /* pos(Matrix, Row, Column) -> float() */
 
107
    Matrix* mx;
 
108
    unsigned i, j;
 
109
    if (!enif_get_resource(env, argv[0], resource_type, (void**)&mx) ||
 
110
        !enif_get_uint(env, argv[1], &i) || (--i >= mx->nrows) ||
 
111
        !enif_get_uint(env, argv[2], &j) || (--j >= mx->ncols)) {
 
112
        return enif_make_badarg(env);
 
113
    }
 
114
    return enif_make_double(env, POS(mx, i,j));
 
115
}
 
116
 
 
117
static ERL_NIF_TERM add(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 
118
{
 
119
    /* add(Matrix_A, Matrix_B) -> Matrix_Sum */
 
120
    unsigned i, j;
 
121
    ERL_NIF_TERM ret;
 
122
    Matrix* mxA = NULL;
 
123
    Matrix* mxB = NULL;
 
124
    Matrix* mxS = NULL;
 
125
 
 
126
    if (!enif_get_resource(env, argv[0], resource_type, (void**)&mxA) ||
 
127
        !enif_get_resource(env, argv[1], resource_type, (void**)&mxB) ||
 
128
        mxA->nrows != mxB->nrows ||
 
129
        mxB->ncols != mxB->ncols) {
 
130
 
 
131
        return enif_make_badarg(env);
 
132
    }
 
133
    mxS = alloc_matrix(env, mxA->nrows, mxA->ncols);
 
134
    for (i = 0; i < mxA->nrows; i++) {
 
135
        for (j = 0; j < mxA->ncols; j++) {
 
136
            POS(mxS, i, j) = POS(mxA, i, j) + POS(mxB, i, j);
 
137
        }
 
138
    }
 
139
    ret = enif_make_resource(env, mxS);
 
140
    enif_release_resource(env, mxS);
 
141
    return ret;
 
142
}
 
143
 
 
144
static ERL_NIF_TERM size_of(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 
145
{
 
146
    /* size(Matrix) -> {Nrows, Ncols} */
 
147
    Matrix* mx;
 
148
    if (!enif_get_resource(env, argv[0], resource_type, (void**)&mx)) {
 
149
        return enif_make_badarg(env);
 
150
    }
 
151
    return enif_make_tuple2(env, enif_make_uint(env, mx->nrows),
 
152
                            enif_make_uint(env, mx->ncols));
 
153
}
 
154
 
 
155
static ERL_NIF_TERM to_term(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 
156
{
 
157
    /* to_term(Matrix) -> [[first row], [second row], ...,[last row]] */
 
158
    unsigned i, j;
 
159
    ERL_NIF_TERM res;
 
160
    Matrix* mx = NULL;
 
161
 
 
162
    if (!enif_get_resource(env, argv[0], resource_type, (void**)&mx)) { 
 
163
        return enif_make_badarg(env);
 
164
    }
 
165
    res = enif_make_list(env, 0);
 
166
    for (i = mx->nrows; i-- > 0; ) {
 
167
        ERL_NIF_TERM row = enif_make_list(env, 0);
 
168
        for (j = mx->ncols; j-- > 0; ) {
 
169
            row = enif_make_list_cell(env, enif_make_double(env, POS(mx,i,j)),
 
170
                                      row);
 
171
        }
 
172
        res = enif_make_list_cell(env, row, res);
 
173
    }
 
174
    return res;
 
175
}
 
176
 
 
177
static int get_number(ErlNifEnv* env, ERL_NIF_TERM term, double* dp)
 
178
{
 
179
    long i;
 
180
    return enif_get_double(env, term, dp) || 
 
181
        (enif_get_long(env, term, &i) && (*dp=(double)i, 1));
 
182
}
 
183
 
 
184
static Matrix* alloc_matrix(ErlNifEnv* env, unsigned nrows, unsigned ncols)
 
185
{
 
186
    Matrix* mx = enif_alloc_resource(env, resource_type, sizeof(Matrix));
 
187
    mx->nrows = nrows;
 
188
    mx->ncols = ncols;
 
189
    mx->data = enif_alloc(env, nrows*ncols*sizeof(double));
 
190
    return mx;
 
191
}
 
192
 
 
193
static void matrix_dtor(ErlNifEnv* env, void* obj)
 
194
{
 
195
    Matrix* mx = (Matrix*) obj;
 
196
    enif_free(env, mx->data);
 
197
    mx->data = NULL;
 
198
}
 
199
 
 
200
static ErlNifFunc nif_funcs[] =
 
201
{
 
202
    {"create", 3, create},
 
203
    {"pos", 3, pos},
 
204
    {"add", 2, add},
 
205
    {"size_of", 1, size_of},
 
206
    {"to_term", 1, to_term}
 
207
};
 
208
 
 
209
ERL_NIF_INIT(matrix_nif,nif_funcs,load,NULL,NULL,NULL);
 
210