codegen: improve floating point comparisons on loongarch, mips, parisc
[ajla.git] / stdlib / ffi.ajla
bloba22e6057f9087c8189fcf0464322ad243d20e216
1 {*
2  * Copyright (C) 2024 Mikulas Patocka
3  *
4  * This file is part of Ajla.
5  *
6  * Ajla is free software: you can redistribute it and/or modify it under the
7  * terms of the GNU General Public License as published by the Free Software
8  * Foundation, either version 3 of the License, or (at your option) any later
9  * version.
10  *
11  * Ajla is distributed in the hope that it will be useful, but WITHOUT ANY
12  * WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
13  * A PARTICULAR PURPOSE. See the GNU General Public License for more details.
14  *
15  * You should have received a copy of the GNU General Public License along with
16  * Ajla. If not, see <https://www.gnu.org/licenses/>.
17  *}
19 unit ffi;
21 uses io;
23 type ffi_structure;
25 option ffi_type [
26         t_void;
27         t_uint8;
28         t_sint8;
29         t_uint16;
30         t_sint16;
31         t_uint32;
32         t_sint32;
33         t_uint64;
34         t_sint64;
35         t_float;
36         t_double;
37         t_longdouble;
38         t_pointer;
39         t_uchar;
40         t_schar;
41         t_ushort;
42         t_sshort;
43         t_uint;
44         t_sint;
45         t_ulong;
46         t_slong;
47         t_usize;
48         t_ssize;
49         t_bool;
50         t_structure : ffi_structure;
53 option ffi_error [
54         e_none;
55         e_errno;
56         e_get_last_error;
57         e_get_last_socket_error;
60 type ffi_function;
61 type ffi_destructor;
63 fn ffi_unsafe_get_world : world;
65 fn ffi_get_size(ft : ffi_type) : int;
66 fn ffi_get_alignment(ft : ffi_type) : int;
68 fn ffi_create_structure(elements : list(ffi_type)) : (ffi_structure, list(int));
69 fn ffi_get_structure_offset(str : ffi_structure, element : int) : int;
71 fn ffi_poke(w : world, ptr : int, ft : ffi_type, val : int) : world;
72 fn ffi_peek(w : world, ptr : int, ft : ffi_type) : (world, int);
74 fn ffi_poke_array(t : type, w : world, ptr : int, a : list(t)) : world;
75 fn ffi_peek_array(w : world, ptr : int, l : int, ft : ffi_type, t : type) : (world, list(t));
77 fn ffi_handle_to_number(w : world, desc : ffi_destructor, h : handle) : (world, int);
78 fn ffi_number_to_handle(w : world, n : int, sckt : bool) : (world, handle);
80 fn ffi_create_function(filename : bytes, funcname : bytes, err_type : ffi_error, nvarargs : int, rtype : ffi_type, args : list(ffi_type)) : ffi_function;
81 fn ffi_call_function(w : world, func : ffi_function, args : list(int)) : (world, int, int);
83 fn ffi_encode_float(f : real32) : int;
84 fn ffi_encode_double(f : real64) : int;
85 fn ffi_encode_longdouble(f : real80) : int;
86 fn ffi_decode_float(i : int) : real32;
87 fn ffi_decode_double(i : int) : real64;
88 fn ffi_decode_longdouble(i : int) : real80;
90 fn ffi_destructor_new(w : world) : (world, ffi_destructor);
91 fn ffi_destructor_destroy(w : world, fd : ffi_destructor) : world;
92 fn ffi_destructor_allocate(w : world, fd : ffi_destructor, size align : int, zero : bool) : (world, int);
93 fn ffi_destructor_free(w : world, fd : ffi_destructor, ptr : int) : world;
94 fn ffi_destructor_call(w : world, fd : ffi_destructor, func : ffi_function, args : list(int)) : world;
96 implementation
98 type ffi_structure := internal_type;
99 type ffi_function := internal_type;
101 fn ffi_unsafe_get_world : world
103         return unsafe_get_world;
106 fn ffi_get_size(ft : ffi_type) : int
108         var r : int;
109         pcode IO IO_FFI_Get_Size_Alignment 1 1 1 =r ft 0;
110         return r;
113 fn ffi_get_alignment(ft : ffi_type) : int
115         var r : int;
116         pcode IO IO_FFI_Get_Size_Alignment 1 1 1 =r ft 1;
117         return r;
120 fn ffi_create_structure(elements : list(ffi_type)) : (ffi_structure, list(int))
122         var r : ffi_structure;
123         var offs : list(int);
124         pcode IO IO_FFI_Create_Structure 2 1 0 =r =offs elements;
125         return r, offs;
128 fn ffi_get_structure_offset(str : ffi_structure, element : int) : int
130         var r : int;
131         pcode IO IO_FFI_Structure_Offset 1 2 0 =r str element;
132         return r;
135 fn ffi_poke(w : world, ptr : int, ft : ffi_type, val : int) : world
137         var w2 : world;
138         pcode IO IO_FFI_Poke 1 4 0 =w2 w ptr ft val;
139         return w2;
142 fn ffi_peek(w : world, ptr : int, ft : ffi_type) : (world, int)
144         var r : int;
145         var w2 : world;
146         pcode IO IO_FFI_Peek 2 3 0 =w2 =r w ptr ft;
147         return w2, r;
150 fn ffi_poke_array(t : type, w : world, ptr : int, a : list(t)) : world
152         var w2 : world;
153         pcode IO IO_FFI_Poke_Array 1 3 0 =w2 w ptr a;
154         return w2;
157 fn ffi_peek_array(w : world, ptr : int, l : int, ft : ffi_type, t : type) : (world, list(t))
159         var r : list(t);
160         var w2 : world;
161         pcode IO IO_FFI_Peek_Array 2 4 0 =w2 =r w ptr l ft;
162         return w2, r;
165 fn ffi_handle_to_number(w : world, desc : ffi_destructor, h : handle) : (world, int)
167         var n : int;
168         var w2 : world;
169         pcode IO IO_FFI_Handle_To_Number 2 3 0 =w2 =n w desc h;
170         return w2, n;
173 fn ffi_number_to_handle(w : world, n : int, sckt : bool) : (world, handle)
175         var h : handle;
176         var w2 : world;
177         pcode IO IO_FFI_Number_To_Handle 2 3 0 =w2 =h w n sckt;
178         return w2, h;
181 fn ffi_create_function(filename : bytes, funcname : bytes, err_type : ffi_error, nvarargs : int, rtype : ffi_type, args : list(ffi_type)) : ffi_function
183         var r : ffi_function;
184         pcode IO IO_FFI_Create_Function 1 6 0 =r filename funcname err_type nvarargs rtype args;
185         return r;
188 fn ffi_call_function(w : world, func : ffi_function, args : list(int)) : (world, int, int)
190         var r e : int;
191         var w2 : world;
192         pcode IO IO_FFI_Call_Function 3 3 0 =w2 =r =e w func args;
193         return w2, r, e;
196 fn ffi_encode_float(f : real32) : int
198         var r : int;
199         pcode IO IO_FFI_Encode_Real 1 1 0 =r f;
200         return r;
203 fn ffi_encode_double(f : real64) : int
205         var r : int;
206         pcode IO IO_FFI_Encode_Real 1 1 0 =r f;
207         return r;
210 fn ffi_encode_longdouble(f : real80) : int
212         var r : int;
213         pcode IO IO_FFI_Encode_Real 1 1 0 =r f;
214         return r;
217 fn ffi_decode_float(i : int) : real32
219         var r : real32;
220         pcode IO IO_FFI_Decode_Real 1 1 0 =r i;
221         return r;
224 fn ffi_decode_double(i : int) : real64
226         var r : real64;
227         pcode IO IO_FFI_Decode_Real 1 1 0 =r i;
228         return r;
231 fn ffi_decode_longdouble(i : int) : real80
233         var r : real80;
234         pcode IO IO_FFI_Decode_Real 1 1 0 =r i;
235         return r;
238 type ffi_destructor := internal_type;
240 fn ffi_destructor_new(w : world) : (world, ffi_destructor)
242         var r : ffi_destructor;
243         var w2 : world;
244         pcode IO IO_FFI_Destructor_New 2 1 0 =w2 =r w;
245         return w2, r;
248 fn ffi_destructor_destroy(w : world, fd : ffi_destructor) : world
250         var w2 : world;
251         pcode IO IO_Consume_Parameters 1 2 0 =w2 w fd;
252         return w2;
255 fn ffi_destructor_allocate(w : world, fd : ffi_destructor, size align : int, zero : bool) : (world, int)
257         var r : int;
258         var w2 : world;
259         pcode IO IO_FFI_Destructor_Allocate 2 5 0 =w2 =r w fd size align zero;
260         return w2, r;
263 fn ffi_destructor_free(w : world, fd : ffi_destructor, ptr : int) : world
265         var w2 : world;
266         pcode IO IO_FFI_Destructor_Free 1 3 0 =w2 w fd ptr;
267         return w2;
270 fn ffi_destructor_call(w : world, fd : ffi_destructor, func : ffi_function, args : list(int)) : world
272         var w2 : world;
273         pcode IO IO_FFI_Destructor_Call 1 4 0 =w2 w fd func args;
274         return w2;