OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
write_th.F File Reference
#include "implicit_f.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine write_th (n, nspmd, nn, nvar, ittyp, eltype_struct, wa_eltype_p0)

Function/Subroutine Documentation

◆ write_th()

subroutine write_th ( integer, intent(in) n,
integer, intent(in) nspmd,
integer, intent(in) nn,
integer, intent(in) nvar,
integer, intent(in) ittyp,
type(th_proc_type), intent(in) eltype_struct,
type(th_wa_real), intent(in) wa_eltype_p0 )

Definition at line 32 of file write_th.F.

34 USE th_mod
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C D u m m y A r g u m e n t s
41C-----------------------------------------------
42 INTEGER, INTENT(in) :: N,NSPMD,NN,NVAR,ITTYP
43 TYPE(TH_WA_REAL), INTENT(in) ::WA_ELTYPE_P0
44 TYPE(TH_PROC_TYPE), INTENT(in) :: ELTYPE_STRUCT
45! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
46! N : integer ; current TH group
47! NSPMD : integer ; number of MPI domains
48! NN : integer, number of element group
49! NVAR : integer ; number of value per element group
50! ITTYP : integer ; type of TH group
51! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 LOGICAL :: BOOL
56 INTEGER :: I,J,K,II,IJK,LOCAL_SIZE
57 INTEGER :: NEXT,CURRENT,SIZE_N
58 INTEGER :: CURRENT_J,REST
59 my_real, DIMENSION(:), ALLOCATABLE :: wa_local
60! ----------------------------------------
61!$COMMENT
62! WRITE_TH_COQ description
63! write all the values for shell element
64! and for a given group N by the PROC0
65!
66! WRITE_TH_COQ organization :
67! * loop over the NSPMD processor and:
68! - check if a processor must write its values (SIZE_N>0)
69! - compute the number of group for a given processor (REST)
70! - compute the position in the TH file (CURRENT_J)
71! - initialization of the written values WA_LOCAL with the position CURRENT_J + J
72! * write the WA_LOCAL values
73!$ENDCOMMENT
74
75! allocation + initialization of local array
76 ALLOCATE( wa_local(nn*nvar) )
77 wa_local(1:nn*nvar) = zero
78
79
80
81 DO i=1,nspmd
82 local_size = eltype_struct%TH_PROC(i)%TH_ELM_SIZE
83 bool=.true.
84 DO k=1,local_size
85 IF(bool.EQV..true.) THEN
86 IF(eltype_struct%TH_PROC(i)%TH_ELM(k,2)==n) THEN
87 bool=.false.
88 ijk=k
89 ENDIF
90 ENDIF
91 ENDDO
92 IF(bool.EQV..false.) THEN
93 current = eltype_struct%TH_PROC(i)%TH_ELM(ijk,1) ! index of the current proc and N
94 next = eltype_struct%TH_PROC(i)%TH_ELM(ijk+1,1) ! index of the next proc and n
95 size_n = next-current ! nbr of WA element of the current proc and for the current N
96! IF( SIZE_N>0 ) THEN ! if SIZE_N>0, must write some data
97 rest = size_n / (nvar+1) ! nbr of th group for the current proc
98 ii = 0
99 DO k=1,rest
100 current_j = nint(wa_eltype_p0%WA_REAL( current+k*(nvar+1) ) ) ! the position in WA_LOCAL for the current TH
101 DO j=1,nvar
102 ii = ii + 1
103 wa_local(current_j+j) = wa_eltype_p0%WA_REAL(current+ii)
104 ENDDO
105 ii = ii + 1 ! skip the NVAR+1 value = the position in WA_LOCAL
106 ENDDO
107! ENDIF
108 ENDIF
109 ENDDO
110
111! write the data
112 CALL wrtdes(wa_local,wa_local,nn*nvar,ittyp,1)
113! deallocation
114 DEALLOCATE( wa_local )
115
116! ----------------------------------------
117 RETURN
#define my_real
Definition cppsort.cpp:32
end diagonal values have been computed in the(sparse) matrix id.SOL
integer function nvar(text)
Definition nvar.F:32
subroutine wrtdes(a, ia, l, iform, ir)
Definition wrtdes.F:45