OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
soltosph_on2.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "param_c.inc"
#include "sphcom.inc"
#include "task_c.inc"
#include "vect01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine soltosph_on2 (x, spbuf, kxsp, ipartsp, elbuf_tab, iparg, ngrounc, igrounc, itask, ixsp, nod2sp, sol2sph, waspact)

Function/Subroutine Documentation

◆ soltosph_on2()

subroutine soltosph_on2 ( x,
spbuf,
integer, dimension(nisp,*) kxsp,
integer, dimension(*) ipartsp,
type (elbuf_struct_), dimension(ngroup), target elbuf_tab,
integer, dimension(nparg,*) iparg,
integer ngrounc,
integer, dimension(*) igrounc,
integer itask,
integer, dimension(kvoisph,*) ixsp,
integer, dimension(*) nod2sp,
integer, dimension(2,*) sol2sph,
integer, dimension(*) waspact )

Definition at line 39 of file soltosph_on2.F.

43C-----------------------------------------------
44C M o d u l e s
45C-----------------------------------------------
46 USE sphbox
47 USE elbufdef_mod
48 USE message_mod
49 USE soltosph_mod
50C-----------------------------------------------
51C I m p l i c i t T y p e s
52C-----------------------------------------------
53#include "implicit_f.inc"
54C-----------------------------------------------
55C C o m m o n B l o c k s
56C-----------------------------------------------
57#include "com01_c.inc"
58#include "param_c.inc"
59#include "sphcom.inc"
60#include "task_c.inc"
61#include "vect01_c.inc"
62C-----------------------------------------------
63C D u m m y A r g u m e n t s
64C-----------------------------------------------
65 INTEGER KXSP(NISP,*),
66 . IPARTSP(*), IPARG(NPARG,*), NGROUNC,
67 . IGROUNC(*), ITASK, IXSP(KVOISPH,*), NOD2SP(*),
68 . SOL2SPH(2,*), WASPACT(*)
70 . x(3,*), spbuf(nspbuf,*)
71 TYPE (ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
72C-----------------------------------------------
73C L o c a l V a r i a b l e s
74C-----------------------------------------------
75 INTEGER I, N, IP, KP, NG, MG, J, NP, KFT, IG, NELEM,
76 . NEL, OFFSET, NVOIS, M, JNOD, NN, IERROR
77C
78C-----
79 TYPE(G_BUFEL_) ,POINTER :: GBUF, GBUFSP
80 TYPE(L_BUFEL_) ,POINTER :: LBUF
81 TYPE(BUF_MAT_) ,POINTER :: MBUF
82C-----------------------------------------------
83 IF(itask==0)THEN
84 ALLOCATE(wspcloud(numsph),stat=ierror)
85 IF(ierror/=0) THEN
86 CALL ancmsg(msgid=19,anmode=aninfo,
87 . c1='(SOLIDS to SPH)')
88 CALL arret(2)
89 ENDIF
90 wspcloud(1:numsph)=0
91 END IF
92C /---------------/
93 CALL my_barrier
94C /---------------/
95!$OMP DO SCHEDULE(DYNAMIC,1)
96 DO ig = 1, ngrounc
97 ng = igrounc(ig)
98C
99C look for groups to awake (active particles plus cloud active particles)
100 IF (iddw>0) CALL startimeg(ng)
101 DO nelem = 1,iparg(2,ng),nvsiz
102 offset = nelem - 1
103 nel =iparg(2,ng)
104 nft =iparg(3,ng) + offset
105 iad =iparg(4,ng)
106 ity =iparg(5,ng)
107 lft=1
108 llt=min(nvsiz,nel-nelem+1)
109 IF(ity==51) THEN
110C-----------
111 DO i=lft,llt
112 np=nft+i
113 IF(kxsp(2,np)>0) THEN
114 iparg(8,ng)=0
115 wspcloud(np)=1
116 ELSEIF(kxsp(2,np)<0) THEN
117 nvois=kxsp(4,np)
118 DO j=1,nvois
119 jnod=ixsp(j,np)
120 IF(jnod>0)THEN
121 m=nod2sp(jnod)
122 IF(kxsp(2,m)>0)THEN
123 iparg(8,ng)=0
124 wspcloud(np)=1
125 EXIT
126 END IF
127 ELSE
128 nn = -jnod
129 IF(nint(xsphr(13,nn))>0)THEN
130 iparg(8,ng)=0
131 wspcloud(np)=1
132 EXIT
133 END IF
134 END IF
135 END DO
136 END IF
137 ENDDO
138 END IF
139 END DO
140 IF (iddw>0) CALL stoptimeg(ng)
141C--------
142 END DO
143!$OMP END DO
144C-----------------------------------------------
145 IF(itask==0)THEN
146 DO np=1,numsph
147 IF(wspcloud(np)/=0)THEN
148 nsphact=nsphact+1
149 waspact(nsphact)=np
150 END IF
151 END DO
152 DEALLOCATE(wspcloud)
153 END IF
154C-----------------------------------------------
155 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine startimeg(ng)
Definition timer.F:1487
subroutine stoptimeg(ng)
Definition timer.F:1535
#define min(a, b)
Definition macros.h:20
integer, dimension(:), allocatable wspcloud
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889
subroutine arret(nn)
Definition arret.F:87
subroutine my_barrier
Definition machine.F:31