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

Ignore:
Timestamp:
2016-11-01T15:26:15+01:00 (7 years ago)
Author:
gm
Message:

#1751 - branch SIMPLIF_6_aerobulk: update option control in sbcmod + uniformization of print in ocean_output (many module involved)

File:
1 edited

Legend:

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

    r6723 r7163  
    3636   USE sbcice_lim_2   ! surface boundary condition: LIM 2.0 sea-ice model 
    3737   USE sbcice_cice    ! surface boundary condition: CICE    sea-ice model 
    38    USE sbccpl         ! surface boundary condition: coupled florulation 
     38   USE sbccpl         ! surface boundary condition: coupled formulation 
    3939   USE cpl_oasis3     ! OASIS routines for coupling 
    4040   USE sbcssr         ! surface boundary condition: sea surface restoring 
     
    8383      !!              - nsbc: type of sbc 
    8484      !!---------------------------------------------------------------------- 
    85       INTEGER ::   icpt   ! local integer 
    86       !! 
    87       NAMELIST/namsbc/ nn_fsbc  , ln_ana   , ln_flx, ln_blk, ln_cpl   , ln_mixcpl,        & 
    88          &             nn_components      , nn_limflx  ,                                  & 
    89          &             ln_traqsr, ln_dm2dc ,                                              & 
    90          &             nn_ice   , nn_ice_embd,                                            & 
    91          &             ln_rnf   , ln_ssr   , ln_isf   , nn_fwb    , ln_apr_dyn,           & 
    92          &             ln_wave  ,                                                         & 
     85      INTEGER ::   ios, icpt                         ! local integer 
     86      LOGICAL ::   ll_purecpl, ll_opa, ll_not_nemo   ! local logical 
     87      !! 
     88      NAMELIST/namsbc/ nn_fsbc  ,                                                    & 
     89         &             ln_ana   , ln_flx   , ln_blk       ,                          & 
     90         &             ln_cpl   , ln_mixcpl, nn_components, nn_limflx,               & 
     91         &             nn_ice   , nn_ice_embd,                                       & 
     92         &             ln_traqsr, ln_dm2dc ,                                         & 
     93         &             ln_rnf   , nn_fwb   , ln_ssr       , ln_isf   , ln_apr_dyn,   & 
     94         &             ln_wave  ,                                                    & 
    9395         &             nn_lsm 
    94       INTEGER  ::   ios 
    95       INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
    96       LOGICAL  ::   ll_purecpl 
    9796      !!---------------------------------------------------------------------- 
    9897      ! 
     
    103102      ENDIF 
    104103      ! 
    105       REWIND( numnam_ref )              ! Namelist namsbc in reference namelist : Surface boundary 
     104      !                       !**  read Surface Module namelist 
     105      REWIND( numnam_ref )          !* Namelist namsbc in reference namelist : Surface boundary 
    106106      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) 
    107107901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) 
    108108      ! 
    109       REWIND( numnam_cfg )              ! Namelist namsbc in configuration namelist : Parameters of the run 
     109      REWIND( numnam_cfg )          !* Namelist namsbc in configuration namelist : Parameters of the run 
    110110      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) 
    111111902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) 
    112112      IF(lwm) WRITE( numond, namsbc ) 
    113113      ! 
    114       !                          ! overwrite namelist parameter using CPP key information 
     114      !                             !* overwrite namelist parameter using CPP key information 
    115115      IF( Agrif_Root() ) THEN                ! AGRIF zoom 
    116116         IF( lk_lim2 )   nn_ice      = 2 
     
    123123      ENDIF 
    124124      ! 
    125       IF(lwp) THEN               ! Control print 
    126          WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
    127          WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc 
    128          WRITE(numout,*) '           Type of air-sea fluxes : ' 
    129          WRITE(numout,*) '              analytical formulation                     ln_ana        = ', ln_ana 
    130          WRITE(numout,*) '              flux       formulation                     ln_flx        = ', ln_flx 
    131          WRITE(numout,*) '              bulk       formulation                     ln_blk        = ', ln_blk 
    132          WRITE(numout,*) '           Type of coupling (Ocean/Ice/Atmosphere) : ' 
    133          WRITE(numout,*) '              ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
    134          WRITE(numout,*) '              forced-coupled mixed formulation           ln_mixcpl     = ', ln_mixcpl 
    135          WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
    136          WRITE(numout,*) '              components of your executable              nn_components = ', nn_components 
    137          WRITE(numout,*) '              Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
    138          WRITE(numout,*) '           Sea-ice : ' 
    139          WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice 
    140          WRITE(numout,*) '              ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
    141          WRITE(numout,*) '           Misc. options of sbc : ' 
    142          WRITE(numout,*) '              Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
    143          WRITE(numout,*) '                 daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc 
    144          WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
    145          WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
    146          WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn    = ', ln_apr_dyn 
    147          WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf        = ', ln_rnf 
    148          WRITE(numout,*) '              iceshelf formulation                       ln_isf        = ', ln_isf 
    149          WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
    150          WRITE(numout,*) '              nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
    151          WRITE(numout,*) '              surface wave                               ln_wave       = ', ln_wave 
    152       ENDIF 
    153       ! 
    154       IF(lwp) THEN 
    155          WRITE(numout,*) 
    156          SELECT CASE ( nn_limflx )        ! LIM3 Multi-category heat flux formulation 
    157          CASE ( -1 )   ;   WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
    158          CASE ( 0  )   ;   WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) ' 
    159          CASE ( 1  )   ;   WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
    160          CASE ( 2  )   ;   WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     125      IF(lwp) THEN                  !* Control print 
     126         WRITE(numout,*) '   Namelist namsbc (partly overwritten with CPP key setting)' 
     127         WRITE(numout,*) '      frequency update of sbc (and ice)             nn_fsbc       = ', nn_fsbc 
     128         WRITE(numout,*) '      Type of air-sea fluxes : ' 
     129         WRITE(numout,*) '         analytical formulation                     ln_ana        = ', ln_ana 
     130         WRITE(numout,*) '         flux       formulation                     ln_flx        = ', ln_flx 
     131         WRITE(numout,*) '         bulk       formulation                     ln_blk        = ', ln_blk 
     132         WRITE(numout,*) '      Type of coupling (Ocean/Ice/Atmosphere) : ' 
     133         WRITE(numout,*) '         ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
     134         WRITE(numout,*) '         mixed forced-coupled     formulation       ln_mixcpl     = ', ln_mixcpl 
     135!!gm  lk_oasis is controlled by key_oasis3  ===>>>  It shoud be removed from the namelist  
     136         WRITE(numout,*) '         OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
     137         WRITE(numout,*) '         components of your executable              nn_components = ', nn_components 
     138         WRITE(numout,*) '         Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
     139         WRITE(numout,*) '      Sea-ice : ' 
     140         WRITE(numout,*) '         ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice 
     141         WRITE(numout,*) '         ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
     142         WRITE(numout,*) '      Misc. options of sbc : ' 
     143         WRITE(numout,*) '         Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
     144         WRITE(numout,*) '            daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc 
     145         WRITE(numout,*) '         Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
     146         WRITE(numout,*) '         FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
     147         WRITE(numout,*) '         Patm gradient added in ocean & ice Eqs.    ln_apr_dyn    = ', ln_apr_dyn 
     148         WRITE(numout,*) '         runoff / runoff mouths                     ln_rnf        = ', ln_rnf 
     149         WRITE(numout,*) '         iceshelf formulation                       ln_isf        = ', ln_isf 
     150         WRITE(numout,*) '         closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
     151         WRITE(numout,*) '         nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
     152         WRITE(numout,*) '         surface wave                               ln_wave       = ', ln_wave 
     153      ENDIF 
     154      ! 
     155      !                       !**  check option consistency 
     156      ! 
     157      IF(lwp) WRITE(numout,*)       !* Single / Multi - executable (NEMO / OPA+SAS)  
     158      SELECT CASE( nn_components ) 
     159      CASE( jp_iam_nemo ) 
     160         IF(lwp) WRITE(numout,*) '   NEMO configured as a single executable (i.e. including both OPA and Surface module'  
     161      CASE( jp_iam_opa  ) 
     162         IF(lwp) WRITE(numout,*) '   Multi executable configuration. Here, OPA component' 
     163         IF( .NOT.lk_oasis )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     164         IF( ln_cpl        )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA'   ) 
     165         IF( ln_mixcpl     )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     166      CASE( jp_iam_sas  ) 
     167         IF(lwp) WRITE(numout,*) '   Multi executable configuration. Here, SAS component' 
     168         IF( .NOT.lk_oasis )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     169         IF( ln_mixcpl     )   CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
     170      CASE DEFAULT 
     171         CALL ctl_stop( 'sbc_init : unsupported value for nn_components' ) 
     172      END SELECT 
     173      !                             !* coupled options 
     174      IF( ln_cpl ) THEN 
     175         IF( .NOT. lk_oasis )   CALL ctl_stop( 'sbc_init : coupled mode with an atmosphere model (ln_cpl=T)',   & 
     176            &                                  '           required to defined key_oasis3' ) 
     177      ENDIF 
     178      IF( ln_mixcpl ) THEN 
     179         IF( .NOT. lk_oasis )   CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) ',   & 
     180            &                                  '           required to defined key_oasis3' ) 
     181         IF( .NOT.ln_cpl    )   CALL ctl_stop( 'sbc_init : mixed forced-coupled mode (ln_mixcpl=T) requires ln_cpl = T' ) 
     182         IF( nn_components /= jp_iam_nemo )    & 
     183            &                   CALL ctl_stop( 'sbc_init : the mixed forced-coupled mode (ln_mixcpl=T) ',   & 
     184            &                                   '          not yet working with sas-opa coupling via oasis' ) 
     185      ENDIF 
     186      !                             !* sea-ice 
     187      SELECT CASE( nn_ice ) 
     188      CASE( 0 )                        !- no ice in the domain 
     189      CASE( 1 )                        !- Ice-cover climatology ("Ice-if" model)   
     190      CASE( 2 )                        !- LIM2 ice model 
     191         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : LIM2 sea-ice model requires ln_blk or ln_cpl = T' ) 
     192      CASE( 3 )                        !- LIM3 ice model 
     193         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : LIM3 sea-ice model requires ln_blk or ln_cpl = T' ) 
     194         IF( nn_ice_embd == 0            )   CALL ctl_stop( 'sbc_init : LIM3 sea-ice models require nn_ice_embd = 1 or 2' ) 
     195      CASE( 4 )                        !- CICE ice model 
     196         IF( .NOT.( ln_blk .OR. ln_cpl ) )   CALL ctl_stop( 'sbc_init : CICE sea-ice model requires ln_blk or ln_cpl = T' ) 
     197         IF( nn_ice_embd == 0            )   CALL ctl_stop( 'sbc_init : CICE sea-ice models require nn_ice_embd = 1 or 2' ) 
     198         IF( lk_agrif                    )   CALL ctl_stop( 'sbc_init : CICE sea-ice model not currently available with AGRIF' ) 
     199      CASE DEFAULT                     !- not supported 
     200      END SELECT 
     201      ! 
     202      IF( nn_ice == 3 ) THEN           !- LIM3 case: multi-category flux option 
     203         IF(lwp) WRITE(numout,*) 
     204         SELECT CASE( nn_limflx )         ! LIM3 Multi-category heat flux formulation 
     205         CASE ( -1 )    
     206            IF(lwp) WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
     207            IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     208         CASE ( 0  )    
     209            IF(lwp) WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) ' 
     210         CASE ( 1  ) 
     211            IF(lwp) WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
     212            IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     213         CASE ( 2  ) 
     214            IF(lwp) WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     215            IF( .NOT.ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
     216         CASE DEFAULT 
     217            CALL ctl_stop( 'sbcmod: LIM3 option, nn_limflx, should be between -1 and 2' ) 
    161218         END SELECT 
    162       ENDIF 
    163       ! 
    164       IF( nn_components /= jp_iam_nemo .AND. .NOT. lk_oasis )   & 
    165          &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
    166       IF( nn_components == jp_iam_opa .AND. ln_cpl )   & 
    167          &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_cpl = T in OPA' ) 
    168       IF( nn_components == jp_iam_opa .AND. ln_mixcpl )   & 
    169          &      CALL ctl_stop( 'sbc_init : OPA-SAS coupled via OASIS, but ln_mixcpl = T in OPA' ) 
    170       IF( ln_cpl .AND. .NOT. lk_oasis )    & 
    171          &      CALL ctl_stop( 'sbc_init : OASIS-coupled atmosphere model, but key_oasis3 disabled' ) 
    172       IF( ln_mixcpl .AND. .NOT. lk_oasis )    & 
    173          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires the cpp key key_oasis3' ) 
    174       IF( ln_mixcpl .AND. .NOT. ln_cpl )    & 
    175          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) requires ln_cpl = T' ) 
    176       IF( ln_mixcpl .AND. nn_components /= jp_iam_nemo )    & 
    177          &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) is not yet working with sas-opa coupling via oasis' ) 
    178  
    179       !                              ! allocate sbc arrays 
     219      ELSE                             ! other sea-ice model 
     220         IF( nn_limflx >= 0  )   CALL ctl_warn( 'sbc_init : multi-category flux option (nn_limflx) only available in LIM3' ) 
     221      ENDIF 
     222      ! 
     223      !                       !**  allocate and set required variables 
     224      ! 
     225      !                             !* allocate sbc arrays 
    180226      IF( sbc_oce_alloc() /= 0 )   CALL ctl_stop( 'sbc_init : unable to allocate sbc_oce arrays' ) 
    181  
    182       !                          ! Checks: 
    183       IF( .NOT. ln_isf ) THEN                      ! variable initialisation if no ice shelf 
     227      ! 
     228      IF( .NOT.ln_isf ) THEN        !* No ice-shelf in the domain : allocate and set to zero 
    184229         IF( sbc_isf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_isf arrays' ) 
    185          fwfisf  (:,:)   = 0.0_wp ; fwfisf_b  (:,:)   = 0.0_wp 
    186          risf_tsc(:,:,:) = 0.0_wp ; risf_tsc_b(:,:,:) = 0.0_wp 
     230         fwfisf  (:,:)   = 0._wp   ;   risf_tsc  (:,:,:) = 0._wp 
     231         fwfisf_b(:,:)   = 0._wp   ;   risf_tsc_b(:,:,:) = 0._wp 
    187232      END IF 
    188       IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! no ice in the domain, ice fraction is always zero 
    189  
    190       sfx(:,:) = 0._wp                             ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero) 
    191       !                                            ! only if sea-ice is present 
    192  
    193       fmmflx(:,:) = 0._wp                          ! freezing-melting array initialisation 
    194  
    195       taum(:,:) = 0._wp                            ! Initialise taum for use in gls in case of reduced restart 
    196  
    197       !                                            ! restartability 
    198       IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk .OR. ln_cpl ) )   & 
    199          &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
    200       IF( nn_ice == 4 .AND. .NOT.( ln_blk .OR. ln_cpl ) )   & 
    201          &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk or ln_cpl' ) 
    202       IF( nn_ice == 4 .AND. lk_agrif )   & 
    203          &   CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' ) 
    204       IF( ( nn_ice == 3 .OR. nn_ice == 4 ) .AND. nn_ice_embd == 0 )   & 
    205          &   CALL ctl_stop( 'LIM3 and CICE sea-ice models require nn_ice_embd = 1 or 2' ) 
    206       IF( ( nn_ice /= 3 ) .AND. ( nn_limflx >= 0 ) )   & 
    207          &   WRITE(numout,*) 'The nn_limflx>=0 option has no effect if sea ice model is not LIM3' 
    208       IF( ( nn_ice == 3 ) .AND. ( ln_cpl ) .AND. ( ( nn_limflx == -1 ) .OR. ( nn_limflx == 1 ) ) )   & 
    209          &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
    210       IF( ( nn_ice == 3 ) .AND. ( .NOT. ln_cpl ) .AND. ( nn_limflx == 2 ) )   & 
    211          &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
    212  
    213       IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
    214  
    215       IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk ) .AND. nn_components /= jp_iam_opa )   & 
    216          &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or the bulk formulation' ) 
    217  
    218       !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    219       ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl 
    220       ! 
     233      IF( nn_ice == 0 ) THEN        !* No sea-ice in the domain : ice fraction is always zero 
     234         IF( nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! except for OPA in SAS-OPA coupled case 
     235      ENDIF 
     236      ! 
     237      sfx   (:,:) = 0._wp           !* salt flux due to freezing/melting 
     238      fmmflx(:,:) = 0._wp           !* freezing minus melting flux 
     239 
     240      taum(:,:) = 0._wp             !* wind stress module (needed in GLS in case of reduced restart) 
     241 
     242 
     243      IF( ln_dm2dc ) THEN           !* daily mean to diurnal cycle 
     244         nday_qsr = -1   ! allow initialization at the 1st call 
     245         IF( .NOT.( ln_flx .OR. ln_blk ) .AND. nn_components /= jp_iam_opa )   & 
     246            &   CALL ctl_stop( 'qsr diurnal cycle from daily values requires a flux or bulk formulation' ) 
     247      ENDIF 
     248 
     249      !                             !* Choice of the Surface Boudary Condition (set nsbc) 
     250      ! 
     251      ll_purecpl  = ln_cpl .AND. .NOT.ln_mixcpl 
     252      ll_opa      = nn_components == jp_iam_opa 
     253      ll_not_nemo = nn_components /= jp_iam_nemo 
    221254      icpt = 0 
     255      ! 
    222256      IF( ln_ana          ) THEN   ;   nsbc = jp_ana     ; icpt = icpt + 1   ;   ENDIF       ! analytical           formulation 
    223257      IF( ln_flx          ) THEN   ;   nsbc = jp_flx     ; icpt = icpt + 1   ;   ENDIF       ! flux                 formulation 
     
    225259      IF( ll_purecpl      ) THEN   ;   nsbc = jp_purecpl ; icpt = icpt + 1   ;   ENDIF       ! Pure Coupled         formulation 
    226260      IF( cp_cfg == 'gyre') THEN   ;   nsbc = jp_gyre                        ;   ENDIF       ! GYRE analytical      formulation 
    227       IF( nn_components == jp_iam_opa )   & 
    228          &                  THEN   ;   nsbc = jp_none    ; icpt = icpt + 1   ;   ENDIF       ! opa coupling via SAS module 
    229       ! 
    230       IF( icpt /= 1 )    CALL ctl_stop( 'sbc_init: choose ONE and only ONE sbc option' ) 
    231       ! 
    232       IF(lwp) THEN 
     261      IF( ll_opa          ) THEN   ;   nsbc = jp_none    ; icpt = icpt + 1   ;   ENDIF       ! opa coupling via SAS module 
     262      ! 
     263      IF( icpt /= 1 )    CALL ctl_stop( 'sbc_init : choose ONE and only ONE sbc option' ) 
     264      ! 
     265      IF(lwp) THEN                     !- print the choice of surface flux formulation 
    233266         WRITE(numout,*) 
    234267         SELECT CASE( nsbc ) 
    235          CASE( jp_gyre    )   ;   WRITE(numout,*) '   GYRE analytical formulation' 
    236          CASE( jp_ana     )   ;   WRITE(numout,*) '   analytical formulation' 
    237          CASE( jp_flx     )   ;   WRITE(numout,*) '   flux formulation' 
    238          CASE( jp_blk     )   ;   WRITE(numout,*) '   bulk formulation' 
    239          CASE( jp_purecpl )   ;   WRITE(numout,*) '   pure coupled formulation' 
    240          CASE( jp_none    )   ;   WRITE(numout,*) '   OPA coupled to SAS via oasis' 
    241             IF( ln_mixcpl )       WRITE(numout,*) '       + forced-coupled mixed formulation' 
     268         CASE( jp_gyre    )   ;   WRITE(numout,*) '      ===>>   GYRE analytical formulation' 
     269         CASE( jp_ana     )   ;   WRITE(numout,*) '      ===>>   analytical 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' 
    242276         END SELECT 
    243          IF( nn_components/= jp_iam_nemo )  & 
    244             &                     WRITE(numout,*) '       + OASIS coupled SAS' 
    245       ENDIF 
    246       ! 
    247       IF( lk_oasis )   CALL sbc_cpl_init (nn_ice)   ! OASIS initialisation. must be done before: (1) first time step 
    248       !                                             !                                            (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 
    249284      !     nn_fsbc initialization if OPA-SAS coupling via OASIS 
    250       !     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 
    251286      IF( nn_components /= jp_iam_nemo ) THEN 
    252287         IF( nn_components == jp_iam_opa )   nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) 
     
    260295      ENDIF 
    261296      ! 
     297      !                             !* check consistency between model timeline and nn_fsbc 
    262298      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
    263299          MOD( nstock             , nn_fsbc) /= 0 ) THEN 
    264          WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
     300         WRITE(ctmp1,*) 'sbc_init : experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
    265301            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
    266302         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     
    268304      ! 
    269305      IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   & 
    270          &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
    271       ! 
    272       IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   & 
    273          &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
    274       ! 
    275                           CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
    276       ! 
    277       IF( ln_ssr      )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
    278       ! 
    279                           CALL sbc_rnf_init               ! Runof initialisation 
    280       ! 
    281       IF( nn_ice == 3 )   CALL sbc_lim_init               ! LIM3 initialisation 
    282       ! 
    283       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 
    284325      ! 
    285326   END SUBROUTINE sbc_init 
     
    337378      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    338379      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx) 
    339       CASE( jp_gyre    )   ;   CALL sbc_gyre  ( kt )                     ! analytical formulation : GYRE configuration 
    340       CASE( jp_ana     )   ;   CALL sbc_ana   ( kt )                     ! analytical formulation : uniform sbc 
    341       CASE( jp_flx     )   ;   CALL sbc_flx   ( kt )                     ! flux formulation 
     380      CASE( jp_gyre    )   ;   CALL sbc_gyre   ( kt )                    ! analytical formulation : GYRE configuration 
     381      CASE( jp_ana     )   ;   CALL sbc_ana    ( kt )                    ! analytical formulation : uniform sbc 
     382      CASE( jp_flx     )   ;   CALL sbc_flx    ( kt )                    ! flux formulation 
    342383      CASE( jp_blk     ) 
    343384         IF( ll_sas    )       CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA 
Note: See TracChangeset for help on using the changeset viewer.