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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssm.F90 @ 4416

Last change on this file since 4416 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 9.5 KB
Line 
1MODULE sbcssm
2   !!======================================================================
3   !!                       ***  MODULE  sbcssm  ***
4   !! Surface module :  provide time-mean ocean surface variables
5   !!======================================================================
6   !! History :  9.0  ! 2006-07  (G. Madec)  Original code
7   !!            3.3  ! 2010-10  (C. Bricaud, G. Madec)  add the Patm forcing for sea-ice
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   sbc_ssm        : calculate sea surface mean currents, temperature, 
12   !!                    and salinity over nn_fsbc time-step
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE sbc_oce         ! surface boundary condition: ocean fields
17   USE sbcapr          ! surface boundary condition: atmospheric pressure
18   USE prtctl          ! Print control                    (prt_ctl routine)
19   USE restart         ! ocean restart
20   USE iom
21   USE in_out_manager  ! I/O manager
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   sbc_ssm    ! routine called by step.F90
27
28   !! * Control permutation of array indices
29#  include "oce_ftrans.h90"
30#  include "dom_oce_ftrans.h90"
31#  include "sbc_oce_ftrans.h90"
32   
33   !! * Substitutions
34#  include "domzgr_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
37   !! $Id$
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE sbc_ssm( kt )
43      !!---------------------------------------------------------------------
44      !!                     ***  ROUTINE sbc_oce  ***
45      !!                     
46      !! ** Purpose :   provide ocean surface variable to sea-surface boundary
47      !!                condition computation
48      !!               
49      !! ** Method  :   compute mean surface velocity (2 components at U and
50      !!      V-points) [m/s], temperature [Celcius] and salinity [psu] over
51      !!      the periode (kt - nn_fsbc) to kt
52      !!         Note that the inverse barometer ssh (i.e. ssh associated with Patm)
53      !!      is add to ssh_m when ln_apr_dyn = T. Required for sea-ice dynamics.
54      !!---------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kt   ! ocean time step
56      !
57      REAL(wp) ::   zcoef, zf_sbc       ! local scalar
58      !!---------------------------------------------------------------------
59      !                                                   ! ---------------------------------------- !
60      IF( nn_fsbc == 1 ) THEN                             !      Instantaneous surface fields        !
61         !                                                ! ---------------------------------------- !
62         IF( kt == nit000 ) THEN
63            IF(lwp) WRITE(numout,*)
64            IF(lwp) WRITE(numout,*) 'sbc_ssm : sea surface mean fields, nn_fsbc=1 : instantaneous values'
65            IF(lwp) WRITE(numout,*) '~~~~~~~ '
66         ENDIF
67         !
68         ssu_m(:,:) = ub(:,:,1)
69         ssv_m(:,:) = vb(:,:,1)
70         sst_m(:,:) = tn(:,:,1)
71         sss_m(:,:) = sn(:,:,1)
72         !                          ! removed inverse barometer ssh when Patm forcing is used (for sea-ice dynamics)
73         IF( ln_apr_dyn ) THEN   ;   ssh_m(:,:) = sshn(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) )
74         ELSE                    ;   ssh_m(:,:) = sshn(:,:)
75         ENDIF
76
77         !
78      ELSE
79         !                                                ! ---------------------------------------- !
80         IF( kt == nit000) THEN                           !       Initialisation: 1st time-step      !
81            !                                             ! ---------------------------------------- !
82            IF(lwp) WRITE(numout,*)
83            IF(lwp) WRITE(numout,*) 'sbc_ssm : sea surface mean fields'
84            !
85            IF( ln_rstart .AND. iom_varid( numror, 'nn_fsbc', ldstop = .FALSE. ) > 0 ) THEN
86               CALL iom_get( numror               , 'nn_fsbc', zf_sbc )   ! sbc frequency of previous run
87               CALL iom_get( numror, jpdom_autoglo, 'ssu_m'  , ssu_m  )   ! sea surface mean velocity    (T-point)
88               CALL iom_get( numror, jpdom_autoglo, 'ssv_m'  , ssv_m  )   !   "         "    velocity    (V-point)
89               CALL iom_get( numror, jpdom_autoglo, 'sst_m'  , sst_m  )   !   "         "    temperature (T-point)
90               CALL iom_get( numror, jpdom_autoglo, 'sss_m'  , sss_m  )   !   "         "    salinity    (T-point)
91               CALL iom_get( numror, jpdom_autoglo, 'ssh_m'  , ssh_m  )   !   "         "    height      (T-point)
92               !
93               IF( zf_sbc /= REAL( nn_fsbc, wp ) ) THEN      ! nn_fsbc has changed between 2 runs
94                  IF(lwp) WRITE(numout,*) '~~~~~~~   restart with a change in the frequency of mean ',   &
95                     &                    'from ', zf_sbc, ' to ', nn_fsbc
96                  zcoef = REAL( nn_fsbc - 1, wp ) / zf_sbc
97                  ssu_m(:,:) = zcoef * ssu_m(:,:)
98                  ssv_m(:,:) = zcoef * ssv_m(:,:)
99                  sst_m(:,:) = zcoef * sst_m(:,:)
100                  sss_m(:,:) = zcoef * sss_m(:,:)
101                  ssh_m(:,:) = zcoef * ssh_m(:,:)
102               ELSE
103                  IF(lwp) WRITE(numout,*) '~~~~~~~   mean fields read in the ocean restart file'
104               ENDIF
105            ELSE
106               IF(lwp) WRITE(numout,*) '~~~~~~~   mean fields initialised to instantaneous values'
107               zcoef = REAL( nn_fsbc - 1, wp )
108               ssu_m(:,:) = zcoef * ub(:,:,1)
109               ssv_m(:,:) = zcoef * vb(:,:,1)
110               sst_m(:,:) = zcoef * tn(:,:,1)
111               sss_m(:,:) = zcoef * sn(:,:,1)
112               !                          ! removed inverse barometer ssh when Patm forcing is used
113               IF( ln_apr_dyn ) THEN   ;   ssh_m(:,:) = zcoef * ( sshn(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) ) )
114               ELSE                    ;   ssh_m(:,:) = zcoef *   sshn(:,:)
115               ENDIF
116
117            ENDIF
118            !                                             ! ---------------------------------------- !
119         ELSEIF( MOD( kt - 2 , nn_fsbc ) == 0 ) THEN      !   Initialisation: New mean computation   !
120            !                                             ! ---------------------------------------- !
121            ssu_m(:,:) = 0.e0      ! reset to zero ocean mean sbc fields
122            ssv_m(:,:) = 0.e0
123            sst_m(:,:) = 0.e0
124            sss_m(:,:) = 0.e0
125            ssh_m(:,:) = 0.e0
126         ENDIF
127         !                                                ! ---------------------------------------- !
128         !                                                !        Cumulate at each time step        !
129         !                                                ! ---------------------------------------- !
130         ssu_m(:,:) = ssu_m(:,:) + ub(:,:,1)
131         ssv_m(:,:) = ssv_m(:,:) + vb(:,:,1)
132         sst_m(:,:) = sst_m(:,:) + tn(:,:,1)
133         sss_m(:,:) = sss_m(:,:) + sn(:,:,1)
134         !                          ! removed inverse barometer ssh when Patm forcing is used (for sea-ice dynamics)
135         IF( ln_apr_dyn ) THEN   ;   ssh_m(:,:) = ssh_m(:,:) + sshn(:,:) - 0.5 *  ( ssh_ib(:,:) + ssh_ibb(:,:) )
136         ELSE                    ;   ssh_m(:,:) = ssh_m(:,:) + sshn(:,:)
137         ENDIF
138
139         !                                                ! ---------------------------------------- !
140         IF( MOD( kt - 1 , nn_fsbc ) == 0 ) THEN          !   Mean value at each nn_fsbc time-step   !
141            !                                             ! ---------------------------------------- !
142            zcoef = 1. / REAL( nn_fsbc, wp )
143            sst_m(:,:) = sst_m(:,:) * zcoef           ! mean SST             [Celcius]
144            sss_m(:,:) = sss_m(:,:) * zcoef           ! mean SSS             [psu]
145            ssu_m(:,:) = ssu_m(:,:) * zcoef           ! mean suface current  [m/s]
146            ssv_m(:,:) = ssv_m(:,:) * zcoef           !
147            ssh_m(:,:) = ssh_m(:,:) * zcoef           ! mean SSH             [m]
148            !
149         ENDIF
150         !                                                ! ---------------------------------------- !
151         IF( lrst_oce ) THEN                              !      Write in the ocean restart file     !
152            !                                             ! ---------------------------------------- !
153            IF(lwp) WRITE(numout,*)
154            IF(lwp) WRITE(numout,*) 'sbc_ssm : sea surface mean fields written in ocean restart file ',   &
155               &                    'at it= ', kt,' date= ', ndastp
156            IF(lwp) WRITE(numout,*) '~~~~~~~'
157            zf_sbc = REAL( nn_fsbc, wp )
158            CALL iom_rstput( kt, nitrst, numrow, 'nn_fsbc', zf_sbc )    ! sbc frequency
159            CALL iom_rstput( kt, nitrst, numrow, 'ssu_m'  , ssu_m  )    ! sea surface mean fields
160            CALL iom_rstput( kt, nitrst, numrow, 'ssv_m'  , ssv_m  )
161            CALL iom_rstput( kt, nitrst, numrow, 'sst_m'  , sst_m  )
162            CALL iom_rstput( kt, nitrst, numrow, 'sss_m'  , sss_m  )
163            CALL iom_rstput( kt, nitrst, numrow, 'ssh_m'  , ssh_m  )
164            !
165         ENDIF
166         !
167      ENDIF
168      !
169   END SUBROUTINE sbc_ssm
170
171   !!======================================================================
172END MODULE sbcssm
Note: See TracBrowser for help on using the repository browser.