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.
sbcssm.F90 in NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/SAS – NEMO

source: NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/SAS/sbcssm.F90 @ 11872

Last change on this file since 11872 was 11872, checked in by acc, 4 years ago

Branch 2019/fix_sn_cfctl_ticket2328. See #2328. Replacement of ln_ctl and activation of full functionality with
sn_cfctl structure. These changes rename structure components l_mppout and l_mpptop as l_prtctl and l_prttrc
and introduce l_glochk to activate former ln_ctl code in stpctl.F90 to perform global location of min and max
checks. Also added is l_allon which can be used to activate all output (much like the former ln_ctl). If l_allon
is .false. then l_config decides whether or not the suboptions are used.

   sn_cfctl%l_glochk = .FALSE.    ! Range sanity checks are local (F) or global (T). Set T for debugging only
   sn_cfctl%l_allon  = .FALSE.    ! IF T activate all options. If F deactivate all unless l_config is T
   sn_cfctl%l_config = .TRUE.     ! IF .true. then control which reports are written with the remaining options

Note, these changes pass SETTE tests but all references to ln_ctl need to be removed from the sette scripts.

  • Property svn:keywords set to Id
File size: 15.8 KB
Line 
1MODULE sbcssm
2   !!======================================================================
3   !!                       ***  MODULE  sbcssm  ***
4   !! Off-line : interpolation of the physical fields
5   !!======================================================================
6   !! History :  3.4  ! 2012-03 (S. Alderson)  original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   sbc_ssm_init  : initialization, namelist read, and SAVEs control
11   !!   sbc_ssm       : Interpolation of the fields
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and tracers variables
14   USE c1d            ! 1D configuration: lk_c1d
15   USE dom_oce        ! ocean domain: variables
16   USE zdf_oce        ! ocean vertical physics: variables
17   USE sbc_oce        ! surface module: variables
18   USE phycst         ! physical constants
19   USE eosbn2         ! equation of state - Brunt Vaisala frequency
20   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
21   USE zpshde         ! z-coord. with partial steps: horizontal derivatives
22   USE closea         ! for ln_closea
23   !
24   USE in_out_manager ! I/O manager
25   USE iom            ! I/O library
26   USE lib_mpp        ! distributed memory computing library
27   USE prtctl         ! print control
28   USE fldread        ! read input fields
29   USE timing         ! Timing
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   sbc_ssm_init   ! called by sbc_init
35   PUBLIC   sbc_ssm        ! called by sbc
36
37   CHARACTER(len=100) ::   cn_dir        ! Root directory for location of ssm files
38   LOGICAL            ::   ln_3d_uve     ! specify whether input velocity data is 3D
39   LOGICAL            ::   ln_read_frq   ! specify whether we must read frq or not
40   
41   LOGICAL            ::   l_sasread     ! Ice intilisation: =T read a file ; =F anaytical initilaistion
42   LOGICAL            ::   l_initdone = .false.
43   INTEGER     ::   nfld_3d
44   INTEGER     ::   nfld_2d
45
46   INTEGER     ::   jf_tem         ! index of temperature
47   INTEGER     ::   jf_sal         ! index of salinity
48   INTEGER     ::   jf_usp         ! index of u velocity component
49   INTEGER     ::   jf_vsp         ! index of v velocity component
50   INTEGER     ::   jf_ssh         ! index of sea surface height
51   INTEGER     ::   jf_e3t         ! index of first T level thickness
52   INTEGER     ::   jf_frq         ! index of fraction of qsr absorbed in the 1st T level
53
54   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_ssm_3d  ! structure of input fields (file information, fields read)
55   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_ssm_2d  ! structure of input fields (file information, fields read)
56
57   !!----------------------------------------------------------------------
58   !! NEMO/SAS 4.0 , NEMO Consortium (2018)
59   !! $Id$
60   !! Software governed by the CeCILL license (see ./LICENSE)
61   !!----------------------------------------------------------------------
62CONTAINS
63
64   SUBROUTINE sbc_ssm( kt )
65      !!----------------------------------------------------------------------
66      !!                  ***  ROUTINE sbc_ssm  ***
67      !!
68      !! ** Purpose :  Prepares dynamics and physics fields from a NEMO run
69      !!               for an off-line simulation using surface processes only
70      !!
71      !! ** Method : calculates the position of data
72      !!             - interpolates data if needed
73      !!----------------------------------------------------------------------
74      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
75      !
76      INTEGER  ::   ji, jj     ! dummy loop indices
77      REAL(wp) ::   ztinta     ! ratio applied to after  records when doing time interpolation
78      REAL(wp) ::   ztintb     ! ratio applied to before records when doing time interpolation
79      !!----------------------------------------------------------------------
80      !
81      IF( ln_timing )   CALL timing_start( 'sbc_ssm')
82     
83      IF ( l_sasread ) THEN
84         IF( nfld_3d > 0 ) CALL fld_read( kt, 1, sf_ssm_3d )      !==   read data at kt time step   ==!
85         IF( nfld_2d > 0 ) CALL fld_read( kt, 1, sf_ssm_2d )      !==   read data at kt time step   ==!
86         !
87         IF( ln_3d_uve ) THEN
88            IF( .NOT. ln_linssh ) THEN
89               e3t_m(:,:) = sf_ssm_3d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor
90            ELSE
91               e3t_m(:,:) = e3t_0(:,:,1)                                 ! vertical scale factor
92            ENDIF
93            ssu_m(:,:) = sf_ssm_3d(jf_usp)%fnow(:,:,1) * umask(:,:,1)    ! u-velocity
94            ssv_m(:,:) = sf_ssm_3d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1)    ! v-velocity
95         ELSE
96            IF( .NOT. ln_linssh ) THEN
97               e3t_m(:,:) = sf_ssm_2d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor
98            ELSE
99               e3t_m(:,:) = e3t_0(:,:,1)                                 ! vertical scale factor
100            ENDIF
101            ssu_m(:,:) = sf_ssm_2d(jf_usp)%fnow(:,:,1) * umask(:,:,1)    ! u-velocity
102            ssv_m(:,:) = sf_ssm_2d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1)    ! v-velocity
103         ENDIF
104         !
105         sst_m(:,:) = sf_ssm_2d(jf_tem)%fnow(:,:,1) * tmask(:,:,1)    ! temperature
106         sss_m(:,:) = sf_ssm_2d(jf_sal)%fnow(:,:,1) * tmask(:,:,1)    ! salinity
107         ssh_m(:,:) = sf_ssm_2d(jf_ssh)%fnow(:,:,1) * tmask(:,:,1)    ! sea surface height
108         IF( ln_read_frq ) THEN
109            frq_m(:,:) = sf_ssm_2d(jf_frq)%fnow(:,:,1) * tmask(:,:,1) ! solar penetration
110         ELSE
111            frq_m(:,:) = 1._wp
112         ENDIF
113      ELSE
114         sss_m(:,:) = 35._wp                             ! =35. to obtain a physical value for the freezing point
115         CALL eos_fzp( sss_m(:,:), sst_m(:,:) )          ! sst_m is set at the freezing point
116         ssu_m(:,:) = 0._wp
117         ssv_m(:,:) = 0._wp
118         ssh_m(:,:) = 0._wp
119         IF( .NOT. ln_linssh ) e3t_m(:,:) = e3t_0(:,:,1) !clem: necessary at least for sas2D
120         frq_m(:,:) = 1._wp                              !              - -
121         sshn (:,:) = 0._wp                              !              - -
122      ENDIF
123     
124      IF ( nn_ice == 1 ) THEN
125         tsn(:,:,1,jp_tem) = sst_m(:,:)
126         tsn(:,:,1,jp_sal) = sss_m(:,:)
127         tsb(:,:,1,jp_tem) = sst_m(:,:)
128         tsb(:,:,1,jp_sal) = sss_m(:,:)
129      ENDIF
130      ub (:,:,1) = ssu_m(:,:)
131      vb (:,:,1) = ssv_m(:,:)
132 
133      IF(sn_cfctl%l_prtctl) THEN            ! print control
134         CALL prt_ctl(tab2d_1=sst_m, clinfo1=' sst_m   - : ', mask1=tmask   )
135         CALL prt_ctl(tab2d_1=sss_m, clinfo1=' sss_m   - : ', mask1=tmask   )
136         CALL prt_ctl(tab2d_1=ssu_m, clinfo1=' ssu_m   - : ', mask1=umask   )
137         CALL prt_ctl(tab2d_1=ssv_m, clinfo1=' ssv_m   - : ', mask1=vmask   )
138         CALL prt_ctl(tab2d_1=ssh_m, clinfo1=' ssh_m   - : ', mask1=tmask   )
139         IF( .NOT.ln_linssh )   CALL prt_ctl(tab2d_1=ssh_m, clinfo1=' e3t_m   - : ', mask1=tmask   )
140         IF( ln_read_frq    )   CALL prt_ctl(tab2d_1=frq_m, clinfo1=' frq_m   - : ', mask1=tmask   )
141      ENDIF
142      !
143      IF( l_initdone ) THEN          !   Mean value at each nn_fsbc time-step   !
144         CALL iom_put( 'ssu_m', ssu_m )
145         CALL iom_put( 'ssv_m', ssv_m )
146         CALL iom_put( 'sst_m', sst_m )
147         CALL iom_put( 'sss_m', sss_m )
148         CALL iom_put( 'ssh_m', ssh_m )
149         IF( .NOT.ln_linssh )   CALL iom_put( 'e3t_m', e3t_m )
150         IF( ln_read_frq    )   CALL iom_put( 'frq_m', frq_m )
151      ENDIF
152      !
153      IF( ln_timing )   CALL timing_stop( 'sbc_ssm')
154      !
155   END SUBROUTINE sbc_ssm
156
157
158   SUBROUTINE sbc_ssm_init
159      !!----------------------------------------------------------------------
160      !!                  ***  ROUTINE sbc_ssm_init  ***
161      !!
162      !! ** Purpose :   Initialisation of sea surface mean data     
163      !!----------------------------------------------------------------------
164      INTEGER  :: ierr, ierr0, ierr1, ierr2, ierr3   ! return error code
165      INTEGER  :: ifpr                               ! dummy loop indice
166      INTEGER  :: inum, idv, idimv, jpm              ! local integer
167      INTEGER  ::   ios                              ! Local integer output status for namelist read
168      !!
169      CHARACTER(len=100)                     ::  cn_dir       ! Root directory for location of core files
170      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::  slf_3d       ! array of namelist information on the fields to read
171      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::  slf_2d       ! array of namelist information on the fields to read
172      TYPE(FLD_N) ::   sn_tem, sn_sal                     ! information about the fields to be read
173      TYPE(FLD_N) ::   sn_usp, sn_vsp
174      TYPE(FLD_N) ::   sn_ssh, sn_e3t, sn_frq
175      !!
176      NAMELIST/namsbc_sas/ l_sasread, cn_dir, ln_3d_uve, ln_read_frq,   &
177         &                 sn_tem, sn_sal, sn_usp, sn_vsp, sn_ssh, sn_e3t, sn_frq
178      !!----------------------------------------------------------------------
179      !
180      IF( ln_rstart .AND. nn_components == jp_iam_sas )   RETURN
181      !
182      IF(lwp) THEN
183         WRITE(numout,*)
184         WRITE(numout,*) 'sbc_ssm_init : sea surface mean data initialisation '
185         WRITE(numout,*) '~~~~~~~~~~~~ '
186      ENDIF
187      !
188      REWIND( numnam_ref )              ! Namelist namsbc_sas in reference namelist : Input fields
189      READ  ( numnam_ref, namsbc_sas, IOSTAT = ios, ERR = 901)
190901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_sas in reference namelist' )
191      REWIND( numnam_cfg )              ! Namelist namsbc_sas in configuration namelist : Input fields
192      READ  ( numnam_cfg, namsbc_sas, IOSTAT = ios, ERR = 902 )
193902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_sas in configuration namelist' )
194      IF(lwm) WRITE ( numond, namsbc_sas )
195      !           
196      IF(lwp) THEN                              ! Control print
197         WRITE(numout,*) '   Namelist namsbc_sas'
198         WRITE(numout,*) '      Initialisation using an input file                                 l_sasread   = ', l_sasread 
199         WRITE(numout,*) '      Are we supplying a 3D u,v and e3 field                             ln_3d_uve   = ', ln_3d_uve
200         WRITE(numout,*) '      Are we reading frq (fraction of qsr absorbed in the 1st T level)   ln_read_frq = ', ln_read_frq
201      ENDIF
202      !
203      !! switch off stuff that isn't sensible with a standalone module
204      !! note that we need sbc_ssm called first in sbc
205      !
206      IF( ln_apr_dyn ) THEN
207         IF( lwp ) WRITE(numout,*) '         ==>>>   No atmospheric gradient needed with StandAlone Surface scheme'
208         ln_apr_dyn = .FALSE.
209      ENDIF
210      IF( ln_rnf ) THEN
211         IF( lwp ) WRITE(numout,*) '         ==>>>   No runoff needed with StandAlone Surface scheme'
212         ln_rnf = .FALSE.
213      ENDIF
214      IF( ln_ssr ) THEN
215         IF( lwp ) WRITE(numout,*) '         ==>>>   No surface relaxation needed with StandAlone Surface scheme'
216         ln_ssr = .FALSE.
217      ENDIF
218      IF( nn_fwb > 0 ) THEN
219         IF( lwp ) WRITE(numout,*) '         ==>>>   No freshwater budget adjustment needed with StandAlone Surface scheme'
220         nn_fwb = 0
221      ENDIF
222      IF( ln_closea ) THEN
223         IF( lwp ) WRITE(numout,*) '         ==>>>   No closed seas adjustment needed with StandAlone Surface scheme'
224         ln_closea = .false.
225      ENDIF
226     
227      !                 
228      IF( l_sasread ) THEN                       ! store namelist information in an array
229         !
230         !! following code is a bit messy, but distinguishes between when u,v are 3d arrays and
231         !! when we have other 3d arrays that we need to read in
232         !! so if a new field is added i.e. jf_new, just give it the next integer in sequence
233         !! for the corresponding dimension (currently if ln_3d_uve is true, 4 for 2d and 3 for 3d,
234         !! alternatively if ln_3d_uve is false, 6 for 2d and 1 for 3d), reset nfld_3d, nfld_2d,
235         !! and the rest of the logic should still work
236         !
237         jf_tem = 1   ;   jf_ssh = 3   ! default 2D fields index
238         jf_sal = 2   ;   jf_frq = 4   !
239         !
240         IF( ln_3d_uve ) THEN
241            jf_usp = 1   ;   jf_vsp = 2   ;   jf_e3t = 3     ! define 3D fields index
242            nfld_3d  = 2 + COUNT( (/.NOT.ln_linssh/) )       ! number of 3D fields to read
243            nfld_2d  = 3 + COUNT( (/ln_read_frq/) )          ! number of 2D fields to read
244         ELSE
245            jf_usp = 4   ;   jf_e3t = 6                      ! update 2D fields index
246            jf_vsp = 5   ;   jf_frq = 6 + COUNT( (/.NOT.ln_linssh/) )
247            !
248            nfld_3d  = 0                                     ! no 3D fields to read
249            nfld_2d  = 5 + COUNT( (/.NOT.ln_linssh/) ) + COUNT( (/ln_read_frq/) )    ! number of 2D fields to read
250         ENDIF
251         !
252         IF( nfld_3d > 0 ) THEN
253            ALLOCATE( slf_3d(nfld_3d), STAT=ierr )         ! set slf structure
254            IF( ierr > 0 ) THEN
255               CALL ctl_stop( 'sbc_ssm_init: unable to allocate slf 3d structure' )   ;   RETURN
256            ENDIF
257            slf_3d(jf_usp) = sn_usp
258            slf_3d(jf_vsp) = sn_vsp
259            IF( .NOT.ln_linssh )   slf_3d(jf_e3t) = sn_e3t
260         ENDIF
261         !
262         IF( nfld_2d > 0 ) THEN
263            ALLOCATE( slf_2d(nfld_2d), STAT=ierr )         ! set slf structure
264            IF( ierr > 0 ) THEN
265               CALL ctl_stop( 'sbc_ssm_init: unable to allocate slf 2d structure' )   ;   RETURN
266            ENDIF
267            slf_2d(jf_tem) = sn_tem   ;   slf_2d(jf_sal) = sn_sal   ;   slf_2d(jf_ssh) = sn_ssh
268            IF( ln_read_frq )   slf_2d(jf_frq) = sn_frq
269            IF( .NOT. ln_3d_uve ) THEN
270               slf_2d(jf_usp) = sn_usp ; slf_2d(jf_vsp) = sn_vsp
271               IF( .NOT.ln_linssh )   slf_2d(jf_e3t) = sn_e3t
272            ENDIF
273         ENDIF
274         !
275         ierr1 = 0    ! default definition if slf_?d(ifpr)%ln_tint = .false.
276         IF( nfld_3d > 0 ) THEN
277            ALLOCATE( sf_ssm_3d(nfld_3d), STAT=ierr )         ! set sf structure
278            IF( ierr > 0 ) THEN
279               CALL ctl_stop( 'sbc_ssm_init: unable to allocate sf structure' )   ;   RETURN
280            ENDIF
281            DO ifpr = 1, nfld_3d
282                                            ALLOCATE( sf_ssm_3d(ifpr)%fnow(jpi,jpj,jpk)    , STAT=ierr0 )
283               IF( slf_3d(ifpr)%ln_tint )   ALLOCATE( sf_ssm_3d(ifpr)%fdta(jpi,jpj,jpk,2)  , STAT=ierr1 )
284               IF( ierr0 + ierr1 > 0 ) THEN
285                  CALL ctl_stop( 'sbc_ssm_init : unable to allocate sf_ssm_3d array structure' )   ;   RETURN
286               ENDIF
287            END DO
288            !                                         ! fill sf with slf_i and control print
289            CALL fld_fill( sf_ssm_3d, slf_3d, cn_dir, 'sbc_ssm_init', '3D Data in file', 'namsbc_ssm' )
290         ENDIF
291         !
292         IF( nfld_2d > 0 ) THEN
293            ALLOCATE( sf_ssm_2d(nfld_2d), STAT=ierr )         ! set sf structure
294            IF( ierr > 0 ) THEN
295               CALL ctl_stop( 'sbc_ssm_init: unable to allocate sf 2d structure' )   ;   RETURN
296            ENDIF
297            DO ifpr = 1, nfld_2d
298                                            ALLOCATE( sf_ssm_2d(ifpr)%fnow(jpi,jpj,1)    , STAT=ierr0 )
299               IF( slf_2d(ifpr)%ln_tint )   ALLOCATE( sf_ssm_2d(ifpr)%fdta(jpi,jpj,1,2)  , STAT=ierr1 )
300               IF( ierr0 + ierr1 > 0 ) THEN
301                  CALL ctl_stop( 'sbc_ssm_init : unable to allocate sf_ssm_2d array structure' )   ;   RETURN
302               ENDIF
303            END DO
304            !
305            CALL fld_fill( sf_ssm_2d, slf_2d, cn_dir, 'sbc_ssm_init', '2D Data in file', 'namsbc_ssm' )
306         ENDIF
307         !
308         IF( nfld_3d > 0 )   DEALLOCATE( slf_3d, STAT=ierr )
309         IF( nfld_2d > 0 )   DEALLOCATE( slf_2d, STAT=ierr )
310         !
311      ENDIF
312      !
313      CALL sbc_ssm( nit000 )   ! need to define ss?_m arrays used in iceistate
314      l_initdone = .TRUE.
315      !
316   END SUBROUTINE sbc_ssm_init
317
318   !!======================================================================
319END MODULE sbcssm
Note: See TracBrowser for help on using the repository browser.