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.
Changeset 6140 for trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90 – NEMO

Ignore:
Timestamp:
2015-12-21T12:35:23+01:00 (8 years ago)
Author:
timgraham
Message:

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r5836 r6140  
    1717 
    1818   !!---------------------------------------------------------------------- 
    19    !!   sbc_init       : read namsbc namelist 
    20    !!   sbc            : surface ocean momentum, heat and freshwater boundary conditions 
     19   !!   sbc_init      : read namsbc namelist 
     20   !!   sbc           : surface ocean momentum, heat and freshwater boundary conditions 
    2121   !!---------------------------------------------------------------------- 
    22    USE oce              ! ocean dynamics and tracers 
    23    USE dom_oce          ! ocean space and time domain 
    24    USE phycst           ! physical constants 
    25    USE sbc_oce          ! Surface boundary condition: ocean fields 
    26    USE trc_oce          ! shared ocean-passive tracers variables 
    27    USE sbc_ice          ! Surface boundary condition: ice fields 
    28    USE sbcdcy           ! surface boundary condition: diurnal cycle 
    29    USE sbcssm           ! surface boundary condition: sea-surface mean variables 
    30    USE sbcana           ! surface boundary condition: analytical formulation 
    31    USE sbcflx           ! surface boundary condition: flux formulation 
    32    USE sbcblk_clio      ! surface boundary condition: bulk formulation : CLIO 
    33    USE sbcblk_core      ! surface boundary condition: bulk formulation : CORE 
    34    USE sbcblk_mfs       ! surface boundary condition: bulk formulation : MFS 
    35    USE sbcice_if        ! surface boundary condition: ice-if sea-ice model 
    36    USE sbcice_lim       ! surface boundary condition: LIM 3.0 sea-ice model 
    37    USE sbcice_lim_2     ! surface boundary condition: LIM 2.0 sea-ice model 
    38    USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model 
    39    USE sbccpl           ! surface boundary condition: coupled florulation 
    40    USE cpl_oasis3       ! OASIS routines for coupling 
    41    USE sbcssr           ! surface boundary condition: sea surface restoring 
    42    USE sbcrnf           ! surface boundary condition: runoffs 
    43    USE sbcisf           ! surface boundary condition: ice shelf 
    44    USE sbcfwb           ! surface boundary condition: freshwater budget 
    45    USE closea           ! closed sea 
    46    USE icbstp           ! Icebergs! 
    47  
    48    USE prtctl           ! Print control                    (prt_ctl routine) 
    49    USE iom              ! IOM library 
    50    USE in_out_manager   ! I/O manager 
    51    USE lib_mpp          ! MPP library 
    52    USE timing           ! Timing 
    53    USE sbcwave          ! Wave module 
    54    USE bdy_par          ! Require lk_bdy 
     22   USE oce            ! ocean dynamics and tracers 
     23   USE dom_oce        ! ocean space and time domain 
     24   USE phycst         ! physical constants 
     25   USE sbc_oce        ! Surface boundary condition: ocean fields 
     26   USE trc_oce        ! shared ocean-passive tracers variables 
     27   USE sbc_ice        ! Surface boundary condition: ice fields 
     28   USE sbcdcy         ! surface boundary condition: diurnal cycle 
     29   USE sbcssm         ! surface boundary condition: sea-surface mean variables 
     30   USE sbcana         ! surface boundary condition: analytical formulation 
     31   USE sbcflx         ! surface boundary condition: flux formulation 
     32   USE sbcblk_clio    ! surface boundary condition: bulk formulation : CLIO 
     33   USE sbcblk_core    ! surface boundary condition: bulk formulation : CORE 
     34   USE sbcblk_mfs     ! surface boundary condition: bulk formulation : MFS 
     35   USE sbcice_if      ! surface boundary condition: ice-if sea-ice model 
     36   USE sbcice_lim     ! surface boundary condition: LIM 3.0 sea-ice model 
     37   USE sbcice_lim_2   ! surface boundary condition: LIM 2.0 sea-ice model 
     38   USE sbcice_cice    ! surface boundary condition: CICE    sea-ice model 
     39   USE sbccpl         ! surface boundary condition: coupled florulation 
     40   USE cpl_oasis3     ! OASIS routines for coupling 
     41   USE sbcssr         ! surface boundary condition: sea surface restoring 
     42   USE sbcrnf         ! surface boundary condition: runoffs 
     43   USE sbcisf         ! surface boundary condition: ice shelf 
     44   USE sbcfwb         ! surface boundary condition: freshwater budget 
     45   USE closea         ! closed sea 
     46   USE icbstp         ! Icebergs 
     47   USE traqsr         ! active tracers: light penetration 
     48   USE sbcwave        ! Wave module 
     49   USE bdy_par        ! Require lk_bdy 
     50   ! 
     51   USE prtctl         ! Print control                    (prt_ctl routine) 
     52   USE iom            ! IOM library 
     53   USE in_out_manager ! I/O manager 
     54   USE lib_mpp        ! MPP library 
     55   USE timing         ! Timing 
     56 
     57   USE diurnal_bulk, ONLY: & 
     58      & ln_diurnal_only  
    5559 
    5660   IMPLICIT NONE 
     
    6266   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations) 
    6367       
    64    !! * Substitutions 
    65 #  include "domzgr_substitute.h90" 
    6668   !!---------------------------------------------------------------------- 
    6769   !! NEMO/OPA 4.0 , NEMO-consortium (2011)  
     
    8587      INTEGER ::   icpt   ! local integer 
    8688      !! 
    87       NAMELIST/namsbc/ nn_fsbc   , ln_ana    , ln_flx, ln_blk_clio, ln_blk_core, ln_mixcpl,   & 
    88          &             ln_blk_mfs, ln_apr_dyn, nn_ice, nn_ice_embd, ln_dm2dc   , ln_rnf   ,   & 
    89          &             ln_ssr    , nn_isf    , nn_fwb, ln_cdgw    , ln_wave    , ln_sdw   ,   & 
    90          &             nn_lsm    , nn_limflx , nn_components, ln_cpl 
     89      NAMELIST/namsbc/ nn_fsbc  , ln_ana   , ln_flx, ln_blk_clio, ln_blk_core, ln_blk_mfs,   & 
     90         &             ln_cpl   , ln_mixcpl, nn_components      , nn_limflx  ,               & 
     91         &             ln_traqsr, ln_dm2dc ,                                                 &   
     92         &             nn_ice   , nn_ice_embd,                                               & 
     93         &             ln_rnf   , ln_ssr   , ln_isf   , nn_fwb    , ln_apr_dyn,              & 
     94         &             ln_wave  ,                                                            & 
     95         &             nn_lsm    
    9196      INTEGER  ::   ios 
    9297      INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
    9398      LOGICAL  ::   ll_purecpl 
    9499      !!---------------------------------------------------------------------- 
    95  
     100      ! 
    96101      IF(lwp) THEN 
    97102         WRITE(numout,*) 
     
    99104         WRITE(numout,*) '~~~~~~~~ ' 
    100105      ENDIF 
    101  
     106      ! 
    102107      REWIND( numnam_ref )              ! Namelist namsbc in reference namelist : Surface boundary 
    103108      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) 
    104 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) 
    105  
     109901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) 
     110      ! 
    106111      REWIND( numnam_cfg )              ! Namelist namsbc in configuration namelist : Parameters of the run 
    107112      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) 
    108 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) 
    109       IF(lwm) WRITE ( numond, namsbc ) 
    110  
     113902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) 
     114      IF(lwm) WRITE( numond, namsbc ) 
     115      ! 
    111116      !                          ! overwrite namelist parameter using CPP key information 
    112117      IF( Agrif_Root() ) THEN                ! AGRIF zoom 
     
    119124          nn_ice      =   0 
    120125      ENDIF 
    121  
     126      ! 
    122127      IF(lwp) THEN               ! Control print 
    123128         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
    124129         WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc 
    125          WRITE(numout,*) '           Type of sbc : ' 
    126          WRITE(numout,*) '              analytical formulation                     ln_ana      = ', ln_ana 
    127          WRITE(numout,*) '              flux       formulation                     ln_flx      = ', ln_flx 
    128          WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_clio = ', ln_blk_clio 
    129          WRITE(numout,*) '              CORE bulk  formulation                     ln_blk_core = ', ln_blk_core 
    130          WRITE(numout,*) '              MFS  bulk  formulation                     ln_blk_mfs  = ', ln_blk_mfs 
    131          WRITE(numout,*) '              ocean-atmosphere coupled formulation       ln_cpl      = ', ln_cpl 
    132          WRITE(numout,*) '              forced-coupled mixed formulation           ln_mixcpl   = ', ln_mixcpl 
    133          WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis    = ', lk_oasis 
    134          WRITE(numout,*) '              components of your executable            nn_components = ', nn_components 
    135          WRITE(numout,*) '              Multicategory heat flux formulation (LIM3) nn_limflx   = ', nn_limflx 
     130         WRITE(numout,*) '           Type of air-sea fluxes : ' 
     131         WRITE(numout,*) '              analytical formulation                     ln_ana        = ', ln_ana 
     132         WRITE(numout,*) '              flux       formulation                     ln_flx        = ', ln_flx 
     133         WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_clio   = ', ln_blk_clio 
     134         WRITE(numout,*) '              CORE bulk  formulation                     ln_blk_core   = ', ln_blk_core 
     135         WRITE(numout,*) '              MFS  bulk  formulation                     ln_blk_mfs    = ', ln_blk_mfs 
     136         WRITE(numout,*) '           Type of coupling (Ocean/Ice/Atmosphere) : ' 
     137         WRITE(numout,*) '              ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
     138         WRITE(numout,*) '              forced-coupled mixed formulation           ln_mixcpl     = ', ln_mixcpl 
     139         WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
     140         WRITE(numout,*) '              components of your executable              nn_components = ', nn_components 
     141         WRITE(numout,*) '              Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
     142         WRITE(numout,*) '           Sea-ice : ' 
     143         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice  
     144         WRITE(numout,*) '              ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
    136145         WRITE(numout,*) '           Misc. options of sbc : ' 
    137          WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn  = ', ln_apr_dyn 
    138          WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice      = ', nn_ice  
    139          WRITE(numout,*) '              ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd = ', nn_ice_embd 
    140          WRITE(numout,*) '              daily mean to diurnal cycle qsr            ln_dm2dc    = ', ln_dm2dc  
    141          WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf      = ', ln_rnf 
    142          WRITE(numout,*) '              iceshelf formulation                       nn_isf      = ', nn_isf 
    143          WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr      = ', ln_ssr 
    144          WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb      = ', nn_fwb 
    145          WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea   = ', nn_closea 
    146          WRITE(numout,*) '              n. of iterations if land-sea-mask applied  nn_lsm      = ', nn_lsm 
    147       ENDIF 
    148  
    149       ! LIM3 Multi-category heat flux formulation 
    150       SELECT CASE ( nn_limflx) 
    151       CASE ( -1 ) 
    152          IF(lwp) WRITE(numout,*) '              Use of per-category fluxes (nn_limflx = -1) ' 
    153       CASE ( 0  ) 
    154          IF(lwp) WRITE(numout,*) '              Average per-category fluxes (nn_limflx = 0) '  
    155       CASE ( 1  ) 
    156          IF(lwp) WRITE(numout,*) '              Average then redistribute per-category fluxes (nn_limflx = 1) ' 
    157       CASE ( 2  ) 
    158          IF(lwp) WRITE(numout,*) '              Redistribute a single flux over categories (nn_limflx = 2) ' 
    159       END SELECT 
    160       ! 
    161       IF ( nn_components /= jp_iam_nemo .AND. .NOT. lk_oasis )   & 
    162          &      CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
    163       IF ( nn_components == jp_iam_opa .AND. ln_cpl )   & 
    164          &      CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA' ) 
    165       IF ( nn_components == jp_iam_opa .AND. ln_mixcpl )   & 
    166          &      CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
    167       IF ( ln_cpl .AND. .NOT. lk_oasis )    & 
    168          &      CALL ctl_stop( 'STOP', 'sbc_init : OASIS-coupled atmosphere model, but key_oasis3 disabled' ) 
     146         WRITE(numout,*) '              Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
     147         WRITE(numout,*) '                 daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc  
     148         WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
     149         WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
     150         WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn    = ', ln_apr_dyn 
     151         WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf        = ', ln_rnf 
     152         WRITE(numout,*) '              iceshelf formulation                       ln_isf        = ', ln_isf 
     153         WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
     154         WRITE(numout,*) '              nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
     155         WRITE(numout,*) '              surface wave                               ln_wave       = ', ln_wave   
     156      ENDIF 
     157      ! 
     158      IF(lwp) THEN 
     159         WRITE(numout,*) 
     160         SELECT CASE ( nn_limflx )        ! LIM3 Multi-category heat flux formulation 
     161         CASE ( -1 )   ;   WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
     162         CASE ( 0  )   ;   WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) '  
     163         CASE ( 1  )   ;   WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
     164         CASE ( 2  )   ;   WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     165         END SELECT 
     166      ENDIF 
     167      ! 
     168      IF( nn_components /= jp_iam_nemo .AND. .NOT. lk_oasis )   & 
     169         &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     170      IF( nn_components == jp_iam_opa .AND. ln_cpl )   & 
     171         &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA' ) 
     172      IF( nn_components == jp_iam_opa .AND. ln_mixcpl )   & 
     173         &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     174      IF( ln_cpl .AND. .NOT. lk_oasis )    & 
     175         &      CALL ctl_stop( 'sbc_init : OASIS-coupled atmosphere model, but key_oasis3 disabled' ) 
    169176      IF( ln_mixcpl .AND. .NOT. lk_oasis )    & 
    170177         &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires the cpp key key_oasis3' ) 
     
    178185 
    179186      !                          ! Checks: 
    180       IF( nn_isf .EQ. 0 ) THEN                      ! variable initialisation if no ice shelf  
    181          IF( sbc_isf_alloc() /= 0 )   CALL ctl_stop( 'sbc_init : unable to allocate sbc_isf arrays' ) 
     187      IF( .NOT. ln_isf ) THEN                      ! variable initialisation if no ice shelf  
     188         IF( sbc_isf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_isf arrays' ) 
    182189         fwfisf  (:,:)   = 0.0_wp ; fwfisf_b  (:,:)   = 0.0_wp 
    183190         risf_tsc(:,:,:) = 0.0_wp ; risf_tsc_b(:,:,:) = 0.0_wp 
    184          rdivisf       = 0.0_wp 
    185191      END IF 
    186       IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa )   fr_i(:,:) = 0.e0 ! no ice in the domain, ice fraction is always zero 
    187  
    188       sfx(:,:) = 0.0_wp                            ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero)  
     192      IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! no ice in the domain, ice fraction is always zero 
     193 
     194      sfx(:,:) = 0._wp                             ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero)  
    189195                                                   ! only if sea-ice is present 
    190196  
    191       fmmflx(:,:) = 0.0_wp                        ! freezing-melting array initialisation 
     197      fmmflx(:,:) = 0._wp                          ! freezing-melting array initialisation 
    192198       
    193       taum(:,:) = 0.0_wp                           ! Initialise taum for use in gls in case of reduced restart 
     199      taum(:,:) = 0._wp                            ! Initialise taum for use in gls in case of reduced restart 
    194200 
    195201      !                                            ! restartability    
     
    214220         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
    215221       
    216       IF ( ln_wave ) THEN 
    217       !Activated wave module but neither drag nor stokes drift activated 
    218          IF ( .NOT.(ln_cdgw .OR. ln_sdw) )   THEN 
    219             CALL ctl_warn( 'Ask for wave coupling but nor drag coefficient (ln_cdgw=F) neither stokes drift activated (ln_sdw=F)' ) 
    220       !drag coefficient read from wave model definable only with mfs bulk formulae and core  
    221          ELSEIF (ln_cdgw .AND. .NOT.(ln_blk_mfs .OR. ln_blk_core) )       THEN        
    222              CALL ctl_stop( 'drag coefficient read from wave model definable only with mfs bulk formulae and core') 
    223          ENDIF 
    224       ELSE 
    225       IF ( ln_cdgw .OR. ln_sdw  )                                                           &  
    226          &   CALL ctl_stop( 'Not Activated Wave Module (ln_wave=F) but asked coupling ',    & 
    227          &                  'with drag coefficient (ln_cdgw =T) or Stokes drift (ln_sdw=T) ') 
    228       ENDIF  
    229222      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    230223      ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl 
     
    245238      IF(lwp) THEN 
    246239         WRITE(numout,*) 
    247          IF( nsbc == jp_gyre    )   WRITE(numout,*) '              GYRE analytical formulation' 
    248          IF( nsbc == jp_ana     )   WRITE(numout,*) '              analytical formulation' 
    249          IF( nsbc == jp_flx     )   WRITE(numout,*) '              flux formulation' 
    250          IF( nsbc == jp_clio    )   WRITE(numout,*) '              CLIO bulk formulation' 
    251          IF( nsbc == jp_core    )   WRITE(numout,*) '              CORE bulk formulation' 
    252          IF( nsbc == jp_purecpl )   WRITE(numout,*) '              pure coupled formulation' 
    253          IF( nsbc == jp_mfs     )   WRITE(numout,*) '              MFS Bulk formulation' 
    254          IF( nsbc == jp_none    )   WRITE(numout,*) '              OPA coupled to SAS via oasis' 
    255          IF( ln_mixcpl          )   WRITE(numout,*) '              + forced-coupled mixed formulation' 
     240         SELECT CASE( nsbc ) 
     241         CASE( jp_gyre    )   ;   WRITE(numout,*) '   GYRE analytical formulation' 
     242         CASE( jp_ana     )   ;   WRITE(numout,*) '   analytical formulation' 
     243         CASE( jp_flx     )   ;   WRITE(numout,*) '   flux formulation' 
     244         CASE( jp_clio    )   ;   WRITE(numout,*) '   CLIO bulk formulation' 
     245         CASE( jp_core    )   ;   WRITE(numout,*) '   CORE bulk formulation' 
     246         CASE( jp_purecpl )   ;   WRITE(numout,*) '   pure coupled formulation' 
     247         CASE( jp_mfs     )   ;   WRITE(numout,*) '   MFS Bulk formulation' 
     248         CASE( jp_none    )   ;   WRITE(numout,*) '   OPA coupled to SAS via oasis' 
     249            IF( ln_mixcpl )       WRITE(numout,*) '       + forced-coupled mixed formulation' 
     250         END SELECT 
    256251         IF( nn_components/= jp_iam_nemo )  & 
    257             &                       WRITE(numout,*) '              + OASIS coupled SAS' 
     252            &                     WRITE(numout,*) '       + OASIS coupled SAS' 
    258253      ENDIF 
    259254      ! 
    260255      IF( lk_oasis )   CALL sbc_cpl_init (nn_ice)   ! OASIS initialisation. must be done before: (1) first time step 
    261256      !                                             !                                            (2) the use of nn_fsbc 
    262  
    263 !     nn_fsbc initialization if OPA-SAS coupling via OASIS 
    264 !     sas model time step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
    265       IF ( nn_components /= jp_iam_nemo ) THEN 
    266          IF ( nn_components == jp_iam_opa ) nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) 
    267          IF ( nn_components == jp_iam_sas ) nn_fsbc = cpl_freq('I_SFLX') / NINT(rdt) 
     257      !     nn_fsbc initialization if OPA-SAS coupling via OASIS 
     258      !     sas model time step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
     259      IF( nn_components /= jp_iam_nemo ) THEN 
     260         IF( nn_components == jp_iam_opa )   nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) 
     261         IF( nn_components == jp_iam_sas )   nn_fsbc = cpl_freq('I_SFLX') / NINT(rdt) 
    268262         ! 
    269263         IF(lwp)THEN 
     
    273267         ENDIF 
    274268      ENDIF 
    275  
     269      ! 
    276270      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
    277271          MOD( nstock             , nn_fsbc) /= 0 ) THEN  
     
    286280      IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   & 
    287281         &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
    288  
    289                                CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
    290       ! 
    291       IF( ln_ssr           )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
    292       ! 
    293                                CALL sbc_rnf_init               ! Runof initialisation 
    294       ! 
    295       IF( nn_ice == 3      )   CALL sbc_lim_init               ! LIM3 initialisation 
    296  
    297       IF( nn_ice == 4      )   CALL cice_sbc_init( nsbc )      ! CICE initialisation 
    298        
     282      ! 
     283                          CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
     284      ! 
     285      IF( ln_ssr      )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
     286      ! 
     287                          CALL sbc_rnf_init               ! Runof initialisation 
     288      ! 
     289      IF( nn_ice == 3 )   CALL sbc_lim_init               ! LIM3 initialisation 
     290      ! 
     291      IF( nn_ice == 4 )   CALL cice_sbc_init( nsbc )      ! CICE initialisation 
     292      ! 
    299293   END SUBROUTINE sbc_init 
    300294 
     
    327321         vtau_b(:,:) = vtau(:,:)                         ! (except at nit000 where before fields 
    328322         qns_b (:,:) = qns (:,:)                         !  are set at the end of the routine) 
    329          ! The 3D heat content due to qsr forcing is treated in traqsr 
    330          ! qsr_b (:,:) = qsr (:,:) 
    331          emp_b(:,:) = emp(:,:) 
    332          sfx_b(:,:) = sfx(:,:) 
     323         emp_b (:,:) = emp (:,:) 
     324         sfx_b (:,:) = sfx (:,:) 
    333325      ENDIF 
    334326      !                                            ! ---------------------------------------- ! 
     
    336328      !                                            ! ---------------------------------------- ! 
    337329      ! 
    338       IF( nn_components /= jp_iam_sas )   CALL sbc_ssm( kt )   ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     330      IF( nn_components /= jp_iam_sas )   CALL sbc_ssm ( kt )  ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
    339331      !                                                        ! averaged over nf_sbc time-step 
    340  
    341       IF (ln_wave) CALL sbc_wave( kt ) 
     332      IF( ln_wave                     )   CALL sbc_wave( kt )  ! surface waves 
     333       
     334       
    342335                                                   !==  sbc formulation  ==! 
    343336                                                             
     
    357350      CASE( jp_mfs   )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
    358351      CASE( jp_none  )  
    359          IF( nn_components == jp_iam_opa ) & 
    360                              CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
     352         IF( nn_components == jp_iam_opa )   & 
     353            &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
    361354      END SELECT 
    362355 
    363356      IF( ln_mixcpl )        CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    364357 
    365  
     358      ! 
    366359      !                                            !==  Misc. Options  ==! 
    367        
     360      ! 
    368361      SELECT CASE( nn_ice )                                       ! Update heat and freshwater fluxes over sea-ice areas 
    369362      CASE(  1 )   ;         CALL sbc_ice_if   ( kt )                ! Ice-cover climatology ("Ice-if" model) 
     
    375368      IF( ln_icebergs    )   CALL icb_stp( kt )                   ! compute icebergs 
    376369 
    377       IF( nn_isf   /= 0  )   CALL sbc_isf( kt )                    ! compute iceshelves 
     370      IF( ln_isf         )   CALL sbc_isf( kt )                   ! compute iceshelves 
    378371 
    379372      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes 
     
    383376      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    384377 
    385       IF( nn_closea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain  
    386       !                                                           ! (update freshwater fluxes) 
     378      ! treatment of closed sea in the model domain  
     379      ! (update freshwater fluxes) 
     380      ! Should not be ran if ln_diurnal_only 
     381      IF( .NOT.(ln_diurnal_only) .AND. (nn_closea == 1) )   CALL sbc_clo( kt )    
     382 
    387383!RBbug do not understand why see ticket 667 
    388384!clem: it looks like it is necessary for the north fold (in certain circumstances). Don't know why. 
     
    430426         CALL iom_rstput( kt, nitrst, numrow, 'sfx_b'  , sfx  ) 
    431427      ENDIF 
    432  
    433428      !                                                ! ---------------------------------------- ! 
    434429      !                                                !        Outputs and control print         ! 
     
    452447      ! 
    453448      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    454          CALL prt_ctl(tab2d_1=fr_i              , clinfo1=' fr_i     - : ', mask1=tmask, ovlap=1 ) 
    455          CALL prt_ctl(tab2d_1=(emp-rnf + fwfisf), clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 ) 
    456          CALL prt_ctl(tab2d_1=(sfx-rnf + fwfisf), clinfo1=' sfx-rnf  - : ', mask1=tmask, ovlap=1 ) 
     449         CALL prt_ctl(tab2d_1=fr_i              , clinfo1=' fr_i    - : ', mask1=tmask, ovlap=1 ) 
     450         CALL prt_ctl(tab2d_1=(emp-rnf + fwfisf), clinfo1=' emp-rnf - : ', mask1=tmask, ovlap=1 ) 
     451         CALL prt_ctl(tab2d_1=(sfx-rnf + fwfisf), clinfo1=' sfx-rnf - : ', mask1=tmask, ovlap=1 ) 
    457452         CALL prt_ctl(tab2d_1=qns              , clinfo1=' qns      - : ', mask1=tmask, ovlap=1 ) 
    458453         CALL prt_ctl(tab2d_1=qsr              , clinfo1=' qsr      - : ', mask1=tmask, ovlap=1 ) 
Note: See TracChangeset for help on using the changeset viewer.