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 7280 for branches/2016/dev_CNRS_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90 – NEMO

Ignore:
Timestamp:
2016-11-21T11:40:00+01:00 (7 years ago)
Author:
flavoni
Message:

merge CNRS2016 with aerobulk branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_CNRS_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r7278 r7280  
    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 
     
    3031   USE sbcssm         ! surface boundary condition: sea-surface mean variables 
    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 
     
    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   !!---------------------------------------------------------------------- 
    6968   !! NEMO/OPA 4.0 , NEMO-consortium (2016)  
     
    8584      !!              - nsbc: type of sbc 
    8685      !!---------------------------------------------------------------------- 
    87       INTEGER ::   icpt   ! local integer 
    88       !! 
    89       NAMELIST/namsbc/ nn_fsbc  , ln_usr   , 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  ,                                                    & 
     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 
     115      !                             !* overwrite namelist parameter using CPP key information 
    117116      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       ! 
    123       IF(lwp) THEN               ! Control print 
     117         IF( lk_lim2 )   nn_ice      = 2 
     118         IF( lk_lim3 )   nn_ice      = 3 
     119         IF( lk_cice )   nn_ice      = 4 
     120      ENDIF 
     121      ! 
     122      IF(lwp) THEN                  !* Control print 
    124123         WRITE(numout,*) '   Namelist namsbc (partly overwritten with CPP key setting)' 
    125          WRITE(numout,*) '      Frequency update of sbc (and ice)             nn_fsbc       = ', nn_fsbc 
     124         WRITE(numout,*) '      frequency update of sbc (and ice)             nn_fsbc       = ', nn_fsbc 
    126125         WRITE(numout,*) '      Type of air-sea fluxes : ' 
    127126         WRITE(numout,*) '         user defined formulation                   ln_usr        = ', ln_usr 
    128127         WRITE(numout,*) '         flux         formulation                   ln_flx        = ', ln_flx 
    129          WRITE(numout,*) '         CLIO bulk    formulation                   ln_blk_clio   = ', ln_blk_clio 
    130          WRITE(numout,*) '         CORE bulk    formulation                   ln_blk_core   = ', ln_blk_core 
    131          WRITE(numout,*) '         MFS  bulk    formulation                   ln_blk_mfs    = ', ln_blk_mfs 
     128         WRITE(numout,*) '         bulk         formulation                   ln_blk        = ', ln_blk 
    132129         WRITE(numout,*) '      Type of coupling (Ocean/Ice/Atmosphere) : ' 
    133130         WRITE(numout,*) '         ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
    134          WRITE(numout,*) '         forced-coupled mixed formulation           ln_mixcpl     = ', ln_mixcpl 
     131         WRITE(numout,*) '         mixed forced-coupled     formulation       ln_mixcpl     = ', ln_mixcpl 
     132!!gm  lk_oasis is controlled by key_oasis3  ===>>>  It shoud be removed from the namelist  
    135133         WRITE(numout,*) '         OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
    136134         WRITE(numout,*) '         components of your executable              nn_components = ', nn_components 
    137135         WRITE(numout,*) '         Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
    138136         WRITE(numout,*) '      Sea-ice : ' 
    139          WRITE(numout,*) '         ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice  
     137         WRITE(numout,*) '         ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice 
    140138         WRITE(numout,*) '         ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
    141139         WRITE(numout,*) '      Misc. options of sbc : ' 
    142140         WRITE(numout,*) '         Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
    143          WRITE(numout,*) '            daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc  
     141         WRITE(numout,*) '            daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc 
    144142         WRITE(numout,*) '         Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
    145143         WRITE(numout,*) '         FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
     
    149147         WRITE(numout,*) '         closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
    150148         WRITE(numout,*) '         nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
    151          WRITE(numout,*) '         surface wave                               ln_wave       = ', ln_wave   
     149         WRITE(numout,*) '         surface wave                               ln_wave       = ', ln_wave 
    152150      ENDIF 
    153151      ! 
     
    157155         IF( MOD( rdt  , 2.  ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
    158156      ENDIF 
    159       ! 
    160       IF(lwp) THEN 
    161          WRITE(numout,*) 
    162          SELECT CASE ( nn_limflx )        ! LIM3 Multi-category heat flux formulation 
    163          CASE ( -1 )   ;   WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
    164          CASE (  0 )   ;   WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) '  
    165          CASE (  1 )   ;   WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
    166          CASE (  2 )   ;   WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     157      !                       !**  check option consistency 
     158      ! 
     159      IF(lwp) WRITE(numout,*)       !* Single / Multi - executable (NEMO / OPA+SAS)  
     160      SELECT CASE( nn_components ) 
     161      CASE( jp_iam_nemo ) 
     162         IF(lwp) WRITE(numout,*) '   NEMO configured as a single executable (i.e. including both OPA and Surface module' 
     163      CASE( jp_iam_opa  ) 
     164         IF(lwp) WRITE(numout,*) '   Multi executable configuration. Here, OPA component' 
     165         IF( .NOT.lk_oasis )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     166         IF( ln_cpl        )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA'   ) 
     167         IF( ln_mixcpl     )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     168      CASE( jp_iam_sas  ) 
     169         IF(lwp) WRITE(numout,*) '   Multi executable configuration. Here, SAS component' 
     170         IF( .NOT.lk_oasis )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     171         IF( ln_mixcpl     )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     172      CASE DEFAULT 
     173         CALL ctl_stop( 'sbc_init : unsupported value for nn_components' ) 
     174      END SELECT 
     175      !                             !* coupled options 
     176      IF( ln_cpl ) THEN 
     177         IF( .NOT. lk_oasis )   CALL ctl_stop( 'sbc_init : coupled mode with an atmosphere model (ln_cpl=T)',   & 
     178            &                                  '           required to defined key_oasis3' ) 
     179      ENDIF 
     180      IF( ln_mixcpl ) THEN 
     181         IF( .NOT. lk_oasis )   CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) ',   & 
     182            &                                  '           required to defined key_oasis3' ) 
     183         IF( .NOT.ln_cpl    )   CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) requires ln_cpl = T' ) 
     184         IF( nn_components /= jp_iam_nemo )    & 
     185            &                   CALL ctl_stop( 'sbc_init : the mixed forced-coupled mode (ln_mixcpl=T) ',   & 
     186            &                                   '          not yet working with sas-opa coupling via oasis' ) 
     187      ENDIF 
     188      !                             !* sea-ice 
     189      SELECT CASE( nn_ice ) 
     190      CASE( 0 )                        !- no ice in the domain 
     191      CASE( 1 )                        !- Ice-cover climatology ("Ice-if" model)   
     192      CASE( 2 )                        !- LIM2 ice model 
     193         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : LIM2 sea-ice model requires ln_blk or ln_cpl = T' ) 
     194      CASE( 3 )                        !- LIM3 ice model 
     195         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : LIM3 sea-ice model requires ln_blk or ln_cpl = T' ) 
     196         IF( nn_ice_embd == 0            )   CALL ctl_stop( 'sbc_init : LIM3 sea-ice models require nn_ice_embd = 1 or 2' ) 
     197      CASE( 4 )                        !- CICE ice model 
     198         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : CICE sea-ice model requires ln_blk or ln_cpl = T' ) 
     199         IF( nn_ice_embd == 0            )   CALL ctl_stop( 'sbc_init : CICE sea-ice models require nn_ice_embd = 1 or 2' ) 
     200         IF( lk_agrif                    )   CALL ctl_stop( 'sbc_init : CICE sea-ice model not currently available with AGRIF' )  
     201      CASE DEFAULT                     !- not supported 
     202      END SELECT 
     203      ! 
     204      IF( nn_ice == 3 ) THEN           !- LIM3 case: multi-category flux option 
     205         IF(lwp) WRITE(numout,*) 
     206         SELECT CASE( nn_limflx )         ! LIM3 Multi-category heat flux formulation 
     207         CASE ( -1 ) 
     208            IF(lwp) WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
     209            IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     210         CASE ( 0  ) 
     211            IF(lwp) WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) ' 
     212         CASE ( 1  ) 
     213            IF(lwp) WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
     214            IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     215         CASE ( 2  ) 
     216            IF(lwp) WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     217            IF( .NOT.ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
     218         CASE DEFAULT 
     219            CALL ctl_stop( 'sbcmod: LIM3 option, nn_limflx, should be between -1 and 2' ) 
    167220         END SELECT 
    168       ENDIF 
    169       ! 
    170       IF( nn_components /= jp_iam_nemo .AND. .NOT. lk_oasis )   & 
    171          &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
    172       IF( nn_components == jp_iam_opa .AND. ln_cpl )   & 
    173          &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA' ) 
    174       IF( nn_components == jp_iam_opa .AND. ln_mixcpl )   & 
    175          &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
    176       IF( ln_cpl .AND. .NOT. lk_oasis )    & 
    177          &      CALL ctl_stop( 'sbc_init : OASIS-coupled atmosphere model, but key_oasis3 disabled' ) 
    178       IF( ln_mixcpl .AND. .NOT. lk_oasis )    & 
    179          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires the cpp key key_oasis3' ) 
    180       IF( ln_mixcpl .AND. .NOT. ln_cpl )    & 
    181          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires ln_cpl = T' ) 
    182       IF( ln_mixcpl .AND. nn_components /= jp_iam_nemo )    & 
    183          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) is not yet working with sas-opa coupling via oasis' ) 
    184  
    185       !                              ! allocate sbc arrays 
     221      ELSE                             ! other sea-ice model 
     222         IF( nn_limflx >= 0  )   CALL ctl_warn( 'sbc_init : multi-category flux option (nn_limflx) only available in LIM3' ) 
     223      ENDIF 
     224      ! 
     225      !                       !**  allocate and set required variables 
     226      ! 
     227      !                             !* allocate sbc arrays 
    186228      IF( sbc_oce_alloc() /= 0 )   CALL ctl_stop( 'sbc_init : unable to allocate sbc_oce arrays' ) 
    187  
    188       !                          ! Checks: 
    189       IF( .NOT. ln_isf ) THEN                      ! variable initialisation if no ice shelf  
     229      ! 
     230      IF( .NOT.ln_isf ) THEN        !* No ice-shelf in the domain : allocate and set to zero 
    190231         IF( sbc_isf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_isf arrays' ) 
    191          fwfisf  (:,:)   = 0.0_wp ; fwfisf_b  (:,:)   = 0.0_wp 
    192          risf_tsc(:,:,:) = 0.0_wp ; risf_tsc_b(:,:,:) = 0.0_wp 
     232         fwfisf  (:,:)   = 0._wp   ;   risf_tsc  (:,:,:) = 0._wp 
     233         fwfisf_b(:,:)   = 0._wp   ;   risf_tsc_b(:,:,:) = 0._wp 
    193234      END IF 
    194       IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! no ice in the domain, ice fraction is always zero 
    195  
    196       sfx(:,:) = 0._wp                             ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero)  
    197                                                    ! only if sea-ice is present 
    198   
    199       fmmflx(:,:) = 0._wp                          ! freezing-melting array initialisation 
    200        
    201       taum(:,:) = 0._wp                            ! Initialise taum for use in gls in case of reduced restart 
    202  
    203       !                                            ! restartability    
    204       IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. ln_cpl ) )   & 
    205          &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
    206       IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. ln_cpl ) )   & 
    207          &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or ln_cpl' ) 
    208       IF( nn_ice == 4 .AND. lk_agrif )   & 
    209          &   CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' ) 
    210       IF( ( nn_ice == 3 .OR. nn_ice == 4 ) .AND. nn_ice_embd == 0 )   & 
    211          &   CALL ctl_stop( 'LIM3 and CICE sea-ice models require nn_ice_embd = 1 or 2' ) 
    212       IF( ( nn_ice /= 3 ) .AND. ( nn_limflx >= 0 ) )   & 
    213          &   WRITE(numout,*) 'The nn_limflx>=0 option has no effect if sea ice model is not LIM3' 
    214       IF( ( nn_ice == 3 ) .AND. ( ln_cpl ) .AND. ( ( nn_limflx == -1 ) .OR. ( nn_limflx == 1 ) ) )   & 
    215          &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
    216       IF( ( nn_ice == 3 ) .AND. ( .NOT. ln_cpl ) .AND. ( nn_limflx == 2 ) )   & 
    217          &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
    218  
    219       IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
    220  
    221       IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) .AND. nn_components /= jp_iam_opa )   & 
    222          &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
    223        
    224       !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    225       ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl 
    226       ! 
     235      IF( nn_ice == 0 ) THEN        !* No sea-ice in the domain : ice fraction is always zero 
     236         IF( nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! except for OPA in SAS-OPA coupled case 
     237      ENDIF 
     238      ! 
     239      sfx   (:,:) = 0._wp           !* salt flux due to freezing/melting 
     240      fmmflx(:,:) = 0._wp           !* freezing minus melting flux 
     241 
     242      taum(:,:) = 0._wp             !* wind stress module (needed in GLS in case of reduced restart) 
     243 
     244      IF( ln_dm2dc ) THEN           !* daily mean to diurnal cycle 
     245         nday_qsr = -1   ! allow initialization at the 1st call 
     246         IF( .NOT.( ln_flx .OR. ln_blk ) .AND. nn_components /= jp_iam_opa )   & 
     247            &   CALL ctl_stop( 'qsr diurnal cycle from daily values requires a flux or bulk formulation' ) 
     248      ENDIF 
     249 
     250      !                             !* Choice of the Surface Boudary Condition 
     251      !                             (set nsbc) 
     252      ! 
     253      ll_purecpl  = ln_cpl .AND. .NOT.ln_mixcpl 
     254      ll_opa      = nn_components == jp_iam_opa 
     255      ll_not_nemo = nn_components /= jp_iam_nemo 
    227256      icpt = 0 
     257      ! 
    228258      IF( ln_usr          ) THEN   ;   nsbc = jp_usr     ; icpt = icpt + 1   ;   ENDIF       ! user defined         formulation 
    229259      IF( ln_flx          ) THEN   ;   nsbc = jp_flx     ; icpt = icpt + 1   ;   ENDIF       ! flux                 formulation 
    230       IF( ln_blk_clio     ) THEN   ;   nsbc = jp_clio    ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk            formulation 
    231       IF( ln_blk_core     ) THEN   ;   nsbc = jp_core    ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk            formulation 
    232       IF( ln_blk_mfs      ) THEN   ;   nsbc = jp_mfs     ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk            formulation 
     260      IF( ln_blk          ) THEN   ;   nsbc = jp_blk     ; icpt = icpt + 1   ;   ENDIF       ! bulk                 formulation 
    233261      IF( ll_purecpl      ) THEN   ;   nsbc = jp_purecpl ; icpt = icpt + 1   ;   ENDIF       ! Pure Coupled         formulation 
    234       IF( nn_components == jp_iam_opa )   & 
    235          &                  THEN   ;   nsbc = jp_none    ; icpt = icpt + 1   ;   ENDIF       ! opa coupling via SAS module 
    236       ! 
    237       IF( icpt /= 1 )    CALL ctl_stop( 'sbc_init: choose ONE and only ONE sbc option' ) 
    238       ! 
    239       IF(lwp) THEN 
     262      IF( ll_opa          ) THEN   ;   nsbc = jp_none    ; icpt = icpt + 1   ;   ENDIF       ! opa coupling via SAS module 
     263      ! 
     264      IF( icpt /= 1 )    CALL ctl_stop( 'sbc_init : choose ONE and only ONE sbc option' ) 
     265      ! 
     266      IF(lwp) THEN                     !- print the choice of surface flux formulation 
    240267         WRITE(numout,*) 
    241268         SELECT CASE( nsbc ) 
    242269         CASE( jp_usr     )   ;   WRITE(numout,*) '   user defined 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' 
     270         CASE( jp_flx     )   ;   WRITE(numout,*) '      ===>>   flux formulation' 
     271         CASE( jp_blk     )   ;   WRITE(numout,*) '      ===>>   bulk formulation' 
     272         CASE( jp_purecpl )   ;   WRITE(numout,*) '      ===>>   pure coupled formulation' 
     273!!gm abusive use of jp_none ??   ===>>> need to be check and changed by adding a jp_sas parameter 
     274         CASE( jp_none    )   ;   WRITE(numout,*) '      ===>>   OPA coupled to SAS via oasis' 
     275            IF( ln_mixcpl )       WRITE(numout,*) '                  + forced-coupled mixed formulation' 
    250276         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 
     277         IF( ll_not_nemo  )       WRITE(numout,*) '                  + OASIS coupled SAS' 
     278      ENDIF 
     279      ! 
     280      !                             !* OASIS initialization 
     281      ! 
     282      IF( lk_oasis )   CALL sbc_cpl_init( nn_ice )   ! Must be done before: (1) first time step 
     283      !                                              !                      (2) the use of nn_fsbc 
    257284      !     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 
     285      !     SAS time-step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
    259286      IF( nn_components /= jp_iam_nemo ) THEN 
    260287         IF( nn_components == jp_iam_opa )   nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) 
     
    268295      ENDIF 
    269296      ! 
     297      !                             !* check consistency between model timeline and nn_fsbc 
    270298      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,   & 
     299          MOD( nstock             , nn_fsbc) /= 0 ) THEN 
     300         WRITE(ctmp1,*) 'sbc_init : experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
    273301            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
    274302         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     
    276304      ! 
    277305      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 
     306         &  CALL ctl_warn( 'sbc_init : nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
     307      ! 
     308      IF( ln_dm2dc .AND. NINT(rday) / ( nn_fsbc * NINT(rdt) ) < 8  )   & 
     309         &   CALL ctl_warn( 'sbc_init : diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
     310      ! 
     311    
     312      !                       !**  associated modules : initialization 
     313      ! 
     314                          CALL sbc_ssm_init            ! Sea-surface mean fields initialization 
     315      ! 
     316      IF( ln_blk      )   CALL sbc_blk_init            ! bulk formulae initialization 
     317 
     318      IF( ln_ssr      )   CALL sbc_ssr_init            ! Sea-Surface Restoring initialization 
     319      ! 
     320                          CALL sbc_rnf_init            ! Runof initialization 
     321      ! 
     322      IF( nn_ice == 3 )   CALL sbc_lim_init            ! LIM3 initialization 
     323      ! 
     324      IF( nn_ice == 4 )   CALL cice_sbc_init( nsbc )   ! CICE initialization 
    292325      ! 
    293326   END SUBROUTINE sbc_init 
     
    297330      !!--------------------------------------------------------------------- 
    298331      !!                    ***  ROUTINE sbc  *** 
    299       !!               
     332      !! 
    300333      !! ** Purpose :   provide at each time-step the ocean surface boundary 
    301334      !!                condition (momentum, heat and freshwater fluxes) 
    302335      !! 
    303       !! ** Method  :   blah blah  to be written ?????????  
     336      !! ** Method  :   blah blah  to be written ????????? 
    304337      !!                CAUTION : never mask the surface stress field (tke sbc) 
    305338      !! 
    306       !! ** Action  : - set the ocean surface boundary condition at before and now  
    307       !!                time step, i.e.   
     339      !! ** Action  : - set the ocean surface boundary condition at before and now 
     340      !!                time step, i.e. 
    308341      !!                utau_b, vtau_b, qns_b, qsr_b, emp_n, sfx_b, qrp_b, erp_b 
    309342      !!                utau  , vtau  , qns  , qsr  , emp  , sfx  , qrp  , erp 
    310343      !!              - updte the ice fraction : fr_i 
    311344      !!---------------------------------------------------------------------- 
    312       INTEGER, INTENT(in) ::   kt       ! ocean time step 
     345      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     346      ! 
     347      LOGICAL ::   ll_sas, ll_opa   ! local logical 
    313348      !!--------------------------------------------------------------------- 
    314349      ! 
     
    332367      !                                            ! ---------------------------------------- ! 
    333368      ! 
    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                                                              
     369      ll_sas = nn_components == jp_iam_sas               ! component flags 
     370      ll_opa = nn_components == jp_iam_opa 
     371      ! 
     372      IF( .NOT.ll_sas )   CALL sbc_ssm ( kt )            ! mean ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     373      IF( ln_wave     )   CALL sbc_wave( kt )            ! surface waves 
     374 
     375      ! 
     376      !                                            !==  sbc formulation  ==! 
     377      !                                                    
    341378      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    342379      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx) 
    343       CASE( jp_usr   )   ;   CALL usr_def_sbc ( kt )                    ! user defined formulation  
    344       CASE( jp_flx   )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
    345       CASE( jp_clio  )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean 
    346       CASE( jp_core  )    
    347          IF( nn_components == jp_iam_sas ) & 
    348             &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA  
    349                              CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
    350                                                                         ! from oce: sea surface variables (sst_m, sss_m,  ssu_m,  ssv_m) 
    351       CASE( jp_purecpl )  ;  CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
    352                                                                         ! 
    353       CASE( jp_mfs   )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
    354       CASE( jp_none  )  
    355          IF( nn_components == jp_iam_opa )   & 
    356             &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
     380      CASE( jp_usr   )     ;   CALL usr_def_sbc( kt )                    ! user defined formulation  
     381      CASE( jp_flx     )   ;   CALL sbc_flx    ( kt )                    ! flux formulation 
     382      CASE( jp_blk     ) 
     383         IF( ll_sas    )       CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA 
     384                               CALL sbc_blk    ( kt )                    ! bulk formulation for the ocean 
     385                               ! 
     386      CASE( jp_purecpl )   ;   CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
     387      CASE( jp_none    ) 
     388         IF( ll_opa    )       CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
    357389      END SELECT 
    358390 
    359       IF( ln_mixcpl )        CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
     391      IF( ln_mixcpl )          CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    360392 
    361393      ! 
     
    367399      CASE(  3 )   ;         CALL sbc_ice_lim  ( kt, nsbc )          ! LIM-3 ice model 
    368400      CASE(  4 )   ;         CALL sbc_ice_cice ( kt, nsbc )          ! CICE ice model 
    369       END SELECT                                               
     401      END SELECT 
    370402 
    371403      IF( ln_icebergs    )   CALL icb_stp( kt )                   ! compute icebergs 
     
    374406 
    375407      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes 
    376   
     408 
    377409      IF( ln_ssr         )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term 
    378410 
    379411      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    380412 
    381       ! treatment of closed sea in the model domain  
    382       ! (update freshwater fluxes) 
     413      ! treatment of closed sea in the model domain   (update freshwater fluxes) 
    383414      ! Should not be ran if ln_diurnal_only 
    384415      IF( .NOT.ln_diurnal_only .AND. nn_closea == 1 )   CALL sbc_clo( kt, cn_cfg, nn_cfg )    
     
    391422         !                                             ! ---------------------------------------- ! 
    392423         IF( ln_rstart .AND.    &                               !* Restart: read in restart file 
    393             & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN  
     424            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN 
    394425            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
    395426            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point) 
     
    407438         ELSE                                                   !* no restart: set from nit000 values 
    408439            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000' 
    409             utau_b(:,:) = utau(:,:)  
     440            utau_b(:,:) = utau(:,:) 
    410441            vtau_b(:,:) = vtau(:,:) 
    411442            qns_b (:,:) = qns (:,:) 
    412             emp_b (:,:) = emp(:,:) 
    413             sfx_b (:,:) = sfx(:,:) 
     443            emp_b (:,:) = emp (:,:) 
     444            sfx_b (:,:) = sfx (:,:) 
    414445         ENDIF 
    415446      ENDIF 
     
    435466         CALL iom_put( "empmr"  , emp    - rnf )                ! upward water flux 
    436467         CALL iom_put( "empbmr" , emp_b  - rnf )                ! before upward water flux ( needed to recalculate the time evolution of ssh in offline ) 
    437          CALL iom_put( "saltflx", sfx  )                        ! downward salt flux   
    438                                                                 ! (includes virtual salt flux beneath ice  
    439                                                                 ! in linear free surface case) 
     468         CALL iom_put( "saltflx", sfx  )                        ! downward salt flux (includes virtual salt flux beneath ice in linear free surface case) 
    440469         CALL iom_put( "fmmflx", fmmflx  )                      ! Freezing-melting water flux 
    441          CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux  
     470         CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux 
    442471         CALL iom_put( "qns"   , qns        )                   ! solar heat flux 
    443472         CALL iom_put( "qsr"   ,       qsr  )                   ! solar heat flux 
    444          IF( nn_ice > 0 .OR. nn_components == jp_iam_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction  
    445          CALL iom_put( "taum"  , taum       )                   ! wind stress module  
     473         IF( nn_ice > 0 .OR. ll_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction 
     474         CALL iom_put( "taum"  , taum       )                   ! wind stress module 
    446475         CALL iom_put( "wspd"  , wndm       )                   ! wind speed  module over free ocean or leads in presence of sea-ice 
    447476      ENDIF 
    448477      ! 
    449       CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at  
    450       CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice) 
     478      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at each time step in sea-ice) 
     479      CALL iom_put( "vtau", vtau )   ! j-wind stress 
    451480      ! 
    452481      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
Note: See TracChangeset for help on using the changeset viewer.