@@ -23,6 +23,10 @@ module flc_set
2323 type (C_PTR), public :: cptr = C_NULL_PTR
2424 integer (C_INT), public :: cmemflags = 0
2525 end type
26+ type, bind(C) :: SwigArrayWrapper
27+ type (C_PTR), public :: data = C_NULL_PTR
28+ integer (C_SIZE_T), public :: size = 0
29+ end type
2630 ! class std::set< int >
2731 type, public :: SetInt
2832 type (SwigClassWrapper), public :: swigdata
@@ -32,18 +36,17 @@ module flc_set
3236 procedure :: clear = > swigf_SetInt_clear
3337 procedure :: erase = > swigf_SetInt_erase
3438 procedure :: count = > swigf_SetInt_count
35- procedure :: insert = > swigf_SetInt_insert
39+ procedure , private :: swigf_SetInt_insert__SWIG_0
40+ procedure , private :: swigf_SetInt_insert__SWIG_1
3641 procedure :: release = > swigf_release_SetInt
3742 procedure , private :: swigf_SetInt_op_assign__
3843 generic :: assignment (= ) = > swigf_SetInt_op_assign__
44+ generic :: insert = > swigf_SetInt_insert__SWIG_0, swigf_SetInt_insert__SWIG_1
3945 end type SetInt
4046 interface SetInt
41- module procedure swigf_create_SetInt
47+ module procedure swigf_new_SetInt__SWIG_0
48+ module procedure swigf_new_SetInt__SWIG_1
4249 end interface
43- type, bind(C) :: SwigArrayWrapper
44- type (C_PTR), public :: data = C_NULL_PTR
45- integer (C_SIZE_T), public :: size = 0
46- end type
4750 ! class std::set< std::string >
4851 type, public :: SetString
4952 type (SwigClassWrapper), public :: swigdata
@@ -54,6 +57,7 @@ module flc_set
5457 procedure :: erase = > swigf_SetString_erase
5558 procedure :: count = > swigf_SetString_count
5659 procedure :: insert = > swigf_SetString_insert
60+ procedure :: insert_ref = > swigf_SetString_insert_ref
5761 procedure :: release = > swigf_release_SetString
5862 procedure , private :: swigf_SetString_op_assign__
5963 generic :: assignment (= ) = > swigf_SetString_op_assign__
@@ -64,8 +68,8 @@ module flc_set
6468
6569! WRAPPER DECLARATIONS
6670interface
67- function swigc_new_SetInt () &
68- bind(C, name= " _wrap_new_SetInt " ) &
71+ function swigc_new_SetInt__SWIG_0 () &
72+ bind(C, name= " _wrap_new_SetInt__SWIG_0 " ) &
6973result(fresult)
7074use , intrinsic :: ISO_C_BINDING
7175import :: swigclasswrapper
@@ -117,14 +121,33 @@ function swigc_SetInt_count(farg1, farg2) &
117121integer (C_LONG) :: fresult
118122end function
119123
120- subroutine swigc_SetInt_insert (farg1 , farg2 ) &
121- bind(C, name= " _wrap_SetInt_insert " )
124+ subroutine swigc_SetInt_insert__SWIG_0 (farg1 , farg2 ) &
125+ bind(C, name= " _wrap_SetInt_insert__SWIG_0 " )
122126use , intrinsic :: ISO_C_BINDING
123127import :: swigclasswrapper
124128type (SwigClassWrapper) :: farg1
125129integer (C_INT), intent (in ) :: farg2
126130end subroutine
127131
132+ function swigc_new_SetInt__SWIG_1 (farg1 ) &
133+ bind(C, name= " _wrap_new_SetInt__SWIG_1" ) &
134+ result(fresult)
135+ use , intrinsic :: ISO_C_BINDING
136+ import :: swigclasswrapper
137+ import :: swigarraywrapper
138+ type (SwigArrayWrapper) :: farg1
139+ type (SwigClassWrapper) :: fresult
140+ end function
141+
142+ subroutine swigc_SetInt_insert__SWIG_1 (farg1 , farg2 ) &
143+ bind(C, name= " _wrap_SetInt_insert__SWIG_1" )
144+ use , intrinsic :: ISO_C_BINDING
145+ import :: swigclasswrapper
146+ import :: swigarraywrapper
147+ type (SwigClassWrapper) :: farg1
148+ type (SwigArrayWrapper) :: farg2
149+ end subroutine
150+
128151subroutine swigc_delete_SetInt (farg1 ) &
129152bind(C, name= " _wrap_delete_SetInt" )
130153use , intrinsic :: ISO_C_BINDING
@@ -204,6 +227,14 @@ subroutine swigc_SetString_insert(farg1, farg2) &
204227type (SwigArrayWrapper) :: farg2
205228end subroutine
206229
230+ subroutine swigc_SetString_insert_ref (farg1 , farg2 ) &
231+ bind(C, name= " _wrap_SetString_insert_ref" )
232+ use , intrinsic :: ISO_C_BINDING
233+ import :: swigclasswrapper
234+ type (SwigClassWrapper) :: farg1
235+ type (SwigClassWrapper) :: farg2
236+ end subroutine
237+
207238subroutine swigc_delete_SetString (farg1 ) &
208239bind(C, name= " _wrap_delete_SetString" )
209240use , intrinsic :: ISO_C_BINDING
@@ -224,13 +255,13 @@ subroutine swigc_SetString_op_assign__(farg1, farg2) &
224255
225256contains
226257 ! MODULE SUBPROGRAMS
227- function swigf_create_SetInt () &
258+ function swigf_new_SetInt__SWIG_0 () &
228259result(self)
229260use , intrinsic :: ISO_C_BINDING
230261type (SetInt) :: self
231262type (SwigClassWrapper) :: fresult
232263
233- fresult = swigc_new_SetInt ()
264+ fresult = swigc_new_SetInt__SWIG_0 ()
234265self% swigdata = fresult
235266end function
236267
@@ -316,7 +347,7 @@ function swigf_SetInt_count(self, x) &
316347swig_result = int (fresult)
317348end function
318349
319- subroutine swigf_SetInt_insert (self , x )
350+ subroutine swigf_SetInt_insert__SWIG_0 (self , x )
320351use , intrinsic :: ISO_C_BINDING
321352class(SetInt), intent (in ) :: self
322353integer (C_INT), intent (in ) :: x
@@ -325,7 +356,48 @@ subroutine swigf_SetInt_insert(self, x)
325356
326357farg1 = self% swigdata
327358farg2 = x
328- call swigc_SetInt_insert(farg1, farg2)
359+ call swigc_SetInt_insert__SWIG_0(farg1, farg2)
360+ end subroutine
361+
362+ subroutine SWIGTM_fin_int_Sb__SB_ (finp , iminp )
363+ use , intrinsic :: ISO_C_BINDING
364+ integer (C_INT), dimension (:), intent (in ), target :: finp
365+ type (SwigArrayWrapper), intent (out ) :: iminp
366+ integer (C_SIZE_T) :: sz
367+ integer (C_INT), pointer :: imtemp
368+
369+ sz = size (finp, kind= C_SIZE_T)
370+ if (sz > 0_c_size_t ) then
371+ imtemp = > finp(1 )
372+ iminp% data = c_loc(imtemp)
373+ else
374+ iminp% data = c_null_ptr
375+ end if
376+ iminp% size = sz
377+ end subroutine
378+ function swigf_new_SetInt__SWIG_1 (data ) &
379+ result(self)
380+ use , intrinsic :: ISO_C_BINDING
381+ type (SetInt) :: self
382+ integer (C_INT), dimension (:), intent (in ), target :: data
383+ type (SwigClassWrapper) :: fresult
384+ type (SwigArrayWrapper) :: farg1
385+
386+ call SWIGTM_fin_int_Sb__SB_(data , farg1)
387+ fresult = swigc_new_SetInt__SWIG_1(farg1)
388+ self% swigdata = fresult
389+ end function
390+
391+ subroutine swigf_SetInt_insert__SWIG_1 (self , data )
392+ use , intrinsic :: ISO_C_BINDING
393+ class(SetInt), intent (in ) :: self
394+ integer (C_INT), dimension (:), intent (in ), target :: data
395+ type (SwigClassWrapper) :: farg1
396+ type (SwigArrayWrapper) :: farg2
397+
398+ farg1 = self% swigdata
399+ call SWIGTM_fin_int_Sb__SB_(data , farg2)
400+ call swigc_SetInt_insert__SWIG_1(farg1, farg2)
329401end subroutine
330402
331403subroutine swigf_release_SetInt (self )
@@ -467,6 +539,18 @@ subroutine swigf_SetString_insert(self, x)
467539call swigc_SetString_insert(farg1, farg2)
468540end subroutine
469541
542+ subroutine swigf_SetString_insert_ref (self , str )
543+ use , intrinsic :: ISO_C_BINDING
544+ class(SetString), intent (in ) :: self
545+ class(string), intent (in ) :: str
546+ type (SwigClassWrapper) :: farg1
547+ type (SwigClassWrapper) :: farg2
548+
549+ farg1 = self% swigdata
550+ farg2 = str% swigdata
551+ call swigc_SetString_insert_ref(farg1, farg2)
552+ end subroutine
553+
470554subroutine swigf_release_SetString (self )
471555use , intrinsic :: ISO_C_BINDING
472556class(SetString), intent (inout ) :: self
0 commit comments