SPEED
COMPUTE_SDOF_INPUT.f90 File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine compute_sdof_input (sdof_num, mpi_id, elem_mlst, local_el_num, ne_loc, cs_loc, cs_nnz_loc, sdeg_mat, nmat, u2, nnod_loc, xr_mlst, yr_mlst, zr_mlst, dt2, sdofinputab, sdofinputdispl, mpi_np, ub1, ub2, ub3)
 Computes acceleration of sdof systems.
 

Function/Subroutine Documentation

◆ compute_sdof_input()

subroutine compute_sdof_input ( integer*4  sdof_num,
integer*4  mpi_id,
integer*4, dimension(sdof_num)  elem_mlst,
integer*4, dimension(ne_loc)  local_el_num,
integer*4  ne_loc,
integer*4, dimension(0:cs_nnz_loc)  cs_loc,
integer*4  cs_nnz_loc,
integer*4, dimension(nmat)  sdeg_mat,
integer*4  nmat,
real*8, dimension(3*nnod_loc)  u2,
integer*4  nnod_loc,
real*8, dimension(sdof_num)  xr_mlst,
real*8, dimension(sdof_num)  yr_mlst,
real*8, dimension(sdof_num)  zr_mlst,
real*8  dt2,
real*8, dimension(3*sdof_num)  sdofinputab,
real*8, dimension(3*sdof_num)  sdofinputdispl,
integer*4  mpi_np,
real*8, dimension(3*sdof_num)  ub1,
real*8, dimension(3*sdof_num)  ub2,
real*8, dimension(3*sdof_num)  ub3 
)

Computes acceleration of sdof systems.

Author
Aline Herlin
Date
November, 2020
Version
1.0
Parameters
[in]sdof_numnumber of oscillators
[in]mpi_idprocess id
[in]elem_mlstlist of monitored elements
[in]local_el_numlocal element numbering
[in]ne_locnumber of local elements
[in]cs_locconnectivity vector
[in]cs_nnz_loclength of cs_loc
[in]sdeg_matspectral degree of materials
[in]nmatnumber of materials
[in]u2soil displacement at time n+1
[in]nnod_locnumber of local nodes
[in]xr_mlst,yr_mlst,zr_mlstoscillators coordinates
[in]dt2time step square
[in]mpi_nptotal number of mpi processes
[out]ub1,ub2,ub3base displacement at time n+1,n,n-1
[out]SDOFinputabbase acceleration
[out]SDOFinputdisplbase displacement

Definition at line 41 of file COMPUTE_SDOF_INPUT.f90.

48
49 implicit none
50
51 integer*4 :: imon, ielem, ie, im, nn, k, j, i, is, in, iaz, sdof_num, ishift
52 integer*4 :: mpi_id, ne_loc, nmat, nnod_loc, cs_nnz_loc, mpi_np
53 integer*4 :: nmpi
54 integer*4, dimension(0:cs_nnz_loc) :: cs_loc
55 integer*4, dimension(sdof_num) :: elem_mlst
56 integer*4, dimension(nmat) :: sdeg_mat
57 integer*4, dimension(ne_loc) :: local_el_num
58 real*8 :: dt2
59 real*8 :: uxm,uym,uzm
60 real*8 :: axm,aym,azm
61 real*8, dimension(:), allocatable :: ct, ww
62 real*8, dimension(:,:), allocatable :: dd
63 real*8, dimension(:,:,:), allocatable :: ux_el, uy_el, uz_el
64 real*8, dimension(3*nnod_loc) :: u2
65 real*8, dimension(sdof_num) ::xr_mlst, yr_mlst, zr_mlst
66 real*8, dimension(3*sdof_num) :: sdofinputab, sdofinputdispl, ub1, ub2, ub3
67
68 ub3(1:3*sdof_num)=ub2(1:3*sdof_num)
69 ub2(1:3*sdof_num)=ub1(1:3*sdof_num)
70
71 ishift = 0
72
73 do imon = 1,sdof_num !!! loop over the oscillators
74
75 ielem = elem_mlst(imon)
76 call get_indloc_from_indglo(local_el_num, ne_loc, ielem, ie)
77 if (ie .ne. 0) then
78 im = cs_loc(cs_loc(ie -1) +0) !!! material
79 nn = sdeg_mat(im) +1 !!! n of quadrature nodes
80
81 allocate(ct(nn),ww(nn),dd(nn,nn))
82 allocate(ux_el(nn,nn,nn),uy_el(nn,nn,nn),uz_el(nn,nn,nn))
83
84 call make_lgl_nw(nn,ct,ww,dd)
85
86 do k = 1,nn
87 do j = 1,nn
88 do i = 1,nn
89 is = nn*nn*(k -1) +nn*(j -1) +i
90 in = cs_loc(cs_loc(ie -1) + is)
91
92 iaz = 3*(in -1) +1; ux_el(i,j,k) = u2(iaz)
93 iaz = 3*(in -1) +2; uy_el(i,j,k) = u2(iaz)
94 iaz = 3*(in -1) +3; uz_el(i,j,k) = u2(iaz)
95
96 enddo
97 enddo
98 enddo
99
100 !-------------------------------------------------------------
101 ! ACCELERATION AND SOIL FORCES
102 !-------------------------------------------------------------
103 call get_monitor_value(nn,ct,ux_el,&
104 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),uxm)
105 call get_monitor_value(nn,ct,uy_el,&
106 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),uym)
107 call get_monitor_value(nn,ct,uz_el,&
108 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),uzm)
109
110 if (dabs(uxm).lt.1.0e-30) uxm = 0.0e+00
111 if (dabs(uym).lt.1.0e-30) uym = 0.0e+00
112 if (dabs(uzm).lt.1.0e-30) uzm = 0.0e+00
113
114 ub1(ishift+1) = uxm !!! x displacement at the base of the structure at time n+1
115 ub1(ishift+2) = uym !!! y displacement at the base of the structure at time n+1
116 ub1(ishift+3) = uzm !!! z displacement at the base of the structure at time n+1
117
118 ! Central Difference Scheme
119 axm = (ub1(ishift+1) -2.0d0*ub2(ishift+1) +ub3(ishift+1)) / dt2
120 aym = (ub1(ishift+2) -2.0d0*ub2(ishift+2) +ub3(ishift+2)) / dt2
121 azm = (ub1(ishift+3) -2.0d0*ub2(ishift+3) +ub3(ishift+3)) / dt2
122
123 if (dabs(axm).lt.1.0e-30) axm = 0.0e+00
124 if (dabs(aym).lt.1.0e-30) aym = 0.0e+00
125 if (dabs(azm).lt.1.0e-30) azm = 0.0e+00
126
127 do nmpi=1,mpi_np
128 if (mpi_id .eq. (nmpi-1)) then
129 sdofinputab(3*imon-2)=axm
130 sdofinputab(3*imon-1)=aym
131 sdofinputab(3*imon)=azm
132 sdofinputdispl(3*imon-2)=uxm
133 sdofinputdispl(3*imon-1)=uym
134 sdofinputdispl(3*imon)=uzm
135 endif
136 enddo
137
138 deallocate(ct,ww,dd)
139 deallocate(ux_el,uy_el,uz_el)
140
141 ishift = ishift + 3
142 endif !(ie .ne. 0)
143 enddo
144
145 return
146
subroutine get_indloc_from_indglo(local_el, nel_loc, ie, ic)
Returns local id from global id.
subroutine get_monitor_value(nb_nod, xq, val, xref, yref, zref, re
Computes the mean value.
subroutine make_lgl_nw(nb_pnt, xq, wq, dd)
Makes Gauss-Legendre-Lobatto nodes, weigths and spectral derivatives.

References get_indloc_from_indglo(), get_monitor_value(), and make_lgl_nw().

Here is the call graph for this function: