@@ -314,11 +314,13 @@ contains
314314 !> Subroutine that computes bubble wall properties for vapor bubbles
315315 !! @param pb Internal bubble pressure
316316 !! @param iR0 Current bubble size index
317- subroutine s_bwproperty (pb , iR0 )
317+ pure elemental subroutine s_bwproperty(pb, iR0, chi_vw, k_mw, rho_mw )
318318 !$acc routine seq
319319 real (wp), intent (in ) :: pb
320320 integer , intent (in ) :: iR0
321-
321+ real (wp), intent (out ) :: chi_vw !< Bubble wall properties (Ando 2010 )
322+ real (wp), intent (out ) :: k_mw !< Bubble wall properties (Ando 2010 )
323+ real (wp), intent (out ) :: rho_mw !< Bubble wall properties (Ando 2010 )
322324 real (wp) :: x_vw
323325
324326 ! mass fraction of vapor
@@ -342,21 +344,21 @@ contains
342344 !! @param fbeta_c Mass transfer coefficient (EL)
343345 !! @param fR_m Mixture gas constant (EL)
344346 !! @param fgamma_m Mixture gamma (EL)
345- function f_vflux (fR , fV , fpb , fmass_v , iR0 , fmass_n , fbeta_c , fR_m , fgamma_m )
347+ pure elemental subroutine s_vflux (fR, fV, fpb, fmass_v, iR0, vflux , fmass_n, fbeta_c, fR_m, fgamma_m)
346348 !$acc routine seq
347349 real (wp), intent (in ) :: fR
348350 real (wp), intent (in ) :: fV
349351 real (wp), intent (in ) :: fpb
350352 real (wp), intent (in ) :: fmass_v
351353 integer , intent (in ) :: iR0
354+ real (wp), intent (out ) :: vflux
352355 real (wp), intent (in ), optional :: fmass_n, fbeta_c
353356 real (wp), intent (out ), optional :: fR_m, fgamma_m
354357
355358 real (wp) :: chi_bar
356359 real (wp) :: rho_mw_lag
357360 real (wp) :: grad_chi
358361 real (wp) :: conc_v
359- real (wp) :: f_vflux
360362
361363 if (thermal == 3 ) then !transfer
362364 ! constant transfer model
@@ -373,21 +375,21 @@ contains
373375 chi_bar = fmass_v/ (fmass_v + fmass_n)
374376 grad_chi = (chi_bar - conc_v)
375377 rho_mw_lag = (fmass_n + fmass_v)/ (4._wp / 3._wp * pi* fR** 3._wp )
376- f_vflux = 0._wp
378+ vflux = 0._wp
377379 if (lag_params%massTransfer_model) then
378- f_vflux = - fbeta_c* rho_mw_lag* grad_chi/ (1._wp - conc_v)/ fR
380+ vflux = - fbeta_c* rho_mw_lag* grad_chi/ (1._wp - conc_v)/ fR
379381 end if
380382 else
381383 chi_bar = fmass_v/ (fmass_v + mass_n0(iR0))
382384 grad_chi = - Re_trans_c(iR0)* (chi_bar - chi_vw)
383- f_vflux = rho_mw* grad_chi/ Pe_c/ (1._wp - chi_vw)/ fR
385+ vflux = rho_mw* grad_chi/ Pe_c/ (1._wp - chi_vw)/ fR
384386 end if
385387 else
386388 ! polytropic
387- f_vflux = pv* fV/ (R_v* Tw)
389+ vflux = pv* fV/ (R_v* Tw)
388390 end if
389391
390- end function f_vflux
392+ end subroutine s_vflux
391393
392394 !> Function that computes the time derivative of
393395 !! the internal bubble pressure
@@ -457,7 +459,7 @@ contains
457459 !! @param fbeta_t Heat transfer coefficient (EL)
458460 !! @param fCson Speed of sound (EL)
459461 !! @param adap_dt_stop Fail- safe exit if max iteration count reached
460- subroutine s_advance_step (fRho , fP , fR , fV , fR0 , fpb , fpbdot , alf , &
462+ pure subroutine s_advance_step (fRho , fP , fR , fV , fR0 , fpb , fpbdot , alf , &
461463 fntait , fBtait , f_bub_adv_src , f_divu , &
462464 bub_id , fmass_v , fmass_n , fbeta_c , &
463465 fbeta_t , fCson , adap_dt_stop )
@@ -676,7 +678,7 @@ contains
676678 !! @param myV_tmp Bubble radial velocity at each stage
677679 !! @param myPb_tmp Internal bubble pressure at each stage (EL)
678680 !! @param myMv_tmp Mass of vapor in the bubble at each stage (EL)
679- subroutine s_advance_substep (err , fRho , fP , fR , fV , fR0 , fpb , fpbdot , alf , &
681+ pure subroutine s_advance_substep (err , fRho , fP , fR , fV , fR0 , fpb , fpbdot , alf , &
680682 fntait , fBtait , f_bub_adv_src , f_divu , &
681683 bub_id , fmass_v , fmass_n , fbeta_c , &
682684 fbeta_t , fCson , h , &
@@ -705,8 +707,8 @@ contains
705707 if (bubbles_lagrange) then
706708 myPb_tmp(1 ) = fpb
707709 myMv_tmp(1 ) = fmass_v
708- mydMvdt_tmp( 1 ) = f_advance_EL (myR_tmp(1 ), myV_tmp(1 ), myPb_tmp(1 ), myMv_tmp(1 ), bub_id, &
709- fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(1 ))
710+ call s_advance_EL (myR_tmp(1 ), myV_tmp(1 ), myPb_tmp(1 ), myMv_tmp(1 ), bub_id, &
711+ fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(1 ), mydMvdt_tmp( 1 ) )
710712 end if
711713 myA_tmp(1 ) = f_rddot(fRho, fP, myR_tmp(1 ), myV_tmp(1 ), fR0, &
712714 myPb_tmp(1 ), mydPbdt_tmp(1 ), alf, fntait, fBtait, &
@@ -719,8 +721,8 @@ contains
719721 if (bubbles_lagrange) then
720722 myPb_tmp(2 ) = myPb_tmp(1 ) + h* mydPbdt_tmp(1 )
721723 myMv_tmp(2 ) = myMv_tmp(1 ) + h* mydMvdt_tmp(1 )
722- mydMvdt_tmp( 2 ) = f_advance_EL (myR_tmp(2 ), myV_tmp(2 ), myPb_tmp(2 ), myMv_tmp(2 ), &
723- bub_id, fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(2 ))
724+ call s_advance_EL (myR_tmp(2 ), myV_tmp(2 ), myPb_tmp(2 ), myMv_tmp(2 ), &
725+ bub_id, fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(2 ), mydMvdt_tmp( 2 ) )
724726 end if
725727 myA_tmp(2 ) = f_rddot(fRho, fP, myR_tmp(2 ), myV_tmp(2 ), fR0, &
726728 myPb_tmp(2 ), mydPbdt_tmp(2 ), alf, fntait, fBtait, &
@@ -733,8 +735,8 @@ contains
733735 if (bubbles_lagrange) then
734736 myPb_tmp(3 ) = myPb_tmp(1 ) + (h/ 4._wp )* (mydPbdt_tmp(1 ) + mydPbdt_tmp(2 ))
735737 myMv_tmp(3 ) = myMv_tmp(1 ) + (h/ 4._wp )* (mydMvdt_tmp(1 ) + mydMvdt_tmp(2 ))
736- mydMvdt_tmp( 3 ) = f_advance_EL (myR_tmp(3 ), myV_tmp(3 ), myPb_tmp(3 ), myMv_tmp(3 ), &
737- bub_id, fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(3 ))
738+ call s_advance_EL (myR_tmp(3 ), myV_tmp(3 ), myPb_tmp(3 ), myMv_tmp(3 ), &
739+ bub_id, fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(3 ), mydMvdt_tmp( 3 ) )
738740 end if
739741 myA_tmp(3 ) = f_rddot(fRho, fP, myR_tmp(3 ), myV_tmp(3 ), fR0, &
740742 myPb_tmp(3 ), mydPbdt_tmp(3 ), alf, fntait, fBtait, &
@@ -747,8 +749,8 @@ contains
747749 if (bubbles_lagrange) then
748750 myPb_tmp(4 ) = myPb_tmp(1 ) + (h/ 6._wp )* (mydPbdt_tmp(1 ) + mydPbdt_tmp(2 ) + 4._wp * mydPbdt_tmp(3 ))
749751 myMv_tmp(4 ) = myMv_tmp(1 ) + (h/ 6._wp )* (mydMvdt_tmp(1 ) + mydMvdt_tmp(2 ) + 4._wp * mydMvdt_tmp(3 ))
750- mydMvdt_tmp( 4 ) = f_advance_EL (myR_tmp(4 ), myV_tmp(4 ), myPb_tmp(4 ), myMv_tmp(4 ), &
751- bub_id, fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(4 ))
752+ call s_advance_EL (myR_tmp(4 ), myV_tmp(4 ), myPb_tmp(4 ), myMv_tmp(4 ), &
753+ bub_id, fmass_n, fbeta_c, fbeta_t, mydPbdt_tmp(4 ), mydMvdt_tmp( 4 ) )
752754 end if
753755 myA_tmp(4 ) = f_rddot(fRho, fP, myR_tmp(4 ), myV_tmp(4 ), fR0, &
754756 myPb_tmp(4 ), mydPbdt_tmp(4 ), alf, fntait, fBtait, &
@@ -780,20 +782,20 @@ contains
780782 !! @param fMv_tmp Mass of vapor in the bubble
781783 !! @param fdPbdt_tmp Rate of change of the internal bubble pressure
782784 !! @param fdMvdt_tmp Rate of change of the mass of vapor in the bubble
783- function f_advance_EL (fR_tmp , fV_tmp , fPb_tmp , fMv_tmp , bub_id , &
784- fmass_n , fbeta_c , fbeta_t , fdPbdt_tmp )
785+ pure elemental subroutine s_advance_EL (fR_tmp, fV_tmp, fPb_tmp, fMv_tmp, bub_id, &
786+ fmass_n, fbeta_c, fbeta_t, fdPbdt_tmp, advance_EL )
785787 !$acc routine seq
786788 real (wp), intent (IN ) :: fR_tmp, fV_tmp, fPb_tmp, fMv_tmp
787789 real (wp), intent (IN ) :: fmass_n, fbeta_c, fbeta_t
788790 integer , intent (IN ) :: bub_id
789791 real (wp), intent (INOUT ) :: fdPbdt_tmp
792+ real (wp), intent (out ) :: advance_EL
793+ real (wp) :: fVapFlux, myR_m, mygamma_m
790794
791- real (wp) :: fVapFlux, f_advance_EL, myR_m, mygamma_m
792-
793- fVapFlux = f_vflux(fR_tmp, fV_tmp, fPb_tmp, fMv_tmp, bub_id, fmass_n, fbeta_c, myR_m, mygamma_m)
795+ call s_vflux(fR_tmp, fV_tmp, fPb_tmp, fMv_tmp, bub_id, fVapFlux, fmass_n, fbeta_c, myR_m, mygamma_m)
794796 fdPbdt_tmp = f_bpres_dot(fVapFlux, fR_tmp, fV_tmp, fPb_tmp, fMv_tmp, bub_id, fbeta_t, myR_m, mygamma_m)
795- f_advance_EL = 4._wp * pi* fR_tmp** 2._wp * fVapFlux
797+ advance_EL = 4._wp * pi* fR_tmp** 2._wp * fVapFlux
796798
797- end function f_advance_EL
799+ end subroutine s_advance_EL
798800
799801end module m_bubbles
0 commit comments