OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sms_gravit.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "com04_c.inc"
#include "com08_c.inc"
#include "task_c.inc"
#include "param_c.inc"
#include "vectorize.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine sms_gravit (igrv, agrv, npc, tf, a, v, x, skew, ms, sensor_tab, weight, ib, itask, tagslv_rby_sms, nsensor, wfext, python)

Function/Subroutine Documentation

◆ sms_gravit()

subroutine sms_gravit ( integer, dimension(nigrv,*) igrv,
agrv,
integer, dimension(*) npc,
tf,
a,
v,
x,
skew,
ms,
type (sensor_str_), dimension(nsensor), intent(in) sensor_tab,
integer, dimension(*) weight,
integer, dimension(*) ib,
integer itask,
integer, dimension(*) tagslv_rby_sms,
integer nsensor,
double precision, intent(inout) wfext,
type(python_), intent(inout) python )

Definition at line 34 of file sms_gravit.F.

37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE python_funct_mod, ONLY : python_
41 use finter_mixed_mod, only : finter_mixed
42 USE sensor_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47#include "comlock.inc"
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "com04_c.inc"
52!#include "com06_c.inc"
53#include "com08_c.inc"
54#include "task_c.inc"
55#include "param_c.inc"
56C-----------------------------------------------
57C D u m m y A r g u m e n t s
58C-----------------------------------------------
59 INTEGER NPC(*),NDDIM,NVDIM,NSENSOR
60 INTEGER IGRV(NIGRV,*),IB(*)
61 INTEGER WEIGHT(*), ITASK, TAGSLV_RBY_SMS(*)
63 . agrv(lfacgrv,*), tf(*), a(3,*), v(3,*), ms(*),
64 . x(3,*), skew(lskew,*)
65 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) ,INTENT(IN) :: SENSOR_TAB
66 DOUBLE PRECISION,INTENT(INOUT) :: WFEXT
67 TYPE(python_), intent(inout) :: python
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER NL, N1, ISK, N2, IFUNC, K1, K2, K3, ISENS,K,NN,IAD,J, IADF, IADL
72 my_real nx, ny, nz, axi, a0, aa, vv, fx, fy, fz, ax, ts,gama, wfextt,fcx,fcy
73 my_real,EXTERNAL :: finter
74C=======================================================================
75 wfextt=zero
76C
77 DO nl=1,ngrav
78 fcy = agrv(1,nl)
79 fcx = agrv(2,nl)
80 nn=igrv(1,nl)
81 isk=igrv(2,nl)/10
82 n2 =igrv(2,nl)-10*isk
83 ifunc=igrv(3,nl)
84 iad=igrv(4,nl)
85 iadf = iad+itask*nn/nthread
86 iadl = iad-1+(itask+1)*nn/nthread
87C
88 isens=0
89 DO k=1,nsensor
90 IF(igrv(6,nl)== sensor_tab(k)%SENS_ID) isens=k ! do it in starter !!!
91 ENDDO
92 IF(isens==0)THEN
93 ts=tt
94 ELSE
95 ts = tt-sensor_tab(isens)%TSTART
96 IF(ts<0.0)cycle
97 ENDIF
98C
99 IF (ifunc > 0) THEN
100 a0 = fcy*finter_mixed(python,nfunct,ifunc,(ts-dt1)*fcx,npc,tf)
101 gama = fcy*finter_mixed(python,nfunct,ifunc,ts*fcx,npc,tf)
102 ELSE
103 a0 = fcy
104 gama = fcy
105 ENDIF
106C
107 aa = gama
108 IF(isk<=1)THEN
109#include "vectorize.inc"
110 DO j=iadf,iadl
111 n1=iabs(ib(j))
112 IF(tagslv_rby_sms(n1)/=0) cycle
113 a(n2,n1)=a(n2,n1)+ms(n1)*aa
114 IF(ib(j)>0) wfextt=wfextt + half*(a0+aa)*ms(n1)*v(n2,n1)*dt1*weight(n1)
115 ENDDO
116 ELSE
117 k1=3*n2-2
118 k2=3*n2-1
119 k3=3*n2
120#include "vectorize.inc"
121 DO j=iadf,iadl
122 n1=iabs(ib(j))
123 IF(tagslv_rby_sms(n1)/=0) cycle
124 vv = skew(k1,isk)*v(1,n1)+skew(k2,isk)*v(2,n1)+skew(k3,isk)*v(3,n1)
125 a(1,n1)=a(1,n1)+skew(k1,isk)*ms(n1)*aa
126 a(2,n1)=a(2,n1)+skew(k2,isk)*ms(n1)*aa
127 a(3,n1)=a(3,n1)+skew(k3,isk)*ms(n1)*aa
128 IF(ib(j)>0) wfextt=wfextt+half*(a0+aa)*ms(n1)*vv*dt1*weight(n1)
129 ENDDO
130 ENDIF
131 END DO
132C
133!$OMP ATOMIC
134 wfext = wfext + wfextt
135C
136 RETURN
#define my_real
Definition cppsort.cpp:32
character *2 function nl()
Definition message.F:2354