OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
tmax_ipart.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "scr17_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine tmax_ipart (iparg, ipart, iparts, ipartc, ipartg, h3d_data)

Function/Subroutine Documentation

◆ tmax_ipart()

subroutine tmax_ipart ( integer, dimension(nparg,ngroup), intent(in) iparg,
integer, dimension(lipart1,npart), intent(in) ipart,
integer, dimension(numels), intent(in) iparts,
integer, dimension(numelc), intent(in) ipartc,
integer, dimension(numeltg), intent(in) ipartg,
type(h3d_database) h3d_data )

Definition at line 33 of file tmax_ipart.F.

34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37 USE outmax_mod
38 USE h3d_mod
39 USE message_mod
41C-----------------------------------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com01_c.inc"
49#include "com04_c.inc"
50#include "param_c.inc"
51#include "scr17_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER, DIMENSION(NPARG,NGROUP) ,INTENT(IN):: IPARG
56 INTEGER, DIMENSION(LIPART1,NPART),INTENT(IN):: IPART
57 INTEGER ,DIMENSION(NUMELS),INTENT(IN):: IPARTS
58 INTEGER ,DIMENSION(NUMELC),INTENT(IN):: IPARTC
59 INTEGER ,DIMENSION(NUMELTG),INTENT(IN):: IPARTG
60 TYPE(H3D_DATABASE) :: H3D_DATA
61C-----------------------------------------------
62C L o c a l V a r i a b l e s
63C-----------------------------------------------
64 INTEGER I, J, K, N ,NELC , NELTG , IP , NPRT , IPRT
65 INTEGER IH3D,NG,ITY,NFT,IKEY,K_LEN,ID_INPUT,ID,NH3D_P
66
67 INTEGER :: NKPART(NPART,3),NOPART(3)
68 CHARACTER(LEN=NCHARKEY) :: KEY2
69 CHARACTER(LEN=NCHARKEY) :: KEY3
70 CHARACTER(LEN=NCHARKEY) :: KEY4
71 CHARACTER(LEN=NCHARKEY) :: KEY5
72C-----------------------------------------------
73C S o u r c e L i n e s
74C-----------------------------------------------
75C------- IPART_OK(NGROUP,1) for GPS_PART,IPART_OK(NGROUP,2) for GPSRA_PART
76 IF (ALLOCATED(ipart_ok)) DEALLOCATE(ipart_ok)
77 ALLOCATE(ipart_ok(ngroup,2))
78 ipart_ok = 0
79 ncy_gps = 10
80 ncy_gpstr = 10
81 IF ((lmax_nsig+lmax_nstra)>0) THEN
82 IF (lmax_nsig>0) ALLOCATE(igpstag(numnod))
83 IF (lmax_nstra>0)ALLOCATE(igpstratag(numnod))
84 nkpart(1:npart,1:3) = 0
85 nopart(1:3) = 1
86 DO id_input=1,h3d_data%N_INPUT_H3D
87c
88 key2 = h3d_data%INPUT_LIST(id_input)%KEY2
89 key3 = h3d_data%INPUT_LIST(id_input)%KEY3
90 key4 = h3d_data%INPUT_LIST(id_input)%KEY4
91 key5 = h3d_data%INPUT_LIST(id_input)%KEY5
92 IF ( key2=='PART' ) THEN
93 id = 3
94 nopart(id) = 0
95 ELSEIF ( key3=='GPS'.AND. key4=='TMAX') THEN
96 id = 1
97 nopart(id) = 0
98 IF (key5/=' ') READ (key5(3:12),'(I10)',err=100) ncy_gps
99 ELSEIF ( key3=='GPSTRAIN'.AND. key4=='TMAX') THEN
100 id = 2
101 nopart(id) = 0
102 IF (key5/=' ') READ (key5(3:12),'(I10)',err=100) ncy_gpstr
103 ELSE
104 id = 0
105 END IF
106 IF ( id > 0 ) THEN
107 nh3d_p = h3d_data%INPUT_LIST(id_input)%NB_PART
108 IF (nh3d_p==0) THEN
109 nkpart(1:npart,id) = 1
110 ELSE
111 DO j=1,nh3d_p
112 ip = h3d_data%INPUT_LIST(id_input)%PART_LIST(j)
113 DO k=1,npart
114 IF(ip == ipart(4,k)) nkpart(k,id)=1
115 END DO
116 END DO
117 END IF
118 END IF
119 END DO
120c
121 DO id=1,3
122 IF ( nopart(id)>0 ) nkpart(1:npart,id)=1
123 END DO
124 DO id=1,2
125 nkpart(1:npart,id)=nkpart(1:npart,3)*nkpart(1:npart,id)
126 END DO
127 DO ng=1,ngroup
128 IF (iparg(8,ng)==1) cycle
129 nft=iparg(3,ng)+1
130 ity=iparg(5,ng)
131C
132 iprt = 0
133 SELECT CASE (ity)
134 CASE(1)
135 iprt = iparts(nft)
136 CASE(3)
137 iprt = ipartc(nft)
138 CASE(7)
139 iprt = ipartg(nft)
140 END SELECT
141 IF(iprt>0) ipart_ok(ng,1:2) = nkpart(iprt,1:2)
142 END DO
143 END IF
144
145 RETURN
146100 CALL ancmsg(msgid=277,c1=key2//'/'//key3//'/'//key4//'/'//key5,anmode=aninfo)
initmumps id
integer, parameter ncharkey
integer, dimension(:), allocatable igpstratag
Definition outmax_mod.F:71
integer ncy_gpstr
Definition outmax_mod.F:66
integer, dimension(:,:), allocatable ipart_ok
Definition outmax_mod.F:72
integer, dimension(:), allocatable igpstag
Definition outmax_mod.F:71
integer lmax_nstra
Definition outmax_mod.F:63
integer lmax_nsig
Definition outmax_mod.F:62
integer ncy_gps
Definition outmax_mod.F:66
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