Skip to content
Snippets Groups Projects
Commit fabb89bb authored by ESCOBAR Juan's avatar ESCOBAR Juan
Browse files

Juan 03/03/2022:ZSOLVER/turb.f90, for MPPDB_CHECK , compute budget on GPU with ZTEMP_BUD variable

parent 5ade1fcb
No related branches found
No related tags found
No related merge requests found
......@@ -467,6 +467,8 @@ INTEGER :: JIU,JJU,JKU
INTEGER :: JLU_ZRM, JLU_TURB, JJU_ORMC01, JKU_CLOUD, JKU_TURB
LOGICAL :: GOCEAN !Intermediate variable used to work around a Cray compiler bug (CCE 13.0.0)
!
REAL, DIMENSION(:,:,:), pointer , contiguous :: ZTEMP_BUD
!
!------------------------------------------------------------------------------------------
!
! IN variables
......@@ -598,6 +600,7 @@ IF ( HTURBLEN == 'RM17' ) JKU_TURB = size( put, 3 )
allocate( zdudz (JIU,JJU, JKU_TURB ) )
allocate( zdvdz (JIU,JJU, JKU_TURB ) )
ALLOCATE(ZTEMP_BUD(JIU,JJU,JKU))
#else
!Pin positions in the pools of MNH memory
CALL MNH_MEM_POSITION_PIN()
......@@ -668,6 +671,7 @@ IF (HTURBDIM=="1DIM") JKU_TURB = size( pthlt, 3 )
CALL MNH_MEM_GET( ztmp2_device, JIU, JJU, JKU_TURB )
CALL MNH_MEM_GET( ztmp3_device, JIU, JJU, JKU_TURB )
CALL MNH_MEM_GET(ZTEMP_BUD, JIU,JJU,JKU )
#endif
!$acc data present( zcp, zexn, zt, zlocpexnm, zleps, ztrh, &
......@@ -1135,21 +1139,33 @@ if ( lbudget_v ) call Budget_store_init( tbudgets(NBUDGET_V ), 'VTURB', prvs (
if ( lbudget_w ) call Budget_store_init( tbudgets(NBUDGET_W ), 'VTURB', prws (:, :, :) )
if ( lbudget_th ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_TH), 'VTURB', prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_TH), 'VTURB', prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_TH), 'VTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_TH), 'VTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_init( tbudgets(NBUDGET_TH), 'VTURB', prthls(:, :, :) )
end if
end if
if ( lbudget_rv ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_RV), 'VTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_RV), 'VTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RV), 'VTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RV), 'VTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_init( tbudgets(NBUDGET_RV), 'VTURB', prrs(:, :, :, 1) )
end if
......@@ -1189,21 +1205,33 @@ if ( lbudget_v ) call Budget_store_end( tbudgets(NBUDGET_V), 'VTURB', prvs(:, :,
if ( lbudget_w ) call Budget_store_end( tbudgets(NBUDGET_W), 'VTURB', prws(:, :, :) )
if ( lbudget_th ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_TH), 'VTURB', prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_TH), 'VTURB', prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_TH), 'VTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_TH), 'VTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_end( tbudgets(NBUDGET_TH), 'VTURB', prthls(:, :, :) )
end if
end if
if ( lbudget_rv ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_RV), 'VTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_RV), 'VTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RV), 'VTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RV), 'VTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_end( tbudgets(NBUDGET_RV), 'VTURB', prrs(:, :, :, 1) )
end if
......@@ -1224,21 +1252,33 @@ if ( hturbdim == '3DIM' ) then
if ( lbudget_w ) call Budget_store_init( tbudgets(NBUDGET_W ), 'HTURB', prws (:, :, :) )
if (lbudget_th) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_TH), 'HTURB', prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_TH), 'HTURB', prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_TH), 'HTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_TH), 'HTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_init( tbudgets(NBUDGET_TH), 'HTURB', prthls(:, :, :) )
end if
end if
if ( lbudget_rv ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_RV), 'HTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_init( tbudgets(NBUDGET_RV), 'HTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RV), 'HTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RV), 'HTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_init( tbudgets(NBUDGET_RV), 'HTURB', prrs(:, :, :, 1) )
end if
......@@ -1274,21 +1314,33 @@ if ( hturbdim == '3DIM' ) then
if ( lbudget_w ) call Budget_store_end( tbudgets(NBUDGET_W), 'HTURB', prws(:, :, :) )
if ( lbudget_th ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_TH), 'HTURB', prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_TH), 'HTURB', prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlvocpexnm(:, :, :) * prrs(:, :, :, 2) &
+ zlsocpexnm(:, :, :) * prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_TH), 'HTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prthls(:, :, :) + zlocpexnm(:, :, :) * prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_TH), 'HTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_end( tbudgets(NBUDGET_TH), 'HTURB', prthls(:, :, :) )
end if
end if
if ( lbudget_rv ) then
if ( krri >= 1 .and. krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_RV), 'HTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4) )
else if ( krrl >= 1 ) then
call Budget_store_end( tbudgets(NBUDGET_RV), 'HTURB', prrs(:, :, :, 1) - prrs(:, :, :, 2) )
if ( krri >= 1 .and. krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2) - prrs(:, :, :, 4)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RV), 'HTURB', ZTEMP_BUD(:,:,:) )
else if ( krrl >= 1 ) then
!$acc kernels present(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :, 1) - prrs(:, :, :, 2)
!$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RV), 'HTURB', ZTEMP_BUD(:,:,:) )
else
call Budget_store_end( tbudgets(NBUDGET_RV), 'HTURB', prrs(:, :, :, 1) )
end if
......@@ -1587,7 +1639,8 @@ deallocate( zcp, zexn, zt, zlocpexnm, zleps, ztrh, &
ztau11m, ztau12m, ztau22m, ztau33m, &
zuslope, zvslope, zcdueff, zlmo, &
zustar, zrvm, zsfrv, &
ztt, zexne, zlv, zcph, zshear, zdudz, zdvdz )
ztt, zexne, zlv, zcph, zshear, zdudz, zdvdz, &
ZTEMP_BUD)
#else
!Release all memory allocated with MNH_MEM_GET calls since last call to MNH_MEM_POSITION_PIN
CALL MNH_MEM_RELEASE()
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment