Skip to content
Snippets Groups Projects
Commit 8e0a05a7 authored by Clement Rousset's avatar Clement Rousset
Browse files

finish the work on halos for DIA routines

parent 64c00247
No related branches found
No related tags found
No related merge requests found
......@@ -79,7 +79,7 @@ CONTAINS
REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z2d ! 2D workspace
REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z3d
REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zrhd, zgdept ! 3D workspace (zgdept: needed to use the substitute)
REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: ztsn ! 4D workspace
REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: ztsn ! 4D workspace
!!--------------------------------------------------------------------
IF( ln_timing ) CALL timing_start('dia_ar5')
......
......@@ -54,8 +54,8 @@ CONTAINS
INTEGER :: dia_hth_alloc
!!---------------------------------------------------------------------
!
ALLOCATE( hth(jpi,jpj), hd20(jpi,jpj), hd26(jpi,jpj), hd28(jpi,jpj), &
& htc3(jpi,jpj), htc7(jpi,jpj), htc20(jpi,jpj), STAT=dia_hth_alloc )
ALLOCATE( hth(A2D(0)), hd20(A2D(0)), hd26(A2D(0)), hd28(A2D(0)), &
& htc3(A2D(0)), htc7(A2D(0)), htc20(A2D(0)), STAT=dia_hth_alloc )
!
CALL mpp_sum ( 'diahth', dia_hth_alloc )
IF(dia_hth_alloc /= 0) CALL ctl_stop( 'STOP', 'dia_hth_alloc: failed to allocate arrays.' )
......@@ -301,7 +301,7 @@ CONTAINS
!
INTEGER , INTENT(in) :: Kmm ! ocean time level index
REAL(wp), INTENT(in) :: ptem
REAL(wp), DIMENSION(jpi,jpj), INTENT(out) :: pdept
REAL(wp), DIMENSION(A2D(0)), INTENT(out) :: pdept
!
INTEGER :: ji, jj, jk, iid
REAL(wp) :: zztmp, zzdep
......@@ -346,7 +346,7 @@ CONTAINS
INTEGER , INTENT(in) :: Kmm ! ocean time level index
REAL(wp), INTENT(in) :: pdep ! depth over the heat content
REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) :: pt
REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: phtc
REAL(wp), DIMENSION(A2D(0)), INTENT(inout) :: phtc
!
INTEGER :: ji, jj, jk, ik
REAL(wp), DIMENSION(A2D(0)) :: zthick
......
......@@ -315,7 +315,8 @@ CONTAINS
IF(lwp) WRITE(numout,*) 'wzv_RK3 : now vertical velocity '
IF(lwp) WRITE(numout,*) '~~~~~ '
!
pww(:,:,jpk) = 0._wp ! bottom boundary condition: w=0 (set once for all)
pww(:,:,:) = 0._wp ! bottom boundary condition: w=0 (set once for all)
! ! needed over the halos for the output (ww+wi) in diawri.F90
ENDIF
!
CALL div_hor( kt, Kbb, Kmm, puu, pvv, ze3div )
......
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