35 * BOXLIST, BOXLIST_SIZE,
48#include "implicit_f.inc"
57 TYPE (BOX_),
DIMENSION(NBBOX) :: IBOX
59 INTEGER BOXNDS(*),BOXLIST(*)
60 INTEGER , BOXLIST_SIZE
64 CHARACTER(LEN=NCHARFIELD) :: KEYSET
65 CHARACTER(LEN=NCHARTITLE) :: SET_TITLE
69 INTEGER I,B_NDS_SIZE,NB_RESULT,
70 . ID,,,J,CLAUSE_OPERATOR
72 INTEGER,
DIMENSION(:) ,
ALLOCATABLE :: B_NDS,RESULT
74 ALLOCATE(b_nds(numnod))
75 ALLOCATE(result(numnod))
87 * ibox ,x ,skew ,set_title ,keyset,
96 boxnds(1:nb_result) = result(1:nb_result)
115!||====================================================================
117 * IBOX ,X ,SKEW ,SET_TITLE ,KEYSET,
118 * BOXNDS, SZ_BOXNDS )
148#include "implicit_f.inc"
152#include "com04_c.inc"
153#include "param_c.inc"
157 TYPE (
box_) ,
DIMENSION(NBBOX) :: ibox
163 . x(3,*),skew(lskew,*)
165 CHARACTER(LEN=NCHARFIELD) :: keyset
166 CHARACTER(LEN=NCHARTITLE)::set_title
170 INTEGER i,b_nds_size,nb_result,
171 . nb_box_of_box,j,new_box,clause_operator
173 INTEGER,
DIMENSION(:) ,
ALLOCATABLE :: b_nds,result
178 nb_box_of_box = ibox(ib)%NBOXBOX
180 IF ( nb_box_of_box == 0 )
THEN
189 ALLOCATE(b_nds(numnod))
190 ALLOCATE(result(numnod))
195 j = ibox(ib)%IBOXBOX(i)
202 * b_nds, b_nds_size )
211 * b_nds, b_nds_size ,
212 * result, nb_result ,
215 boxnds(1:nb_result) = result(1:nb_result)
216 sz_boxnds = nb_result
recursive subroutine node_box(ib, ibox, x, skew, set_title, keyset, boxnds, sz_boxnds)
subroutine fill_clause_node_box(ibox, x, skew, set_title, keyset, boxlist, boxlist_size, boxnds, sz_boxnds)
integer, parameter nchartitle
integer, parameter ncharfield
integer, parameter set_add
add operator
integer, parameter set_delete
delete operator
subroutine set_merge_simple(set_entity, nb_set_entity, clause_entity, nb_clause_entity, result, nb_result, clause_operator)
subroutine simple_node_box(ibox, x, skew, ib, nd_array, nd_size)