OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
mumps_fac_descband_data_m Module Reference

Data Types

type  descband_struc_t

Functions/Subroutines

subroutine, public mumps_fdbd_init (initial_size, info)
logical function, public mumps_fdbd_is_descband_stored (inode, iwhandler)
subroutine, public mumps_fdbd_save_descband (inode, lbufr, bufr, iwhandler, info)
subroutine, public mumps_fdbd_retrieve_descband (iwhandler, descband_struc)
subroutine, public mumps_fdbd_free_descband_struc (iwhandler)
subroutine, public mumps_fdbd_end (info1)

Variables

integer, save, public inode_waited_for
type(descband_struc_t), dimension(:), pointer, save fdbd_array

Function/Subroutine Documentation

◆ mumps_fdbd_end()

subroutine, public mumps_fac_descband_data_m::mumps_fdbd_end ( integer, intent(in) info1)

Definition at line 128 of file fac_descband_data_m.F.

129 INTEGER, INTENT(IN) :: INFO1
130 INTEGER :: I, IWHANDLER
131 IF (.NOT. associated(fdbd_array)) THEN
132 WRITE(*,*) "Internal error 1 in MUMPS_FAC_FDBD_END"
133 CALL mumps_abort()
134 ENDIF
135 DO i=1, size(fdbd_array)
136 IF (fdbd_array(i)%INODE .GE. 0) THEN
137 IF (info1 .GE.0) THEN
138 WRITE(*,*) "Internal error 2 in MUMPS_FAC_FDBD_END",i
139 CALL mumps_abort()
140 ELSE
141 iwhandler=i
142 CALL mumps_fdbd_free_descband_struc(iwhandler)
143 ENDIF
144 ENDIF
145 ENDDO
146 DEALLOCATE(fdbd_array)
147 RETURN
#define mumps_abort
Definition VE_Metis.h:25

◆ mumps_fdbd_free_descband_struc()

subroutine, public mumps_fac_descband_data_m::mumps_fdbd_free_descband_struc ( integer, intent(inout) iwhandler)

Definition at line 116 of file fac_descband_data_m.F.

118 INTEGER, INTENT(INOUT) :: IWHANDLER
119 TYPE (DESCBAND_STRUC_T), POINTER :: DESCBAND_STRUC
120 descband_struc => fdbd_array(iwhandler)
121 descband_struc%INODE = -7777
122 descband_struc%LBUFR = -7777
123 DEALLOCATE(descband_struc%BUFR)
124 NULLIFY(descband_struc%BUFR)
125 CALL mumps_fdm_end_idx('A', 'DESCBAND', iwhandler)
126 RETURN
subroutine, public mumps_fdm_end_idx(what, from, iwhandler)

◆ mumps_fdbd_init()

subroutine, public mumps_fac_descband_data_m::mumps_fdbd_init ( integer, intent(in) initial_size,
integer, dimension(2), intent(inout) info )

Definition at line 30 of file fac_descband_data_m.F.

31 INTEGER, INTENT(IN) :: INITIAL_SIZE
32 INTEGER, INTENT(INOUT) :: INFO(2)
33 INTEGER :: I, IERR
34 ALLOCATE(fdbd_array( initial_size ), stat=ierr)
35 IF (ierr > 0 ) THEN
36 info(1)=-13
37 info(2)=initial_size
38 RETURN
39 ENDIF
40 DO i=1, initial_size
41 fdbd_array(i)%INODE=-9999
42 fdbd_array(i)%LBUFR=-9999
43 NULLIFY(fdbd_array(i)%BUFR)
44 ENDDO
45 inode_waited_for = -1
46 RETURN

◆ mumps_fdbd_is_descband_stored()

logical function, public mumps_fac_descband_data_m::mumps_fdbd_is_descband_stored ( integer, intent(in) inode,
integer, intent(out) iwhandler )

Definition at line 48 of file fac_descband_data_m.F.

49 LOGICAL :: MUMPS_FDBD_IS_DESCBAND_STORED
50 INTEGER, INTENT(IN) :: INODE
51 INTEGER, INTENT(OUT) :: IWHANDLER
52 INTEGER :: I
53 DO i = 1, size(fdbd_array)
54 IF (fdbd_array(i)%INODE .EQ. inode) THEN
55 iwhandler = i
56 mumps_fdbd_is_descband_stored = .true.
57 RETURN
58 ENDIF
59 ENDDO
60 mumps_fdbd_is_descband_stored = .false.
61 RETURN

◆ mumps_fdbd_retrieve_descband()

subroutine, public mumps_fac_descband_data_m::mumps_fdbd_retrieve_descband ( integer, intent(in) iwhandler,
type (descband_struc_t), pointer descband_struc )

Definition at line 106 of file fac_descband_data_m.F.

107 INTEGER, INTENT(IN) :: IWHANDLER
108#if defined(MUMPS_F2003)
109 TYPE (DESCBAND_STRUC_T), POINTER, INTENT(OUT) :: DESCBAND_STRUC
110#else
111 TYPE (DESCBAND_STRUC_T), POINTER :: DESCBAND_STRUC
112#endif
113 descband_struc => fdbd_array(iwhandler)
114 RETURN

◆ mumps_fdbd_save_descband()

subroutine, public mumps_fac_descband_data_m::mumps_fdbd_save_descband ( integer, intent(in) inode,
integer, intent(in) lbufr,
integer, dimension(lbufr), intent(in) bufr,
integer, intent(out) iwhandler,
integer, dimension(2), intent(inout) info )

Definition at line 63 of file fac_descband_data_m.F.

66 INTEGER, INTENT(IN) :: INODE, LBUFR, BUFR(LBUFR)
67 INTEGER, INTENT(INOUT) :: INFO(2)
68 INTEGER, INTENT(OUT) :: IWHANDLER
69 TYPE(DESCBAND_STRUC_T), POINTER, DIMENSION(:) :: FDBD_ARRAY_TMP
70 INTEGER :: OLD_SIZE, NEW_SIZE, I, IERR
71 iwhandler = -1
72 CALL mumps_fdm_start_idx('A', 'DESCBAND', iwhandler, info)
73 IF (info(1) .LT. 0) RETURN
74 IF (iwhandler > size(fdbd_array)) THEN
75 old_size = size(fdbd_array)
76 new_size = max( (old_size * 3) / 2 + 1, iwhandler)
77 ALLOCATE(fdbd_array_tmp(new_size),stat=ierr)
78 IF (ierr.GT.0) THEN
79 info(1)=-13
80 info(2)=new_size
81 RETURN
82 ENDIF
83 DO i=1, old_size
84 fdbd_array_tmp(i)=fdbd_array(i)
85 ENDDO
86 DO i=old_size+1, new_size
87 fdbd_array_tmp(i)%INODE = -9999
88 fdbd_array_tmp(i)%LBUFR = -9999
89 NULLIFY(fdbd_array_tmp(i)%BUFR)
90 ENDDO
91 DEALLOCATE(fdbd_array)
92 fdbd_array=>fdbd_array_tmp
93 NULLIFY(fdbd_array_tmp)
94 ENDIF
95 fdbd_array(iwhandler)%INODE = inode
96 fdbd_array(iwhandler)%LBUFR = lbufr
97 ALLOCATE(fdbd_array(iwhandler)%BUFR(lbufr), stat=ierr)
98 IF (ierr > 0 ) THEN
99 info(1)=-13
100 info(2)=lbufr
101 RETURN
102 ENDIF
103 fdbd_array(iwhandler)%BUFR = bufr
104 RETURN
#define max(a, b)
Definition macros.h:21
subroutine, public mumps_fdm_start_idx(what, from, iwhandler, info)

Variable Documentation

◆ fdbd_array

type (descband_struc_t), dimension(:), pointer, save mumps_fac_descband_data_m::fdbd_array

Definition at line 28 of file fac_descband_data_m.F.

28 TYPE (DESCBAND_STRUC_T), POINTER, DIMENSION(:), SAVE::FDBD_ARRAY

◆ inode_waited_for

integer, save, public mumps_fac_descband_data_m::inode_waited_for

Definition at line 17 of file fac_descband_data_m.F.

17 INTEGER, SAVE :: INODE_WAITED_FOR