OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
stat_n_temp.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "task_c.inc"
#include "scr14_c.inc"
#include "spmd_c.inc"
#include "com01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine stat_n_temp (x, numnod, itab, itabg, leng, nodglob, weight, nodtag, temp, itherm_fe)

Function/Subroutine Documentation

◆ stat_n_temp()

subroutine stat_n_temp ( x,
integer numnod,
integer, dimension(*) itab,
integer, dimension(*) itabg,
integer leng,
integer, dimension(*) nodglob,
integer, dimension(*) weight,
integer, dimension(*) nodtag,
temp,
integer, intent(in) itherm_fe )

Definition at line 33 of file stat_n_temp.F.

35C-----------------------------------------------
36C M o d u l e s
37C-----------------------------------------------
38 USE my_alloc_mod
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "units_c.inc"
47#include "task_c.inc"
48#include "scr14_c.inc"
49#include "spmd_c.inc"
50#include "com01_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER ITAB(*), NUMNOD,WEIGHT(*),ITABG(*),LENG,
55 . NODGLOB(*),NODTAG(*)
56 INTEGER ,intent(in) :: ITHERM_FE
58 . x(3,*),temp(*)
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I
63 INTEGER,DIMENSION(:),ALLOCATABLE::NODTAGLOB
64 my_real,DIMENSION(:),ALLOCATABLE::tempg
65 CHARACTER*100 LINE
66C-----------------------------------------------
67 CALL my_alloc(nodtaglob,leng)
68 CALL my_alloc(tempg,leng)
69C-----------------------------------------------
70 IF (itherm_fe == 0) RETURN
71
72 IF (nspmd > 1) THEN
73 CALL spmd_dstat_gath(temp,nodglob,weight,tempg,nodtag,
74 . nodtaglob)
75 IF (ispmd/=0) RETURN
76 ENDIF
77
78 IF (izipstrs == 0) THEN
79 WRITE(iugeo,'(A)')'/INITEMP/1'
80 WRITE(iugeo,'(A)')'INITIAL TEMPERATURE'
81 WRITE(iugeo,'(2A)')'# TEMP NODID'
82 WRITE(iugeo,'(A)')' 1'
83 ELSE
84 WRITE(line,'(A)')'/INITEMP/1'
85 CALL strs_txt50(line,100)
86 WRITE(line,'(A)')'INITIAL TEMPERATURE'
87 CALL strs_txt50(line,100)
88 WRITE(line,'(A)')
89 . '# TEMP NODID'
90 CALL strs_txt50(line,100)
91 WRITE(line,'(A)')' 1'
92 CALL strs_txt50(line,100)
93 ENDIF
94
95 IF (nspmd == 1) THEN
96 DO i=1,numnod
97 IF(nodtag(i) /= 0) THEN
98 IF (izipstrs == 0) THEN
99 WRITE(iugeo,'(1PE20.13,I10)')
100 . temp(i),itab(i)
101 ELSE
102 WRITE(line,'(1PE20.13,I10)')
103 . temp(i),itab(i)
104 CALL strs_txt50(line,100)
105 END IF
106 END IF
107 END DO
108 ELSE
109 DO i=1,numnodg
110 IF(nodtaglob(i) /= 0)THEN
111 IF (izipstrs == 0) THEN
112 WRITE(iugeo,'(1pe20.13,i10)')
113 . TEMPG(I),ITABG(I)
114 ELSE
115 WRITE(LINE,'(1pe20.13,i10)')
116 . TEMPG(I),ITABG(I)
117 CALL STRS_TXT50(LINE,100)
118 END IF
119 END IF
120 END DO
121 ENDIF
122C-----------------------------------------------
123 DEALLOCATE(NODTAGLOB)
124 DEALLOCATE(TEMPG)
125C-----------------------------------------------
126 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine spmd_dstat_gath(v, nodglob, weight, vgath, nodtag, nodtaglob)
Definition spmd_stat.F:330
subroutine strs_txt50(text, length)
Definition sta_txt.F:87