Skip to content

Commit

Permalink
ran the MFC format command for PR
Browse files Browse the repository at this point in the history
  • Loading branch information
mrodrig6 committed Dec 21, 2024
1 parent 25bf4fe commit ab772fd
Show file tree
Hide file tree
Showing 9 changed files with 177 additions and 177 deletions.
10 changes: 5 additions & 5 deletions src/common/m_variables_conversion.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1044,11 +1044,11 @@ contains

#ifdef MFC_POST_PROCESS
if (hyperelasticity) then
! to save von Mises stress instead of elastic internal energy
qK_prim_vf(xiend+1)%sf(j, k, l) = sqrt((3_wp/2_wp)* (qK_prim_vf(strxb)%sf(j, k, l)**2_wp + &
2_wp*qK_prim_vf(strxb+1)%sf(j, k, l)**2_wp + qK_prim_vf(strxb+2)%sf(j, k, l)**2_wp + &
2_wp*qK_prim_vf(strxb+3)%sf(j, k, l)**2_wp + 2_wp*qK_prim_vf(strxb+4)%sf(j, k, l)**2_wp + &
qK_prim_vf(strxe)%sf(j, k, l)**2_wp) )
! to save von Mises stress instead of elastic internal energy
qK_prim_vf(xiend + 1)%sf(j, k, l) = sqrt((3_wp/2_wp)*(qK_prim_vf(strxb)%sf(j, k, l)**2_wp + &
2_wp*qK_prim_vf(strxb + 1)%sf(j, k, l)**2_wp + qK_prim_vf(strxb + 2)%sf(j, k, l)**2_wp + &
2_wp*qK_prim_vf(strxb + 3)%sf(j, k, l)**2_wp + 2_wp*qK_prim_vf(strxb + 4)%sf(j, k, l)**2_wp + &
qK_prim_vf(strxe)%sf(j, k, l)**2_wp))
end if
#endif

Expand Down
22 changes: 11 additions & 11 deletions src/post_process/m_start_up.f90
Original file line number Diff line number Diff line change
Expand Up @@ -369,7 +369,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)
! Adding the elastic shear stresses to the formatted database file -----
if (elasticity) then
if (prim_vars_wrt) then
do i = 1, stress_idx%end - stress_idx%beg + 1
do i = 1, stress_idx%end - stress_idx%beg + 1
q_sf = q_prim_vf(i - 1 + stress_idx%beg)%sf( &
-offset_x%beg:m + offset_x%end, &
-offset_y%beg:n + offset_y%end, &
Expand All @@ -378,12 +378,12 @@ subroutine s_save_data(t_step, varname, pres, c, H)
call s_write_variable_to_formatted_database_file(varname, t_step)

varname(:) = ' '
end do
end do
end if
end if
if (hyperelasticity) then
if (prim_vars_wrt) then
do i = 1, xiend - xibeg + 1
do i = 1, xiend - xibeg + 1
q_sf = q_prim_vf(i - 1 + xibeg)%sf( &
-offset_x%beg:m + offset_x%end, &
-offset_y%beg:n + offset_y%end, &
Expand All @@ -392,16 +392,16 @@ subroutine s_save_data(t_step, varname, pres, c, H)
call s_write_variable_to_formatted_database_file(varname, t_step)

varname(:) = ' '
end do
end do

q_sf = q_prim_vf(xiend+1)%sf( &
-offset_x%beg:m + offset_x%end, &
-offset_y%beg:n + offset_y%end, &
-offset_z%beg:p + offset_z%end)
q_sf = q_prim_vf(xiend + 1)%sf( &
-offset_x%beg:m + offset_x%end, &
-offset_y%beg:n + offset_y%end, &
-offset_z%beg:p + offset_z%end)

write (varname, '(A,I0)') 'vonMises'
call s_write_variable_to_formatted_database_file(varname, t_step)
varname(:) = ' '
write (varname, '(A,I0)') 'vonMises'
call s_write_variable_to_formatted_database_file(varname, t_step)
varname(:) = ' '

end if
end if
Expand Down
30 changes: 15 additions & 15 deletions src/pre_process/include/3dHardcodedIC.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -59,37 +59,37 @@
q_prim_vf(advxb)%sf(i, j, k) = patch_icpp(1)%alpha(1)
q_prim_vf(advxe)%sf(i, j, k) = patch_icpp(1)%alpha(2)
end if

case (302) ! (3D lung geometry in X direction - axisym, with smoothing)
lam = 200.E-06_wp
lam = 200.e-06_wp
amp = patch_icpp(patch_id)%a2
h = 0.125_wp*amp

intH = amp/2._wp*(sin(2._wp*pi*y_cc(j)/lam + pi/2._wp) + sin(2._wp*pi*z_cc(k)/lam + pi/2._wp))
alph = patch_icpp(2)%alpha(1) + (patch_icpp(1)%alpha(1)-patch_icpp(2)%alpha(1))/(h)*(x_cc(i)-(intH-h/2._wp))

alph = patch_icpp(2)%alpha(1) + (patch_icpp(1)%alpha(1) - patch_icpp(2)%alpha(1))/(h)*(x_cc(i) - (intH - h/2._wp))

if (x_cc(i) > intH + h/2) then

q_prim_vf(advxb)%sf(i, j, k) = patch_icpp(1)%alpha(1)
q_prim_vf(advxe)%sf(i, j, k) = patch_icpp(1)%alpha(2)
q_prim_vf(contxb)%sf(i, j, k) = patch_icpp(1)%alpha_rho(1)
q_prim_vf(contxe)%sf(i, j, k) = patch_icpp(1)%alpha_rho(2)
q_prim_vf(E_idx)%sf(i, j, k) = patch_icpp(1)%pres
else if ((x_cc(i) .le. intH + h/2) .and. (x_cc(i) .ge. intH - h/2._wp)) then

else if ((x_cc(i) <= intH + h/2) .and. (x_cc(i) >= intH - h/2._wp)) then

q_prim_vf(advxb)%sf(i, j, k) = alph !0.5
q_prim_vf(advxe)%sf(i, j, k) = 1._wp - alph !0.5
q_prim_vf(contxb)%sf(i, j, k) = patch_icpp(1)%alpha_rho(1)/patch_icpp(1)%alpha(1)*alph!0.5
q_prim_vf(contxe)%sf(i, j, k) = patch_icpp(2)%alpha_rho(2)/patch_icpp(2)%alpha(2)*(1-alph)!0.5
q_prim_vf(contxe)%sf(i, j, k) = patch_icpp(2)%alpha_rho(2)/patch_icpp(2)%alpha(2)*(1 - alph)!0.5
q_prim_vf(E_idx)%sf(i, j, k) = patch_icpp(1)%pres

end if

case (303) ! pre_stress for hyperelasticity, bubble in material

R0ref = 30E-6_wp ! equilibrium radius
R0ref = 30e-6_wp ! equilibrium radius
Rinit = patch_icpp(3)%radius ! initial radius
x_bcen = patch_icpp(3)%x_centroid
y_bcen = patch_icpp(3)%y_centroid
Expand All @@ -101,7 +101,7 @@
phi = atan2(y_ccs, x_ccs)
theta = atan2(sqrt(x_ccs**2._wp + y_ccs**2._wp), z_ccs)
!spherical coord, assuming Rmax=1
xi_sph = (rcoord**3._wp - R0ref**3._wp + Rinit**3._wp)**(1._wp/3._wp)
xi_sph = (rcoord**3._wp - R0ref**3._wp + Rinit**3._wp)**(1._wp/3._wp)
xi_cart(1) = xi_sph*sin(theta)*cos(phi)
xi_cart(2) = xi_sph*sin(theta)*sin(phi)
xi_cart(3) = xi_sph*cos(theta)
Expand Down
6 changes: 3 additions & 3 deletions src/pre_process/m_assign_variables.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -498,10 +498,10 @@ contains
if (hyperelasticity .and. .not. pre_stress) then
xi_cart(1) = x_cc(j)
if (p > 0) then
xi_cart(2) = y_cc(k)
xi_cart(3) = z_cc(l)
xi_cart(2) = y_cc(k)
xi_cart(3) = z_cc(l)
elseif (n > 0) then
xi_cart(2) = y_cc(k)
xi_cart(2) = y_cc(k)
end if
! assigning the reference map to the q_prim vector field
Expand Down
8 changes: 4 additions & 4 deletions src/pre_process/m_patches.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1527,17 +1527,17 @@ contains

if (x_cc(i) - x_centroid >= 0 &
.and. &
r - as(2)*Ps(2) - as(3)*Ps(3) - as(4)*Ps(4) - as(5)*Ps(5) - as(6)*Ps(6) &
- as(7)*Ps(7) - as(8)*Ps(8) - as(9)*Ps(9) <= radius .and. &
r - as(2)*Ps(2) - as(3)*Ps(3) - as(4)*Ps(4) - as(5)*Ps(5) - as(6)*Ps(6) &
- as(7)*Ps(7) - as(8)*Ps(8) - as(9)*Ps(9) <= radius .and. &
patch_icpp(patch_id)%alter_patch(patch_id_fp(i, j, 0))) &
then
call s_assign_patch_primitive_variables(patch_id, i, j, 0, &
eta, q_prim_vf, patch_id_fp)

elseif (x_cc(i) - x_centroid < 0 &
.and. &
r - as(2)*Ps(2) + as(3)*Ps(3) - as(4)*Ps(4) + as(5)*Ps(5) - as(6)*Ps(6) &
+ as(7)*Ps(7) - as(8)*Ps(8) + as(9)*Ps(9) <= radius &
r - as(2)*Ps(2) + as(3)*Ps(3) - as(4)*Ps(4) + as(5)*Ps(5) - as(6)*Ps(6) &
+ as(7)*Ps(7) - as(8)*Ps(8) + as(9)*Ps(9) <= radius &
.and. &
patch_icpp(patch_id)%alter_patch(patch_id_fp(i, j, 0))) &
then
Expand Down
Loading

0 comments on commit ab772fd

Please sign in to comment.