comparison erlang/erldc/src/dyncall.erl @ 0:0cfcc391201f

initial from svn dyncall-1745
author Daniel Adler
date Thu, 19 Mar 2015 22:26:28 +0100
parents
children
comparison
equal deleted inserted replaced
-1:000000000000 0:0cfcc391201f
1 %% Copyright (c) 2014 Erik Mackdanz <erikmack@gmail.com>
2
3 %% Permission to use, copy, modify, and distribute this software for any
4 %% purpose with or without fee is hereby granted, provided that the above
5 %% copyright notice and this permission notice appear in all copies.
6
7 %% THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
8 %% WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
9 %% MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
10 %% ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
11 %% WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
12 %% ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
13 %% OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
14
15 -module(dyncall).
16
17 -export([
18 mode/2,
19 get_error/1,
20 reset/1,
21 load_library/1,
22 find_symbol/2,
23 new_call_vm/1,
24 arg_double/2,
25 call_double/2,
26 arg_float/2,
27 call_float/2,
28 arg_int/2,
29 call_int/2,
30 arg_char/2,
31 call_char/2,
32 arg_bool/2,
33 call_bool/2,
34 arg_short/2,
35 call_short/2,
36 arg_long/2,
37 call_long/2,
38 arg_longlong/2,
39 call_longlong/2,
40 arg_ptr/2,
41 call_ptr/2,
42 call_void/2,
43 arg_string/2,
44 call_string/2,
45 argf/3,
46 callf/4
47 ]).
48
49 -on_load(load_nif/0).
50
51 load_nif() ->
52 Dir = case code:priv_dir(dyncall) of
53 {error, bad_name} ->
54 filename:dirname(code:which(?MODULE)) ++ "/../priv";
55 OtherDir -> OtherDir
56 end,
57 erlang:load_nif(Dir ++ "/erldc", 0).
58
59 -spec load_library(LibPath :: string()) -> {ok,Lib :: binary()} | {error,_Reason}.
60 load_library(_LibPath) ->
61 {error,"NIF library not loaded"}.
62
63 -spec find_symbol(Lib :: binary(), SymName :: string()) -> {ok,Sym :: binary()} | {error,_Reason}.
64 find_symbol(_Lib, _SymName) ->
65 {error,"NIF library not loaded"}.
66
67 -spec new_call_vm(Size :: pos_integer()) -> {ok,Vm :: binary()} | {error,_Reason}.
68 new_call_vm(_Size) ->
69 {error,"NIF library not loaded"}.
70
71 -spec arg_double(Vm :: binary(), Double :: float()) -> ok | {error, _Reason}.
72 arg_double(_Vm, _Double) ->
73 {error,"NIF library not loaded"}.
74
75 -spec call_double(Vm :: binary(), Sym :: binary()) -> {ok, Result :: float()} | {error, _Reason}.
76 call_double(_Vm, _Sym) ->
77 {error,"NIF library not loaded"}.
78
79 -spec arg_float(Vm :: binary(), Float :: float()) -> ok | {error, _Reason}.
80 arg_float(_Vm, _Float) ->
81 {error,"NIF library not loaded"}.
82
83 -spec call_float(Vm :: binary(), Sym :: binary()) -> {ok, Result :: float()} | {error, _Reason}.
84 call_float(_Vm, _Sym) ->
85 {error,"NIF library not loaded"}.
86
87 -spec arg_int(Vm :: binary(), Int :: integer()) -> ok | {error, _Reason}.
88 arg_int(_Vm, _Int) ->
89 {error,"NIF library not loaded"}.
90
91 -spec call_int(Vm :: binary(), Sym :: binary()) -> {ok, Result :: integer()} | {error, _Reason}.
92 call_int(_Vm, _Sym) ->
93 {error,"NIF library not loaded"}.
94
95 -spec arg_char(Vm :: binary(), Char :: char()) -> ok | {error, _Reason}.
96 arg_char(_Vm, _Char) ->
97 {error,"NIF library not loaded"}.
98
99 -spec call_char(Vm :: binary(), Sym :: binary()) -> {ok, Result :: char()} | {error, _Reason}.
100 call_char(_Vm, _Sym) ->
101 {error,"NIF library not loaded"}.
102
103 -spec arg_bool(Vm :: binary(), Bool :: boolean()) -> ok | {error, _Reason}.
104 arg_bool(_Vm, _Bool) ->
105 {error,"NIF library not loaded"}.
106
107 -spec call_bool(Vm :: binary(), Sym :: binary()) -> {ok, Result :: boolean()} | {error, _Reason}.
108 call_bool(_Vm, _Sym) ->
109 {error,"NIF library not loaded"}.
110
111 -spec arg_short(Vm :: binary(), Short :: integer()) -> ok | {error, _Reason}.
112 arg_short(_Vm, _Short) ->
113 {error,"NIF library not loaded"}.
114
115 -spec call_short(Vm :: binary(), Sym :: binary()) -> {ok, Result :: integer()} | {error, _Reason}.
116 call_short(_Vm, _Sym) ->
117 {error,"NIF library not loaded"}.
118
119 -spec arg_long(Vm :: binary(), Long :: integer()) -> ok | {error, _Reason}.
120 arg_long(_Vm, _Long) ->
121 {error,"NIF library not loaded"}.
122
123 -spec call_long(Vm :: binary(), Sym :: binary()) -> {ok, Result :: integer()} | {error, _Reason}.
124 call_long(_Vm, _Sym) ->
125 {error,"NIF library not loaded"}.
126
127 -spec arg_longlong(Vm :: binary(), Longlong :: integer()) -> ok | {error, _Reason}.
128 arg_longlong(_Vm, _Longlong) ->
129 {error,"NIF library not loaded"}.
130
131 -spec call_longlong(Vm :: binary(), Sym :: binary()) -> {ok, Result :: integer()} | {error, _Reason}.
132 call_longlong(_Vm, _Sym) ->
133 {error,"NIF library not loaded"}.
134
135
136 -spec arg_ptr(Vm :: binary(), Ptr :: binary()) -> ok | {error, _Reason}.
137 arg_ptr(_Vm, _Ptr) ->
138 {error,"NIF library not loaded"}.
139
140 -spec call_ptr(Vm :: binary(), Sym :: binary()) -> {ok, Result :: binary()} | {error, _Reason}.
141 call_ptr(_Vm, _Sym) ->
142 {error,"NIF library not loaded"}.
143
144 -spec call_void(Vm :: binary(), Sym :: binary()) -> ok | {error, _Reason}.
145 call_void(_Vm, _Sym) ->
146 {error,"NIF library not loaded"}.
147
148 -spec arg_string(Vm :: binary(), String :: string()) -> ok | {error, _Reason}.
149 arg_string(_Vm, _String) ->
150 {error,"NIF library not loaded"}.
151
152 -spec call_string(Vm :: binary(), Sym :: binary()) -> {ok, Result :: string()} | {error, _Reason}.
153 call_string(_Vm, _Sym) ->
154 {error,"NIF library not loaded"}.
155
156 -spec mode(Vm :: binary(), Mode :: pos_integer()) -> ok | {error, _Reason}.
157 mode(_Vm, _Mode) ->
158 {error,"NIF library not loaded"}.
159
160 -spec get_error(Vm :: binary()) -> {ok, ErrorCode :: pos_integer()} | {error, _Reason}.
161 get_error(_Vm) ->
162 {error,"NIF library not loaded"}.
163
164 -spec reset(Vm :: binary()) -> ok | {error, _Reason}.
165 reset(_Vm) ->
166 {error,"NIF library not loaded"}.
167
168 -spec argf(Vm :: binary(), Format :: string(), Args :: [term()]) -> ok | {error, _Reason}.
169 argf(_Vm,_Format,_Args) ->
170 {error,"NIF library not loaded"}.
171
172 -spec callf(Vm :: binary(), Sym :: binary(), Format :: string(), Args :: [term()]) -> ok | {error, _Reason}.
173 callf(_Vm,_Sym,_Format,_Args) ->
174 {error,"NIF library not loaded"}.
175