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

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

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

    r6460 r7646  
    1313   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option 
    1414   !!            3.5  ! 2012-11  (A. Coward, G. Madec) Rethink of heat, mass and salt surface fluxes 
    15    !!            3.6  ! 2014-11  (P. Mathiot, C. Harris) add ice shelves melting                     
     15   !!            3.6  ! 2014-11  (P. Mathiot, C. Harris) add ice shelves melting 
     16   !!            4.0  ! 2016-06  (L. Brodeau) new general bulk formulation 
    1617   !!---------------------------------------------------------------------- 
    1718 
     
    1920   !!   sbc_init      : read namsbc namelist 
    2021   !!   sbc           : surface ocean momentum, heat and freshwater boundary conditions 
     22   !!   sbc_final     : Finalize CICE ice model (if used) 
    2123   !!---------------------------------------------------------------------- 
    2224   USE oce            ! ocean dynamics and tracers 
     
    2830   USE sbcdcy         ! surface boundary condition: diurnal cycle 
    2931   USE sbcssm         ! surface boundary condition: sea-surface mean variables 
    30    USE sbcana         ! surface boundary condition: analytical formulation 
    3132   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 
     33   USE sbcblk         ! surface boundary condition: bulk formulation 
    3534   USE sbcice_if      ! surface boundary condition: ice-if sea-ice model 
    3635   USE sbcice_lim     ! surface boundary condition: LIM 3.0 sea-ice model 
    3736   USE sbcice_lim_2   ! surface boundary condition: LIM 2.0 sea-ice model 
    3837   USE sbcice_cice    ! surface boundary condition: CICE    sea-ice model 
    39    USE sbccpl         ! surface boundary condition: coupled florulation 
     38   USE sbccpl         ! surface boundary condition: coupled formulation 
    4039   USE cpl_oasis3     ! OASIS routines for coupling 
    4140   USE sbcssr         ! surface boundary condition: sea surface restoring 
     
    4342   USE sbcisf         ! surface boundary condition: ice shelf 
    4443   USE sbcfwb         ! surface boundary condition: freshwater budget 
    45    USE closea         ! closed sea 
    4644   USE icbstp         ! Icebergs 
    4745   USE traqsr         ! active tracers: light penetration 
    4846   USE sbcwave        ! Wave module 
    49    USE bdy_par        ! Require lk_bdy 
     47   USE bdy_oce   , ONLY: ln_bdy 
     48   USE usrdef_sbc     ! user defined: surface boundary condition 
     49   USE usrdef_closea  ! user defined: closed sea 
    5050   ! 
    5151   USE prtctl         ! Print control                    (prt_ctl routine) 
     
    5555   USE timing         ! Timing 
    5656 
    57    USE diurnal_bulk, ONLY: & 
    58       & ln_diurnal_only  
     57   USE diurnal_bulk, ONLY:   ln_diurnal_only   ! diurnal SST diagnostic 
    5958 
    6059   IMPLICIT NONE 
     
    6362   PUBLIC   sbc        ! routine called by step.F90 
    6463   PUBLIC   sbc_init   ! routine called by opa.F90 
    65     
     64 
    6665   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations) 
    67        
     66 
    6867   !!---------------------------------------------------------------------- 
    69    !! NEMO/OPA 4.0 , NEMO-consortium (2011)  
     68   !! NEMO/OPA 4.0 , NEMO-consortium (2016)  
    7069   !! $Id$ 
    7170   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    8584      !!              - nsbc: type of sbc 
    8685      !!---------------------------------------------------------------------- 
    87       INTEGER ::   icpt   ! local integer 
    88       !! 
    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    
    96       INTEGER  ::   ios 
    97       INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
    98       LOGICAL  ::   ll_purecpl 
     86      INTEGER ::   ios, icpt                         ! local integer 
     87      LOGICAL ::   ll_purecpl, ll_opa, ll_not_nemo   ! local logical 
     88      !! 
     89      NAMELIST/namsbc/ nn_fsbc  ,                                                    & 
     90         &             ln_usr   , ln_flx   , ln_blk       ,                          & 
     91         &             ln_cpl   , ln_mixcpl, nn_components, nn_limflx,               & 
     92         &             nn_ice   , nn_ice_embd,                                       & 
     93         &             ln_traqsr, ln_dm2dc ,                                         & 
     94         &             ln_rnf   , nn_fwb   , ln_ssr   , ln_isf    , ln_apr_dyn ,     & 
     95         &             ln_wave  , ln_cdgw  , ln_sdw   , ln_tauoc  , ln_stcor   ,     & 
     96         &             nn_lsm 
    9997      !!---------------------------------------------------------------------- 
    10098      ! 
     
    105103      ENDIF 
    106104      ! 
    107       REWIND( numnam_ref )              ! Namelist namsbc in reference namelist : Surface boundary 
     105      !                       !**  read Surface Module namelist 
     106      REWIND( numnam_ref )          !* Namelist namsbc in reference namelist : Surface boundary 
    108107      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) 
    109108901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) 
    110109      ! 
    111       REWIND( numnam_cfg )              ! Namelist namsbc in configuration namelist : Parameters of the run 
     110      REWIND( numnam_cfg )          !* Namelist namsbc in configuration namelist : Parameters of the run 
    112111      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) 
    113112902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) 
    114113      IF(lwm) WRITE( numond, namsbc ) 
    115114      ! 
    116       !                          ! overwrite namelist parameter using CPP key information 
    117       IF( Agrif_Root() ) THEN                ! AGRIF zoom 
    118         IF( lk_lim2 )   nn_ice      = 2 
    119         IF( lk_lim3 )   nn_ice      = 3 
    120         IF( lk_cice )   nn_ice      = 4 
    121       ENDIF 
    122       IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
    123           ln_ana      = .TRUE.    
    124           nn_ice      =   0 
    125       ENDIF 
    126       ! 
    127       IF(lwp) THEN               ! Control print 
    128          WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
    129          WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc 
    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 
    145          WRITE(numout,*) '           Misc. options of sbc : ' 
    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) ' 
     115      !                             !* overwrite namelist parameter using CPP key information 
     116#if defined key_agrif 
     117      IF( Agrif_Root() ) THEN                ! AGRIF zoom (cf r1242: possibility to run without ice in fine grid) 
     118         IF( lk_lim2 )   nn_ice      = 2 
     119         IF( lk_lim3 )   nn_ice      = 3 
     120         IF( lk_cice )   nn_ice      = 4 
     121      ENDIF 
     122#else 
     123      IF( lk_lim2 )   nn_ice      = 2 
     124      IF( lk_lim3 )   nn_ice      = 3 
     125      IF( lk_cice )   nn_ice      = 4 
     126#endif 
     127      ! 
     128      IF(lwp) THEN                  !* Control print 
     129         WRITE(numout,*) '   Namelist namsbc (partly overwritten with CPP key setting)' 
     130         WRITE(numout,*) '      frequency update of sbc (and ice)             nn_fsbc       = ', nn_fsbc 
     131         WRITE(numout,*) '      Type of air-sea fluxes : ' 
     132         WRITE(numout,*) '         user defined formulation                   ln_usr        = ', ln_usr 
     133         WRITE(numout,*) '         flux         formulation                   ln_flx        = ', ln_flx 
     134         WRITE(numout,*) '         bulk         formulation                   ln_blk        = ', ln_blk 
     135         WRITE(numout,*) '      Type of coupling (Ocean/Ice/Atmosphere) : ' 
     136         WRITE(numout,*) '         ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
     137         WRITE(numout,*) '         mixed forced-coupled     formulation       ln_mixcpl     = ', ln_mixcpl 
     138!!gm  lk_oasis is controlled by key_oasis3  ===>>>  It shoud be removed from the namelist  
     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 
     145         WRITE(numout,*) '      Misc. options of sbc : ' 
     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         WRITE(numout,*) '               Stokes drift corr. to vert. velocity ln_sdw        = ', ln_sdw 
     157         WRITE(numout,*) '               wave modified ocean stress           ln_tauoc      = ', ln_tauoc 
     158         WRITE(numout,*) '               Stokes coriolis term                 ln_stcor      = ', ln_stcor 
     159         WRITE(numout,*) '               neutral drag coefficient (CORE, MFS) ln_cdgw       = ', ln_cdgw 
     160      ENDIF 
     161      ! 
     162      IF( .NOT.ln_usr ) THEN     ! the model calendar needs some specificities (except in user defined case) 
     163         IF( MOD( rday , rdt ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     164         IF( MOD( rday , 2.  ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    ) 
     165         IF( MOD( rdt  , 2.  ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
     166      ENDIF 
     167      !                       !**  check option consistency 
     168      ! 
     169      IF(lwp) WRITE(numout,*)       !* Single / Multi - executable (NEMO / OPA+SAS)  
     170      SELECT CASE( nn_components ) 
     171      CASE( jp_iam_nemo ) 
     172         IF(lwp) WRITE(numout,*) '   NEMO configured as a single executable (i.e. including both OPA and Surface module' 
     173      CASE( jp_iam_opa  ) 
     174         IF(lwp) WRITE(numout,*) '   Multi executable configuration. Here, OPA component' 
     175         IF( .NOT.lk_oasis )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     176         IF( ln_cpl        )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA'   ) 
     177         IF( ln_mixcpl     )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     178      CASE( jp_iam_sas  ) 
     179         IF(lwp) WRITE(numout,*) '   Multi executable configuration. Here, SAS component' 
     180         IF( .NOT.lk_oasis )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     181         IF( ln_mixcpl     )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     182      CASE DEFAULT 
     183         CALL ctl_stop( 'sbc_init : unsupported value for nn_components' ) 
     184      END SELECT 
     185      !                             !* coupled options 
     186      IF( ln_cpl ) THEN 
     187         IF( .NOT. lk_oasis )   CALL ctl_stop( 'sbc_init : coupled mode with an atmosphere model (ln_cpl=T)',   & 
     188            &                                  '           required to defined key_oasis3' ) 
     189      ENDIF 
     190      IF( ln_mixcpl ) THEN 
     191         IF( .NOT. lk_oasis )   CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) ',   & 
     192            &                                  '           required to defined key_oasis3' ) 
     193         IF( .NOT.ln_cpl    )   CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) requires ln_cpl = T' ) 
     194         IF( nn_components /= jp_iam_nemo )    & 
     195            &                   CALL ctl_stop( 'sbc_init : the mixed forced-coupled mode (ln_mixcpl=T) ',   & 
     196            &                                   '          not yet working with sas-opa coupling via oasis' ) 
     197      ENDIF 
     198      !                             !* sea-ice 
     199      SELECT CASE( nn_ice ) 
     200      CASE( 0 )                        !- no ice in the domain 
     201      CASE( 1 )                        !- Ice-cover climatology ("Ice-if" model)   
     202      CASE( 2 )                        !- LIM2 ice model 
     203         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : LIM2 sea-ice model requires ln_blk or ln_cpl = T' ) 
     204      CASE( 3 )                        !- LIM3 ice model 
     205         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : LIM3 sea-ice model requires ln_blk or ln_cpl = T' ) 
     206         IF( nn_ice_embd == 0            )   CALL ctl_stop( 'sbc_init : LIM3 sea-ice models require nn_ice_embd = 1 or 2' ) 
     207      CASE( 4 )                        !- CICE ice model 
     208         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : CICE sea-ice model requires ln_blk or ln_cpl = T' ) 
     209         IF( nn_ice_embd == 0            )   CALL ctl_stop( 'sbc_init : CICE sea-ice models require nn_ice_embd = 1 or 2' ) 
     210         IF( lk_agrif                    )   CALL ctl_stop( 'sbc_init : CICE sea-ice model not currently available with AGRIF' )  
     211      CASE DEFAULT                     !- not supported 
     212      END SELECT 
     213      ! 
     214      IF( nn_ice == 3 ) THEN           !- LIM3 case: multi-category flux option 
     215         IF(lwp) WRITE(numout,*) 
     216         SELECT CASE( nn_limflx )         ! LIM3 Multi-category heat flux formulation 
     217         CASE ( -1 ) 
     218            IF(lwp) WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
     219            IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     220         CASE ( 0  ) 
     221            IF(lwp) WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) ' 
     222         CASE ( 1  ) 
     223            IF(lwp) WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
     224            IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     225         CASE ( 2  ) 
     226            IF(lwp) WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     227            IF( .NOT.ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
     228         CASE DEFAULT 
     229            CALL ctl_stop( 'sbcmod: LIM3 option, nn_limflx, should be between -1 and 2' ) 
    165230         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' ) 
    176       IF( ln_mixcpl .AND. .NOT. lk_oasis )    & 
    177          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires the cpp key key_oasis3' ) 
    178       IF( ln_mixcpl .AND. .NOT. ln_cpl )    & 
    179          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires ln_cpl = T' ) 
    180       IF( ln_mixcpl .AND. nn_components /= jp_iam_nemo )    & 
    181          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) is not yet working with sas-opa coupling via oasis' ) 
    182  
    183       !                              ! allocate sbc arrays 
     231      ELSE                             ! other sea-ice model 
     232         IF( nn_limflx >= 0  )   CALL ctl_warn( 'sbc_init : multi-category flux option (nn_limflx) only available in LIM3' ) 
     233      ENDIF 
     234      ! 
     235      !                       !**  allocate and set required variables 
     236      ! 
     237      !                             !* allocate sbc arrays 
    184238      IF( sbc_oce_alloc() /= 0 )   CALL ctl_stop( 'sbc_init : unable to allocate sbc_oce arrays' ) 
    185  
    186       !                          ! Checks: 
    187       IF( .NOT. ln_isf ) THEN                      ! variable initialisation if no ice shelf  
     239      ! 
     240      IF( .NOT.ln_isf ) THEN        !* No ice-shelf in the domain : allocate and set to zero 
    188241         IF( sbc_isf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_isf arrays' ) 
    189          fwfisf  (:,:)   = 0.0_wp ; fwfisf_b  (:,:)   = 0.0_wp 
    190          risf_tsc(:,:,:) = 0.0_wp ; risf_tsc_b(:,:,:) = 0.0_wp 
     242         fwfisf  (:,:)   = 0._wp   ;   risf_tsc  (:,:,:) = 0._wp 
     243         fwfisf_b(:,:)   = 0._wp   ;   risf_tsc_b(:,:,:) = 0._wp 
    191244      END IF 
    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)  
    195                                                    ! only if sea-ice is present 
    196   
    197       fmmflx(:,:) = 0._wp                          ! freezing-melting array initialisation 
    198        
    199       taum(:,:) = 0._wp                            ! Initialise taum for use in gls in case of reduced restart 
    200  
    201       !                                            ! restartability    
    202       IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. ln_cpl ) )   & 
    203          &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
    204       IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. ln_cpl ) )   & 
    205          &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or ln_cpl' ) 
    206       IF( nn_ice == 4 .AND. lk_agrif )   & 
    207          &   CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' ) 
    208       IF( ( nn_ice == 3 .OR. nn_ice == 4 ) .AND. nn_ice_embd == 0 )   & 
    209          &   CALL ctl_stop( 'LIM3 and CICE sea-ice models require nn_ice_embd = 1 or 2' ) 
    210       IF( ( nn_ice /= 3 ) .AND. ( nn_limflx >= 0 ) )   & 
    211          &   WRITE(numout,*) 'The nn_limflx>=0 option has no effect if sea ice model is not LIM3' 
    212       IF( ( nn_ice == 3 ) .AND. ( ln_cpl ) .AND. ( ( nn_limflx == -1 ) .OR. ( nn_limflx == 1 ) ) )   & 
    213          &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
    214       IF( ( nn_ice == 3 ) .AND. ( .NOT. ln_cpl ) .AND. ( nn_limflx == 2 ) )   & 
    215          &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
    216  
    217       IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
    218  
    219       IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) .AND. nn_components /= jp_iam_opa )   & 
    220          &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
    221        
     245      IF( nn_ice == 0 ) THEN        !* No sea-ice in the domain : ice fraction is always zero 
     246         IF( nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! except for OPA in SAS-OPA coupled case 
     247      ENDIF 
     248      ! 
     249      sfx   (:,:) = 0._wp           !* salt flux due to freezing/melting 
     250      fmmflx(:,:) = 0._wp           !* freezing minus melting flux 
     251 
     252      taum(:,:) = 0._wp             !* wind stress module (needed in GLS in case of reduced restart) 
     253 
    222254      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    223       ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl 
    224       ! 
     255      IF( ln_dm2dc ) THEN           !* daily mean to diurnal cycle 
     256         nday_qsr = -1   ! allow initialization at the 1st call 
     257         IF( .NOT.( ln_flx .OR. ln_blk ) .AND. nn_components /= jp_iam_opa )   & 
     258            &   CALL ctl_stop( 'qsr diurnal cycle from daily values requires a flux or bulk formulation' ) 
     259      ENDIF 
     260      !                             !* Choice of the Surface Boudary Condition 
     261      !                             (set nsbc) 
     262      ! 
     263      ll_purecpl  = ln_cpl .AND. .NOT.ln_mixcpl 
     264      ll_opa      = nn_components == jp_iam_opa 
     265      ll_not_nemo = nn_components /= jp_iam_nemo 
    225266      icpt = 0 
    226       IF( ln_ana          ) THEN   ;   nsbc = jp_ana     ; icpt = icpt + 1   ;   ENDIF       ! analytical           formulation 
     267      ! 
     268      IF( ln_usr          ) THEN   ;   nsbc = jp_usr     ; icpt = icpt + 1   ;   ENDIF       ! user defined         formulation 
    227269      IF( ln_flx          ) THEN   ;   nsbc = jp_flx     ; icpt = icpt + 1   ;   ENDIF       ! flux                 formulation 
    228       IF( ln_blk_clio     ) THEN   ;   nsbc = jp_clio    ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk            formulation 
    229       IF( ln_blk_core     ) THEN   ;   nsbc = jp_core    ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk            formulation 
    230       IF( ln_blk_mfs      ) THEN   ;   nsbc = jp_mfs     ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk            formulation 
     270      IF( ln_blk          ) THEN   ;   nsbc = jp_blk     ; icpt = icpt + 1   ;   ENDIF       ! bulk                 formulation 
    231271      IF( ll_purecpl      ) THEN   ;   nsbc = jp_purecpl ; icpt = icpt + 1   ;   ENDIF       ! Pure Coupled         formulation 
    232       IF( cp_cfg == 'gyre') THEN   ;   nsbc = jp_gyre                        ;   ENDIF       ! GYRE analytical      formulation 
    233       IF( nn_components == jp_iam_opa )   & 
    234          &                  THEN   ;   nsbc = jp_none    ; icpt = icpt + 1   ;   ENDIF       ! opa coupling via SAS module 
    235       ! 
    236       IF( icpt /= 1 )    CALL ctl_stop( 'sbc_init: choose ONE and only ONE sbc option' ) 
    237       ! 
    238       IF(lwp) THEN 
     272      IF( ll_opa          ) THEN   ;   nsbc = jp_none    ; icpt = icpt + 1   ;   ENDIF       ! opa coupling via SAS module 
     273      ! 
     274      IF( icpt /= 1 )    CALL ctl_stop( 'sbc_init : choose ONE and only ONE sbc option' ) 
     275      ! 
     276      IF(lwp) THEN                     !- print the choice of surface flux formulation 
    239277         WRITE(numout,*) 
    240278         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' 
     279         CASE( jp_usr     )   ;   WRITE(numout,*) '   user defined formulation' 
     280         CASE( jp_flx     )   ;   WRITE(numout,*) '      ===>>   flux formulation' 
     281         CASE( jp_blk     )   ;   WRITE(numout,*) '      ===>>   bulk formulation' 
     282         CASE( jp_purecpl )   ;   WRITE(numout,*) '      ===>>   pure coupled formulation' 
     283!!gm abusive use of jp_none ??   ===>>> need to be check and changed by adding a jp_sas parameter 
     284         CASE( jp_none    )   ;   WRITE(numout,*) '      ===>>   OPA coupled to SAS via oasis' 
     285            IF( ln_mixcpl )       WRITE(numout,*) '                  + forced-coupled mixed formulation' 
    250286         END SELECT 
    251          IF( nn_components/= jp_iam_nemo )  & 
    252             &                     WRITE(numout,*) '       + OASIS coupled SAS' 
    253       ENDIF 
    254       ! 
    255       IF( lk_oasis )   CALL sbc_cpl_init (nn_ice)   ! OASIS initialisation. must be done before: (1) first time step 
    256       !                                             !                                            (2) the use of nn_fsbc 
     287         IF( ll_not_nemo  )       WRITE(numout,*) '                  + OASIS coupled SAS' 
     288      ENDIF 
     289      ! 
     290      !                             !* OASIS initialization 
     291      ! 
     292      IF( lk_oasis )   CALL sbc_cpl_init( nn_ice )   ! Must be done before: (1) first time step 
     293      !                                              !                      (2) the use of nn_fsbc 
    257294      !     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 
     295      !     SAS time-step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
    259296      IF( nn_components /= jp_iam_nemo ) THEN 
    260297         IF( nn_components == jp_iam_opa )   nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) 
     
    268305      ENDIF 
    269306      ! 
     307      !                             !* check consistency between model timeline and nn_fsbc 
    270308      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
    271           MOD( nstock             , nn_fsbc) /= 0 ) THEN  
    272          WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
     309          MOD( nstock             , nn_fsbc) /= 0 ) THEN 
     310         WRITE(ctmp1,*) 'sbc_init : experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
    273311            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
    274312         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     
    276314      ! 
    277315      IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   & 
    278          &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
    279       ! 
    280       IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   & 
    281          &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
    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 
     316         &  CALL ctl_warn( 'sbc_init : nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
     317      ! 
     318      IF( ln_dm2dc .AND. NINT(rday) / ( nn_fsbc * NINT(rdt) ) < 8  )   & 
     319         &   CALL ctl_warn( 'sbc_init : diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
     320      ! 
     321    
     322      !                       !**  associated modules : initialization 
     323      ! 
     324                          CALL sbc_ssm_init            ! Sea-surface mean fields initialization 
     325      ! 
     326      IF( ln_blk      )   CALL sbc_blk_init            ! bulk formulae initialization 
     327 
     328      IF( ln_ssr      )   CALL sbc_ssr_init            ! Sea-Surface Restoring initialization 
     329      ! 
     330                          CALL sbc_rnf_init            ! Runof initialization 
     331      ! 
     332      IF( nn_ice == 3 )   CALL sbc_lim_init            ! LIM3 initialization 
     333      ! 
     334      IF( nn_ice == 4 )   CALL cice_sbc_init( nsbc )   ! CICE initialization 
     335      ! 
     336      IF( ln_wave     )   CALL sbc_wave_init              ! surface wave initialisation 
    292337      ! 
    293338   END SUBROUTINE sbc_init 
     
    297342      !!--------------------------------------------------------------------- 
    298343      !!                    ***  ROUTINE sbc  *** 
    299       !!               
     344      !! 
    300345      !! ** Purpose :   provide at each time-step the ocean surface boundary 
    301346      !!                condition (momentum, heat and freshwater fluxes) 
    302347      !! 
    303       !! ** Method  :   blah blah  to be written ?????????  
     348      !! ** Method  :   blah blah  to be written ????????? 
    304349      !!                CAUTION : never mask the surface stress field (tke sbc) 
    305350      !! 
    306       !! ** Action  : - set the ocean surface boundary condition at before and now  
    307       !!                time step, i.e.   
     351      !! ** Action  : - set the ocean surface boundary condition at before and now 
     352      !!                time step, i.e. 
    308353      !!                utau_b, vtau_b, qns_b, qsr_b, emp_n, sfx_b, qrp_b, erp_b 
    309354      !!                utau  , vtau  , qns  , qsr  , emp  , sfx  , qrp  , erp 
    310355      !!              - updte the ice fraction : fr_i 
    311356      !!---------------------------------------------------------------------- 
    312       INTEGER, INTENT(in) ::   kt       ! ocean time step 
     357      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     358      ! 
     359      LOGICAL ::   ll_sas, ll_opa   ! local logical 
    313360      !!--------------------------------------------------------------------- 
    314361      ! 
     
    332379      !                                            ! ---------------------------------------- ! 
    333380      ! 
    334       IF( nn_components /= jp_iam_sas )   CALL sbc_ssm ( kt )  ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
    335       !                                                        ! averaged over nf_sbc time-step 
    336       IF( ln_wave                     )   CALL sbc_wave( kt )  ! surface waves 
    337        
    338        
    339                                                    !==  sbc formulation  ==! 
    340                                                              
     381      ll_sas = nn_components == jp_iam_sas               ! component flags 
     382      ll_opa = nn_components == jp_iam_opa 
     383      ! 
     384      IF( .NOT.ll_sas )   CALL sbc_ssm ( kt )            ! mean ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     385      IF( ln_wave     )   CALL sbc_wave( kt )            ! surface waves 
     386 
     387      ! 
     388      !                                            !==  sbc formulation  ==! 
     389      !                                                    
    341390      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    342391      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx) 
    343       CASE( jp_gyre  )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
    344       CASE( jp_ana   )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc 
    345       CASE( jp_flx   )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
    346       CASE( jp_clio  )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean 
    347       CASE( jp_core  )    
    348          IF( nn_components == jp_iam_sas ) & 
    349             &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA  
    350                              CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
    351                                                                         ! from oce: sea surface variables (sst_m, sss_m,  ssu_m,  ssv_m) 
    352       CASE( jp_purecpl )  ;  CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
    353                                                                         ! 
    354       CASE( jp_mfs   )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
    355       CASE( jp_none  )  
    356          IF( nn_components == jp_iam_opa )   & 
    357             &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
     392      CASE( jp_usr   )     ;   CALL usrdef_sbc_oce( kt )                    ! user defined formulation  
     393      CASE( jp_flx     )   ;   CALL sbc_flx       ( kt )                    ! flux formulation 
     394      CASE( jp_blk     ) 
     395         IF( ll_sas    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA 
     396                               CALL sbc_blk       ( kt )                    ! bulk formulation for the ocean 
     397                               ! 
     398      CASE( jp_purecpl )   ;   CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
     399      CASE( jp_none    ) 
     400         IF( ll_opa    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
    358401      END SELECT 
    359  
    360       IF( ln_mixcpl )        CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
     402      IF ( ln_wave .AND. ln_tauoc) THEN                                 ! Wave stress subctracted 
     403            utau(:,:) = utau(:,:)*tauoc_wave(:,:) 
     404            vtau(:,:) = vtau(:,:)*tauoc_wave(:,:) 
     405            taum(:,:) = taum(:,:)*tauoc_wave(:,:) 
     406      ! 
     407            SELECT CASE( nsbc ) 
     408            CASE(  0,1,2,3,5,-1 )  ; 
     409                IF(lwp .AND. kt == nit000 ) WRITE(numout,*) 'WARNING: You are subtracting the wave stress to the ocean. & 
     410                        & If not requested select ln_tauoc=.false' 
     411            END SELECT 
     412      ! 
     413      END IF 
     414      IF( ln_mixcpl )          CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    361415 
    362416      ! 
     
    368422      CASE(  3 )   ;         CALL sbc_ice_lim  ( kt, nsbc )          ! LIM-3 ice model 
    369423      CASE(  4 )   ;         CALL sbc_ice_cice ( kt, nsbc )          ! CICE ice model 
    370       END SELECT                                               
     424      END SELECT 
    371425 
    372426      IF( ln_icebergs    )   CALL icb_stp( kt )                   ! compute icebergs 
     
    375429 
    376430      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes 
    377   
     431 
    378432      IF( ln_ssr         )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term 
    379433 
    380434      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    381435 
    382       ! treatment of closed sea in the model domain  
    383       ! (update freshwater fluxes) 
     436      ! treatment of closed sea in the model domain   (update freshwater fluxes) 
    384437      ! Should not be ran if ln_diurnal_only 
    385       IF( .NOT.(ln_diurnal_only) .AND. (nn_closea == 1) )   CALL sbc_clo( kt )    
     438      IF( .NOT.ln_diurnal_only .AND. nn_closea == 1 )   CALL sbc_clo( kt, cn_cfg, nn_cfg )    
    386439 
    387440!RBbug do not understand why see ticket 667 
     
    392445         !                                             ! ---------------------------------------- ! 
    393446         IF( ln_rstart .AND.    &                               !* Restart: read in restart file 
    394             & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN  
     447            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN 
    395448            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
    396449            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point) 
     
    408461         ELSE                                                   !* no restart: set from nit000 values 
    409462            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000' 
    410             utau_b(:,:) = utau(:,:)  
     463            utau_b(:,:) = utau(:,:) 
    411464            vtau_b(:,:) = vtau(:,:) 
    412465            qns_b (:,:) = qns (:,:) 
    413             emp_b (:,:) = emp(:,:) 
    414             sfx_b (:,:) = sfx(:,:) 
     466            emp_b (:,:) = emp (:,:) 
     467            sfx_b (:,:) = sfx (:,:) 
    415468         ENDIF 
    416469      ENDIF 
     
    436489         CALL iom_put( "empmr"  , emp    - rnf )                ! upward water flux 
    437490         CALL iom_put( "empbmr" , emp_b  - rnf )                ! before upward water flux ( needed to recalculate the time evolution of ssh in offline ) 
    438          CALL iom_put( "saltflx", sfx  )                        ! downward salt flux   
    439                                                                 ! (includes virtual salt flux beneath ice  
    440                                                                 ! in linear free surface case) 
     491         CALL iom_put( "saltflx", sfx  )                        ! downward salt flux (includes virtual salt flux beneath ice in linear free surface case) 
    441492         CALL iom_put( "fmmflx", fmmflx  )                      ! Freezing-melting water flux 
    442          CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux  
     493         CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux 
    443494         CALL iom_put( "qns"   , qns        )                   ! solar heat flux 
    444495         CALL iom_put( "qsr"   ,       qsr  )                   ! solar heat flux 
    445          IF( nn_ice > 0 .OR. nn_components == jp_iam_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction  
    446          CALL iom_put( "taum"  , taum       )                   ! wind stress module  
     496         IF( nn_ice > 0 .OR. ll_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction 
     497         CALL iom_put( "taum"  , taum       )                   ! wind stress module 
    447498         CALL iom_put( "wspd"  , wndm       )                   ! wind speed  module over free ocean or leads in presence of sea-ice 
    448499      ENDIF 
    449500      ! 
    450       CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at  
    451       CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice) 
     501      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at each time step in sea-ice) 
     502      CALL iom_put( "vtau", vtau )   ! j-wind stress 
    452503      ! 
    453504      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
Note: See TracChangeset for help on using the changeset viewer.