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/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/CRS – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/CRS/crsfld.F90 @ 10970

Last change on this file since 10970 was 10970, checked in by davestorkey, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : CRS and FLO. Only tested compilation. Note that base code doesn't compile with key_floats (#2279), so changes to FLO not really tested at all.

  • Property svn:keywords set to Id
File size: 11.7 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 "vectopt_loop_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
37   !! $Id$
38   !! Software governed by the CeCILL license (see ./LICENSE)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE crs_fld( kt, Kmm )
43      !!---------------------------------------------------------------------
44      !!                  ***  ROUTINE crs_fld  ***
45      !!                   
46      !! ** Purpose :   Basic output of coarsened dynamics and tracer fields
47      !!      NETCDF format is used by default
48      !!      1. Accumulate in time the dimensionally-weighted fields
49      !!      2. At time of output, rescale [1] by dimension and time
50      !!         to yield the spatial and temporal average.
51      !!  See. sbcmod.F90
52      !!
53      !! ** Method  : 
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
56      INTEGER, INTENT(in) ::   Kmm  ! time level index
57      !
58      INTEGER  ::   ji, jj, jk        ! dummy loop indices
59      REAL(wp) ::   z2dcrsu, z2dcrsv  ! local scalars
60      REAL(wp) ::   zztmp             !   -      -
61      !
62      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ze3t, ze3u, ze3v, ze3w   ! 3D workspace for e3
63      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zt  , zs  , z3d
64      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk) ::   zt_crs, zs_crs 
65      !!----------------------------------------------------------------------
66      !
67      IF( ln_timing )   CALL timing_start('crs_fld')
68
69      ! Depth work arrrays
70      ze3t(:,:,:) = e3t(:,:,:,Kmm)
71      ze3u(:,:,:) = e3u(:,:,:,Kmm)
72      ze3v(:,:,:) = e3v(:,:,:,Kmm)
73      ze3w(:,:,:) = e3w(:,:,:,Kmm)
74
75      IF( kt == nit000  ) THEN
76         tsn_crs  (:,:,:,:) = 0._wp    ! temp/sal  array, now
77         un_crs   (:,:,:  ) = 0._wp    ! u-velocity
78         vn_crs   (:,:,:  ) = 0._wp    ! v-velocity
79         wn_crs   (:,:,:  ) = 0._wp    ! w
80         avs_crs  (:,:,:  ) = 0._wp    ! avt
81         hdivn_crs(:,:,:  ) = 0._wp    ! hdiv
82         sshn_crs (:,:    ) = 0._wp    ! ssh
83         utau_crs (:,:    ) = 0._wp    ! taux
84         vtau_crs (:,:    ) = 0._wp    ! tauy
85         wndm_crs (:,:    ) = 0._wp    ! wind speed
86         qsr_crs  (:,:    ) = 0._wp    ! qsr
87         emp_crs  (:,:    ) = 0._wp    ! emp
88         emp_b_crs(:,:    ) = 0._wp    ! emp
89         rnf_crs  (:,:    ) = 0._wp    ! runoff
90         fr_i_crs (:,:    ) = 0._wp    ! ice cover
91      ENDIF
92
93      CALL iom_swap( "nemo_crs" )    ! swap on the coarse grid
94
95      ! 2. Coarsen fields at each time step
96      ! --------------------------------------------------------
97
98      !  Temperature
99      zt(:,:,:) = ts(:,:,:,jp_tem,Kmm)  ;      zt_crs(:,:,:) = 0._wp
100      CALL crs_dom_ope( zt, 'VOL', 'T', tmask, zt_crs, p_e12=e1e2t, p_e3=ze3t, psgn=1.0 )
101      tsn_crs(:,:,:,jp_tem) = zt_crs(:,:,:)
102
103      CALL iom_put( "toce", tsn_crs(:,:,:,jp_tem) )    ! temp
104      CALL iom_put( "sst" , tsn_crs(:,:,1,jp_tem) )    ! sst
105
106     
107      !  Salinity
108      zs(:,:,:) = ts(:,:,:,jp_sal,Kmm)  ;      zs_crs(:,:,:) = 0._wp
109      CALL crs_dom_ope( zs, 'VOL', 'T', tmask, zs_crs, p_e12=e1e2t, p_e3=ze3t, psgn=1.0 )
110      tsn_crs(:,:,:,jp_sal) = zt_crs(:,:,:)
111
112      CALL iom_put( "soce" , tsn_crs(:,:,:,jp_sal) )    ! sal
113      CALL iom_put( "sss"  , tsn_crs(:,:,1,jp_sal) )    ! sss
114
115      !  U-velocity
116      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 )
117      !
118      zt(:,:,:) = 0._wp     ;    zs(:,:,:) = 0._wp  ;   zt_crs(:,:,:) = 0._wp   ;    zs_crs(:,:,:) = 0._wp
119      DO jk = 1, jpkm1
120         DO jj = 2, jpjm1
121            DO ji = 2, jpim1   
122               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) ) 
123               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) ) 
124            END DO
125         END DO
126      END DO
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 )
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 )
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 )
136      !                                                                                 
137      zt(:,:,:) = 0._wp     ;    zs(:,:,:) = 0._wp  ;   zt_crs(:,:,:) = 0._wp   ;    zs_crs(:,:,:) = 0._wp
138      DO jk = 1, jpkm1
139         DO jj = 2, jpjm1
140            DO ji = 2, jpim1   
141               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) ) 
142               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) ) 
143            END DO
144         END DO
145      END DO
146      CALL crs_dom_ope( zt, 'SUM', 'V', vmask, zt_crs, p_e12=e1v, p_e3=ze3v, p_surf_crs=e1e3v_msk, psgn=-1.0 )
147      CALL crs_dom_ope( zs, 'SUM', 'V', vmask, zs_crs, p_e12=e1v, p_e3=ze3v, p_surf_crs=e1e3v_msk, psgn=-1.0 )
148 
149      CALL iom_put( "voce"  , vn_crs )   ! i-current
150      CALL iom_put( "vocet" , zt_crs )   ! vT
151      CALL iom_put( "voces" , zs_crs )   ! vS
152
153      IF( iom_use( "eken") ) THEN     !      kinetic energy
154         z3d(:,:,jk) = 0._wp 
155         DO jk = 1, jpkm1
156            DO jj = 2, jpjm1
157               DO ji = fs_2, fs_jpim1   ! vector opt.
158                  zztmp  = r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm)
159                  z3d(ji,jj,jk) = 0.25_wp * zztmp * (                                    &
160                     &            uu(ji-1,jj,jk,Kmm)**2 * e2u(ji-1,jj) * e3u(ji-1,jj,jk,Kmm)   &
161                     &          + uu(ji  ,jj,jk,Kmm)**2 * e2u(ji  ,jj) * e3u(ji  ,jj,jk,Kmm)   &
162                     &          + vv(ji,jj-1,jk,Kmm)**2 * e1v(ji,jj-1) * e3v(ji,jj-1,jk,Kmm)   &
163                     &          + vv(ji,jj  ,jk,Kmm)**2 * e1v(ji,jj  ) * e3v(ji,jj  ,jk,Kmm)   )
164               END DO
165            END DO
166         END DO
167         CALL lbc_lnk( 'crsfld', z3d, 'T', 1. )
168         !
169         CALL crs_dom_ope( z3d, 'VOL', 'T', tmask, zt_crs, p_e12=e1e2t, p_e3=ze3t, psgn=1.0 )
170         CALL iom_put( "eken", zt_crs )
171      ENDIF
172      !  Horizontal divergence ( following OCE/DYN/divhor.F90 )
173      DO jk = 1, jpkm1
174         DO ji = 2, jpi_crsm1
175            DO jj = 2, jpj_crsm1
176               IF( tmask_crs(ji,jj,jk ) > 0 ) THEN
177                   z2dcrsu =  ( un_crs(ji  ,jj  ,jk) * crs_surfu_wgt(ji  ,jj  ,jk) ) &
178                      &     - ( un_crs(ji-1,jj  ,jk) * crs_surfu_wgt(ji-1,jj  ,jk) )
179                   z2dcrsv =  ( vn_crs(ji  ,jj  ,jk) * crs_surfv_wgt(ji  ,jj  ,jk) ) &
180                      &     - ( vn_crs(ji  ,jj-1,jk) * crs_surfv_wgt(ji  ,jj-1,jk) )
181                   !
182                   hdivn_crs(ji,jj,jk) = ( z2dcrsu + z2dcrsv ) / crs_volt_wgt(ji,jj,jk) 
183               ENDIF
184            END DO
185         END DO
186      END DO
187      CALL crs_lbc_lnk( hdivn_crs, 'T', 1.0 )
188      !
189      CALL iom_put( "hdiv", hdivn_crs ) 
190
191
192      !  W-velocity
193      IF( ln_crs_wn ) THEN
194         CALL crs_dom_ope( ww, 'SUM', 'W', tmask, wn_crs, p_e12=e1e2t, p_surf_crs=e1e2w_msk, psgn=1.0 )
195       !  CALL crs_dom_ope( ww, 'VOL', 'W', tmask, wn_crs, p_e12=e1e2t, p_e3=ze3w )
196      ELSE
197        wn_crs(:,:,jpk) = 0._wp
198        DO jk = jpkm1, 1, -1
199           wn_crs(:,:,jk) = wn_crs(:,:,jk+1) - e3t_crs(:,:,jk) * hdivn_crs(:,:,jk)
200        ENDDO
201      ENDIF
202      CALL iom_put( "woce", wn_crs  )   ! vertical velocity
203      !  free memory
204
205      !  avs
206      SELECT CASE ( nn_crs_kz )
207         CASE ( 0 )
208            CALL crs_dom_ope( avt, 'VOL', 'W', tmask, avt_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0 )
209            CALL crs_dom_ope( avs, 'VOL', 'W', tmask, avs_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0 )
210         CASE ( 1 )
211            CALL crs_dom_ope( avt, 'MAX', 'W', tmask, avt_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0 )
212            CALL crs_dom_ope( avs, 'MAX', 'W', tmask, avs_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0 )
213         CASE ( 2 )
214            CALL crs_dom_ope( avt, 'MIN', 'W', tmask, avt_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0 )
215            CALL crs_dom_ope( avs, 'MIN', 'W', tmask, avs_crs, p_e12=e1e2t, p_e3=ze3w, psgn=1.0 )
216      END SELECT
217      !
218      CALL iom_put( "avt", avt_crs )   !  Kz on T
219      CALL iom_put( "avs", avs_crs )   !  Kz on S
220     
221      !  sbc fields 
222      CALL crs_dom_ope( ssh(:,:,Kmm) , 'VOL', 'T', tmask, sshn_crs , p_e12=e1e2t, p_e3=ze3t           , psgn=1.0 ) 
223      CALL crs_dom_ope( utau , 'SUM', 'U', umask, utau_crs , p_e12=e2u  , p_surf_crs=e2u_crs  , psgn=1.0 )
224      CALL crs_dom_ope( vtau , 'SUM', 'V', vmask, vtau_crs , p_e12=e1v  , p_surf_crs=e1v_crs  , psgn=1.0 )
225      CALL crs_dom_ope( wndm , 'SUM', 'T', tmask, wndm_crs , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0 )
226      CALL crs_dom_ope( rnf  , 'MAX', 'T', tmask, rnf_crs                                     , psgn=1.0 )
227      CALL crs_dom_ope( qsr  , 'SUM', 'T', tmask, qsr_crs  , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0 )
228      CALL crs_dom_ope( emp_b, 'SUM', 'T', tmask, emp_b_crs, p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0 )
229      CALL crs_dom_ope( emp  , 'SUM', 'T', tmask, emp_crs  , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0 )
230      CALL crs_dom_ope( sfx  , 'SUM', 'T', tmask, sfx_crs  , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0 )
231      CALL crs_dom_ope( fr_i , 'SUM', 'T', tmask, fr_i_crs , p_e12=e1e2t, p_surf_crs=e1e2t_crs, psgn=1.0 )
232
233      CALL iom_put( "ssh"      , sshn_crs )   ! ssh output
234      CALL iom_put( "utau"     , utau_crs )   ! i-tau output
235      CALL iom_put( "vtau"     , vtau_crs )   ! j-tau output
236      CALL iom_put( "wspd"     , wndm_crs )   ! wind speed output
237      CALL iom_put( "runoffs"  , rnf_crs  )   ! runoff output
238      CALL iom_put( "qsr"      , qsr_crs  )   ! qsr output
239      CALL iom_put( "empmr"    , emp_crs  )   ! water flux output
240      CALL iom_put( "saltflx"  , sfx_crs  )   ! salt flux output
241      CALL iom_put( "ice_cover", fr_i_crs )   ! ice cover output
242
243      !
244      CALL iom_swap( "nemo" )     ! return back on high-resolution grid
245      !
246      IF( ln_timing )   CALL timing_stop('crs_fld')
247      !
248   END SUBROUTINE crs_fld
249
250   !!======================================================================
251END MODULE crsfld
Note: See TracBrowser for help on using the repository browser.