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 branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/SAS_SRC – NEMO

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/SAS_SRC/sbcssm.F90 @ 7795

Last change on this file since 7795 was 5602, checked in by cbricaud, 9 years ago

merge change from trunk rev 5003 to 5519 ( rev where branche 3.6_stable were created )

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