SPEED
MAKE_ELTENSOR_FOR_CASES_NLE.f90 File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine make_eltensor_for_cases_nle (vcase, r_el, nn, rho_el, lambda_el, mu_el, gamma_el, cs_nnz, cs, ielem, func_type, func_indx, func_data, nfdata, nf, t_stress, tag_func, yon, tcase, nnod_loc, vs_tria)
 Assignes material properties node by node for non linear elasticity.
 

Function/Subroutine Documentation

◆ make_eltensor_for_cases_nle()

subroutine make_eltensor_for_cases_nle ( integer*4  vcase,
real*8, dimension(nn,nn,nn)  r_el,
integer*4  nn,
real*8, dimension(nn,nn,nn)  rho_el,
real*8, dimension(nn,nn,nn)  lambda_el,
real*8, dimension(nn,nn,nn)  mu_el,
real*8, dimension(nn,nn,nn)  gamma_el,
integer*4  cs_nnz,
integer*4, dimension(0:cs_nnz)  cs,
integer*4  ielem,
integer*4, dimension(nf)  func_type,
integer*4, dimension(nf +1)  func_indx,
real*8, dimension(nfdata)  func_data,
integer*4  nfdata,
integer*4  nf,
real*8  t_stress,
integer*4, dimension(nf)  tag_func,
integer*4, dimension(nn,nn,nn)  yon,
integer*4  tcase,
integer*4  nnod_loc,
real*8, dimension(nnod_loc)  vs_tria 
)

Assignes material properties node by node for non linear elasticity.

Author
Ilario Mazzieri
Date
September, 2013
Version
1.0
Parameters
[in]vcasevalue case for non linear block
[in]R_elreduction factor
[in]nnpolynomial degree
[in]cs_nnzlength of cs
[in]csconnectivity vector
[in]ielemelement index
[in]nfnumber of functions
[in]func_typefunction type
[in]func_indxindices for the data
[in]func_data(*)data for the calculation (depending on type)
[in]t_stresstime
[in]tag_funclabels for functions
[in]yonis the node nonlinear elastic yes (1) or not (0)?
[in]nnod_locnumber of local nodes
[in]vs_triavs values for each node
[out]rho_elmaterial density
[out]lambda_elLame coefficient lambda
[out]mu_elLame coefficient mu
[out]gamma_eldamping coefficient gamma

Definition at line 44 of file MAKE_ELTENSOR_FOR_CASES_NLE.f90.

50
51
52
53 implicit none
54
55 integer*4 :: vcase
56 integer*4 :: nn
57 integer*4 :: p,q,r
58 integer*4 :: is,in,ielem
59 integer*4 :: cs_nnz
60 integer*4 :: nf,fn,nfdata,tcase,nnod_loc
61
62 integer*4, dimension(nf) :: tag_func
63 integer*4, dimension(nf) :: func_type
64 integer*4, dimension(nf +1) :: func_indx
65 integer*4, dimension(0:cs_nnz) :: cs
66
67 integer*4, dimension(nn,nn,nn) :: yon
68
69 real*8 :: vs,vp
70 real*8 :: vratio
71 real*8 :: t_stress
72 real*8 :: get_func_value
73 real*8 :: reduction_factor
74
75 real*8, dimension(nfdata) :: func_data
76 real*8, dimension(nnod_loc) :: vs_tria
77
78 real*8, dimension(nn,nn,nn) :: rho_el,lambda_el,mu_el,gamma_el
79 real*8, dimension(nn,nn,nn) :: r_el
80
81
82
83
84 do r = 1,nn
85 do q = 1,nn
86 do p = 1,nn
87
88 is = nn*nn*(r -1) +nn*(q -1) +p
89 in = cs(cs(ielem -1) +is)
90
91 if (yon(p,q,r).eq.1) then
92
93 vs = dsqrt( mu_el(p,q,r) / rho_el(p,q,r) )
94 vp = dsqrt( (lambda_el(p,q,r) + 2*mu_el(p,q,r) ) / rho_el(p,q,r) )
95 vratio = vp/vs
96
97 !-------------------------------------------------------------------
98 !
99 if(tcase .ne. 16) then
100 do fn = 1,nf
101 if (vcase .eq. tag_func(fn)) then
102 if (func_type(fn) .eq. 60 ) then
103
104 reduction_factor = get_func_value(nf,func_type,func_indx,func_data, nfdata, &
105 fn,r_el(p,q,r),0,0)
106
107 mu_el(p,q,r) = mu_el(p,q,r) * reduction_factor
108 vs = dsqrt(mu_el(p,q,r)/rho_el(p,q,r))
109 vp = vs * vratio
110 lambda_el(p,q,r)= rho_el(p,q,r)*(vp**2)-2*mu_el(p,q,r)
111
112 endif
113 endif
114 enddo
115
116 elseif (tcase .eq. 16) then
117
118 do fn = 1,nf
119 if (vcase .eq. tag_func(fn)) then
120 if (func_type(fn) .eq. 60 .and. vs_tria(in) .lt. 325.d0) then
121
122 reduction_factor = get_func_value(nf,func_type,func_indx,func_data, nfdata, &
123 fn,r_el(p,q,r),0,0)
124
125 mu_el(p,q,r) = mu_el(p,q,r) * reduction_factor
126 vs = dsqrt(mu_el(p,q,r)/rho_el(p,q,r))
127 vp = vs * vratio
128 lambda_el(p,q,r)= rho_el(p,q,r)*(vp**2)-2*mu_el(p,q,r)
129
130 elseif (func_type(fn) .eq. 62 .and. vs_tria(in) .lt. 450.d0) then
131
132 reduction_factor = get_func_value(nf,func_type,func_indx,func_data, nfdata, &
133 fn,r_el(p,q,r),0,0)
134
135 mu_el(p,q,r) = mu_el(p,q,r) * reduction_factor
136 vs = dsqrt(mu_el(p,q,r)/rho_el(p,q,r))
137 vp = vs * vratio
138 lambda_el(p,q,r)= rho_el(p,q,r)*(vp**2)-2*mu_el(p,q,r)
139
140
141
142 endif
143
144 endif
145 enddo
146
147 endif!tcase = 16
148
149
150 !
151 !-------------------------------------------------------------------
152
153 endif !if (yon(i,j,k).eq.1) then
154
155 enddo
156 enddo
157 enddo
158
159 return
160
real *8 function get_func_value(nb_fnc, type_fnc, ind_fnc, data_fnc, nb_data_fnc, id_fnc, time
Computes time evolution function.

References get_func_value().

Here is the call graph for this function: