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/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/tests/STATION_ASF/MY_SRC – NEMO

source: NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/tests/STATION_ASF/MY_SRC/sbcssm.F90 @ 13655

Last change on this file since 13655 was 13655, checked in by laurent, 3 years ago

Commit all my dev of 2020!

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