New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
crsfld.F90 in NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/CRS – NEMO

source: NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/CRS/crsfld.F90 @ 15540

Last change on this file since 15540 was 15540, checked in by sparonuz, 3 years ago

Mixed precision version, tested up to 30 years on ORCA2.

  • Property svn:keywords set to Id
File size: 11.6 KB
Line 
1MODULE crsfld
2   !!======================================================================
3   !!                     ***  MODULE  crsdfld  ***
4   !!  Ocean coarsening :  coarse ocean fields
5   !!=====================================================================
6   !!   2012-07  (J. Simeon, C. Calone, G. Madec, C. Ethe)
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   crs_fld       : create the standard output files for coarse grid and prep
11   !!                       other variables needed to be passed to TOP
12   !!----------------------------------------------------------------------
13   USE crs
14   USE crsdom
15   USE crslbclnk
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE sbc_oce         ! Surface boundary condition: ocean fields
19   USE zdf_oce         ! vertical  physics: ocean fields
20   USE ldftra          ! ocean active tracers: lateral diffusivity & EIV coefficients
21   USE zdfddm          ! vertical  physics: double diffusion
22   !
23   USE in_out_manager  ! I/O manager
24   USE iom             !
25   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
26   USE timing          ! preformance summary
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   crs_fld                 ! routines called by step.F90
32
33   !! * Substitutions
34#  include "do_loop_substitute.h90"
35#  include "domzgr_substitute.h90"
36#  include "single_precision_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
39   !! $Id$
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE crs_fld( kt, Kmm )
45      !!---------------------------------------------------------------------
46      !!                  ***  ROUTINE crs_fld  ***
47      !!                   
48      !! ** Purpose :   Basic output of coarsened dynamics and tracer fields
49      !!      NETCDF format is used by default
50      !!      1. Accumulate in time the dimensionally-weighted fields
51      !!      2. At time of output, rescale [1] by dimension and time
52      !!         to yield the spatial and temporal average.
53      !!  See. sbcmod.F90
54      !!
55      !! ** Method  : 
56      !!----------------------------------------------------------------------
57      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
58      INTEGER, INTENT(in) ::   Kmm  ! time level index
59      !
60      INTEGER  ::   ji, jj, jk        ! dummy loop indices
61      REAL(dp) ::   z2dcrsu, z2dcrsv  ! local scalars
62      REAL(dp) ::   zztmp             !   -      -
63      !
64      REAL(dp), DIMENSION(jpi,jpj,jpk) ::   ze3t, ze3u, ze3v, ze3w   ! 3D workspace for e3
65      REAL(dp), DIMENSION(jpi,jpj,jpk) ::   zt  , zs  , z3d
66      REAL(dp), DIMENSION(jpi_crs,jpj_crs,jpk) ::   zt_crs, zs_crs 
67      !!----------------------------------------------------------------------
68      !
69      IF( ln_timing )   CALL timing_start('crs_fld')
70
71      ! Depth work arrrays
72      DO jk = 1 , jpk 
73         ze3t(:,:,jk) = e3t(:,:,jk,Kmm)
74         ze3u(:,:,jk) = e3u(:,:,jk,Kmm)
75         ze3v(:,:,jk) = e3v(:,:,jk,Kmm)
76         ze3w(:,:,jk) = e3w(:,:,jk,Kmm)
77      END DO
78
79      IF( kt == nit000  ) THEN
80         tsn_crs  (:,:,:,:) = 0._wp    ! temp/sal  array, now
81         un_crs   (:,:,:  ) = 0._wp    ! u-velocity
82         vn_crs   (:,:,:  ) = 0._wp    ! v-velocity
83         wn_crs   (:,:,:  ) = 0._wp    ! w
84         avs_crs  (:,:,:  ) = 0._wp    ! avt
85         hdivn_crs(:,:,:  ) = 0._wp    ! hdiv
86         sshn_crs (:,:    ) = 0._wp    ! ssh
87         utau_crs (:,:    ) = 0._wp    ! taux
88         vtau_crs (:,:    ) = 0._wp    ! tauy
89         wndm_crs (:,:    ) = 0._wp    ! wind speed
90         qsr_crs  (:,:    ) = 0._wp    ! qsr
91         emp_crs  (:,:    ) = 0._wp    ! emp
92         emp_b_crs(:,:    ) = 0._wp    ! emp
93         rnf_crs  (:,:    ) = 0._wp    ! runoff
94         fr_i_crs (:,:    ) = 0._wp    ! ice cover
95      ENDIF
96
97      CALL iom_swap( "nemo_crs" )    ! swap on the coarse grid
98
99      ! 2. Coarsen fields at each time step
100      ! --------------------------------------------------------
101
102      !  Temperature
103      zt(:,:,:) = ts(:,:,:,jp_tem,Kmm)  ;      zt_crs(:,:,:) = 0._wp
104      CALL crs_dom_ope( zt, 'VOL', 'T', tmask, zt_crs, p_e12=e1e2t, p_e3=ze3t, psgn=1.0_wp )
105      tsn_crs(:,:,:,jp_tem) = zt_crs(:,:,:)
106
107      CALL iom_put( "toce", tsn_crs(:,:,:,jp_tem) )    ! temp
108      CALL iom_put( "sst" , tsn_crs(:,:,1,jp_tem) )    ! sst
109
110     
111      !  Salinity
112      zs(:,:,:) = ts(:,:,:,jp_sal,Kmm)  ;      zs_crs(:,:,:) = 0._wp
113      CALL crs_dom_ope( zs, 'VOL', 'T', tmask, zs_crs, p_e12=e1e2t, p_e3=ze3t, psgn=1.0_wp )
114      tsn_crs(:,:,:,jp_sal) = zt_crs(:,:,:)
115
116      CALL iom_put( "soce" , tsn_crs(:,:,:,jp_sal) )    ! sal
117      CALL iom_put( "sss"  , tsn_crs(:,:,1,jp_sal) )    ! sss
118
119      !  U-velocity
120      CALL crs_dom_ope( uu(:,:,:,Kmm), 'SUM', 'U', umask, un_crs, p_e12=e2u, p_e3=ze3u, p_surf_crs=e2e3u_msk, psgn=-1.0_wp )
121      !
122      zt(:,:,:) = 0._wp     ;    zs(:,:,:) = 0._wp  ;   zt_crs(:,:,:) = 0._wp   ;    zs_crs(:,:,:) = 0._wp
123      DO_3D( 0, 0, 0, 0, 1, jpkm1 )
124         zt(ji,jj,jk)  = uu(ji,jj,jk,Kmm) * 0.5 * ( ts(ji,jj,jk,jp_tem,Kmm) + ts(ji+1,jj,jk,jp_tem,Kmm) ) 
125         zs(ji,jj,jk)  = uu(ji,jj,jk,Kmm) * 0.5 * ( ts(ji,jj,jk,jp_sal,Kmm) + ts(ji+1,jj,jk,jp_sal,Kmm) ) 
126      END_3D
127      CALL crs_dom_ope( zt, 'SUM', 'U', umask, zt_crs, p_e12=e2u, p_e3=ze3u, p_surf_crs=e2e3u_msk, psgn=-1.0_wp )
128      CALL crs_dom_ope( zs, 'SUM', 'U', umask, zs_crs, p_e12=e2u, p_e3=ze3u, p_surf_crs=e2e3u_msk, psgn=-1.0_wp )
129
130      CALL iom_put( "uoce"  , un_crs )   ! i-current
131      CALL iom_put( "uocet" , zt_crs )   ! uT
132      CALL iom_put( "uoces" , zs_crs )   ! uS
133
134      !  V-velocity
135      CALL crs_dom_ope( vv(:,:,:,Kmm), 'SUM', 'V', vmask, vn_crs, p_e12=e1v, p_e3=ze3v, p_surf_crs=e1e3v_msk, psgn=-1.0_wp )
136      !                                                                                 
137      zt(:,:,:) = 0._wp     ;    zs(:,:,:) = 0._wp  ;   zt_crs(:,:,:) = 0._wp   ;    zs_crs(:,:,:) = 0._wp
138      DO_3D( 0, 0, 0, 0, 1, jpkm1 )
139         zt(ji,jj,jk)  = vv(ji,jj,jk,Kmm) * 0.5 * ( ts(ji,jj,jk,jp_tem,Kmm) + ts(ji,jj+1,jk,jp_tem,Kmm) ) 
140         zs(ji,jj,jk)  = vv(ji,jj,jk,Kmm) * 0.5 * ( ts(ji,jj,jk,jp_sal,Kmm) + ts(ji,jj+1,jk,jp_sal,Kmm) ) 
141      END_3D
142      CALL crs_dom_ope( zt, 'SUM', 'V', vmask, zt_crs, p_e12=e1v, p_e3=ze3v, p_surf_crs=e1e3v_msk, psgn=-1.0_wp )
143      CALL crs_dom_ope( zs, 'SUM', 'V', vmask, zs_crs, p_e12=e1v, p_e3=ze3v, p_surf_crs=e1e3v_msk, psgn=-1.0_wp )
144 
145      CALL iom_put( "voce"  , vn_crs )   ! i-current
146      CALL iom_put( "vocet" , zt_crs )   ! vT
147      CALL iom_put( "voces" , zs_crs )   ! vS
148
149      IF( iom_use( "ke") ) THEN     !      kinetic energy
150         z3d(:,:,jk) = 0._wp 
151         DO_3D( 0, 0, 0, 0, 1, jpkm1 )
152            zztmp  = r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm)
153            z3d(ji,jj,jk) = 0.25_wp * zztmp * (                                    &
154               &            uu(ji-1,jj,jk,Kmm)**2 * e2u(ji-1,jj) * e3u(ji-1,jj,jk,Kmm)   &
155               &          + uu(ji  ,jj,jk,Kmm)**2 * e2u(ji  ,jj) * e3u(ji  ,jj,jk,Kmm)   &
156               &          + vv(ji,jj-1,jk,Kmm)**2 * e1v(ji,jj-1) * e3v(ji,jj-1,jk,Kmm)   &
157               &          + vv(ji,jj  ,jk,Kmm)**2 * e1v(ji,jj  ) * e3v(ji,jj  ,jk,Kmm)   )
158         END_3D
159         CALL lbc_lnk( 'crsfld', z3d, 'T', 1.0_wp )
160         !
161         CALL crs_dom_ope( z3d, 'VOL', 'T', tmask, zt_crs, p_e12=e1e2t, p_e3=ze3t, psgn=1.0_wp )
162         CALL iom_put( "ke", zt_crs )
163      ENDIF
164      !  Horizontal divergence ( following OCE/DYN/divhor.F90 )
165      DO jk = 1, jpkm1
166         DO ji = 2, jpi_crsm1
167            DO jj = 2, jpj_crsm1
168               IF( tmask_crs(ji,jj,jk ) > 0 ) THEN
169                   z2dcrsu =  ( un_crs(ji  ,jj  ,jk) * crs_surfu_wgt(ji  ,jj  ,jk) ) &
170                      &     - ( un_crs(ji-1,jj  ,jk) * crs_surfu_wgt(ji-1,jj  ,jk) )
171                   z2dcrsv =  ( vn_crs(ji  ,jj  ,jk) * crs_surfv_wgt(ji  ,jj  ,jk) ) &
172                      &     - ( vn_crs(ji  ,jj-1,jk) * crs_surfv_wgt(ji  ,jj-1,jk) )
173                   !
174                   hdivn_crs(ji,jj,jk) = ( z2dcrsu + z2dcrsv ) / crs_volt_wgt(ji,jj,jk) 
175               ENDIF
176            END DO
177         END DO
178      END DO
179      CALL crs_lbc_lnk( hdivn_crs, 'T', 1.0_wp )
180      !
181      CALL iom_put( "hdiv", hdivn_crs ) 
182
183
184      !  W-velocity
185      IF( ln_crs_wn ) THEN
186         CALL crs_dom_ope( ww, 'SUM', 'W', tmask, wn_crs, p_e12=e1e2t, p_surf_crs=e1e2w_msk, psgn=1.0_wp )
187       !  CALL crs_dom_ope( ww, 'VOL', 'W', tmask, wn_crs, p_e12=e1e2t, p_e3=ze3w )
188      ELSE
189        wn_crs(:,:,jpk) = 0._wp
190        DO jk = jpkm1, 1, -1
191           wn_crs(:,:,jk) = wn_crs(:,:,jk+1) - e3t_crs(:,:,jk) * hdivn_crs(:,:,jk)
192        ENDDO
193      ENDIF
194      CALL iom_put( "woce", wn_crs  )   ! vertical velocity
195      !  free memory
196
197      !  avs
198      SELECT CASE ( nn_crs_kz )
199         CASE ( 0 )
200            CALL crs_dom_ope( avt, 'VOL', 'W', tmask, avt_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0_wp )
201            CALL crs_dom_ope( avs, 'VOL', 'W', tmask, avs_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0_wp )
202         CASE ( 1 )
203            CALL crs_dom_ope( avt, 'MAX', 'W', tmask, avt_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0_wp )
204            CALL crs_dom_ope( avs, 'MAX', 'W', tmask, avs_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0_wp )
205         CASE ( 2 )
206            CALL crs_dom_ope( avt, 'MIN', 'W', tmask, avt_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0_wp )
207            CALL crs_dom_ope( avs, 'MIN', 'W', tmask, avs_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0_wp )
208      END SELECT
209      !
210      CALL iom_put( "avt", avt_crs )   !  Kz on T
211      CALL iom_put( "avs", avs_crs )   !  Kz on S
212     
213      !  sbc fields 
214      CALL crs_dom_ope( ssh(:,:,Kmm) , 'VOL', 'T', tmask, sshn_crs , p_e12=e1e2t, p_e3=ze3t           , psgn=1.0_wp ) 
215      CALL crs_dom_ope( utau , 'SUM', 'U', umask, utau_crs , p_e12=e2u  , p_surf_crs=e2u_crs  , psgn=1.0_wp )
216      CALL crs_dom_ope( vtau , 'SUM', 'V', vmask, vtau_crs , p_e12=e1v  , p_surf_crs=e1v_crs  , psgn=1.0_wp )
217      CALL crs_dom_ope( wndm , 'SUM', 'T', tmask, wndm_crs , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0_wp )
218      CALL crs_dom_ope( CASTDP(rnf)  , 'MAX', 'T', tmask, rnf_crs                                     , psgn=1.0_wp )
219      CALL crs_dom_ope( CASTDP(qsr)  , 'SUM', 'T', tmask, qsr_crs  , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0_wp )
220      CALL crs_dom_ope( emp_b, 'SUM', 'T', tmask, emp_b_crs, p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0_wp )
221      CALL crs_dom_ope( emp  , 'SUM', 'T', tmask, emp_crs  , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0_wp )
222      CALL crs_dom_ope( CASTDP(sfx)  , 'SUM', 'T', tmask, sfx_crs  , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0_wp )
223      CALL crs_dom_ope( fr_i , 'SUM', 'T', tmask, fr_i_crs , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0_wp )
224
225      CALL iom_put( "ssh"      , sshn_crs )   ! ssh output
226      CALL iom_put( "utau"     , utau_crs )   ! i-tau output
227      CALL iom_put( "vtau"     , vtau_crs )   ! j-tau output
228      CALL iom_put( "wspd"     , wndm_crs )   ! wind speed output
229      CALL iom_put( "runoffs"  , rnf_crs  )   ! runoff output
230      CALL iom_put( "qsr"      , qsr_crs  )   ! qsr output
231      CALL iom_put( "empmr"    , emp_crs  )   ! water flux output
232      CALL iom_put( "saltflx"  , sfx_crs  )   ! salt flux output
233      CALL iom_put( "ice_cover", fr_i_crs )   ! ice cover output
234
235      !
236      CALL iom_swap( "nemo" )     ! return back on high-resolution grid
237      !
238      IF( ln_timing )   CALL timing_stop('crs_fld')
239      !
240   END SUBROUTINE crs_fld
241
242   !!======================================================================
243END MODULE crsfld
Note: See TracBrowser for help on using the repository browser.