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 5220 for branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90 – NEMO

Ignore:
Timestamp:
2015-04-17T11:50:03+02:00 (9 years ago)
Author:
smasson
Message:

dev_r5218_CNRS17_coupling: first update

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r5123 r5220  
    3838   USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model 
    3939   USE sbccpl           ! surface boundary condition: coupled florulation 
     40   USE cpl_oasis3       ! OASIS routines for coupling 
    4041   USE sbcssr           ! surface boundary condition: sea surface restoring 
    4142   USE sbcrnf           ! surface boundary condition: runoffs 
     
    8384      INTEGER ::   icpt   ! local integer 
    8485      !! 
    85       NAMELIST/namsbc/ nn_fsbc   , ln_ana    , ln_flx,  ln_blk_clio, ln_blk_core,           & 
    86          &             ln_blk_mfs, ln_apr_dyn, nn_ice,  nn_ice_embd, ln_dm2dc   , ln_rnf,   & 
    87          &             ln_ssr    ,  nn_isf , nn_fwb    , ln_cdgw , ln_wave , ln_sdw, nn_lsm, nn_limflx 
     86      NAMELIST/namsbc/ nn_fsbc   , ln_ana    , ln_flx, ln_blk_clio, ln_blk_core, ln_mixcpl,   & 
     87         &             ln_blk_mfs, ln_apr_dyn, nn_ice, nn_ice_embd, ln_dm2dc   , ln_rnf   ,   & 
     88         &             ln_ssr    , nn_isf    , nn_fwb, ln_cdgw    , ln_wave    , ln_sdw   ,   & 
     89         &             nn_lsm    , nn_limflx , nn_components, ln_cpl 
    8890      INTEGER  ::   ios 
     91      INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
     92      LOGICAL  ::   ll_purecpl 
    8993      !!---------------------------------------------------------------------- 
    9094 
     
    114118          nn_ice      =   0 
    115119      ENDIF 
    116       
     120 
    117121      IF(lwp) THEN               ! Control print 
    118122         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
     
    124128         WRITE(numout,*) '              CORE bulk  formulation                     ln_blk_core = ', ln_blk_core 
    125129         WRITE(numout,*) '              MFS  bulk  formulation                     ln_blk_mfs  = ', ln_blk_mfs 
    126          WRITE(numout,*) '              coupled    formulation (T if key_oasis3)   lk_cpl      = ', lk_cpl 
     130         WRITE(numout,*) '              forced-coupled mixed formulation           ln_mixcpl   = ', ln_mixcpl 
     131         WRITE(numout,*) '              coupled    formulation                     ln_cpl      = ', ln_cpl 
     132         WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis    = ', lk_oasis 
     133         WRITE(numout,*) '              components of your executable              nn_components = ', nn_components 
    127134         WRITE(numout,*) '              Multicategory heat flux formulation (LIM3) nn_limflx   = ', nn_limflx 
    128135         WRITE(numout,*) '           Misc. options of sbc : ' 
     
    163170#endif 
    164171 
     172      IF ( nn_components /= jp_iam_nemo .AND. .NOT. lk_oasis )   & 
     173         &      CALL ctl_stop( 'STOP', 'sbc_init : OPA-SAS coupled via OASIS, but key_oasis3 disabled' ) 
     174      IF ( ln_cpl .AND. .NOT. lk_oasis )    & 
     175         &      CALL ctl_stop( '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. nn_components /= jp_iam_nemo )    & 
     179         &      CALL ctl_stop( 'the forced-coupled mixed mode (ln_mixcpl) is not yet working with sas-opa coupling via oasis' ) 
     180 
    165181      ! 
    166182      !                              ! allocate sbc arrays 
     
    182198         fwfisf_b(:,:) = 0.0_wp 
    183199      END IF 
    184       IF( nn_ice == 0  )   fr_i(:,:) = 0.e0        ! no ice in the domain, ice fraction is always zero 
     200      IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa )   fr_i(:,:) = 0.e0 ! no ice in the domain, ice fraction is always zero 
    185201 
    186202      sfx(:,:) = 0.0_wp                            ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero)  
     
    192208 
    193209      !                                            ! restartability    
    194       IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
    195           MOD( nstock             , nn_fsbc) /= 0 ) THEN  
    196          WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
    197             &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
    198          CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
    199       ENDIF 
    200       ! 
    201       IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   & 
    202          &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
    203       ! 
    204       IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   & 
     210      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. ln_cpl ) )   & 
    205211         &   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. lk_cpl ) )   & 
    207          &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or lk_cpl' ) 
     212      IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. ln_cpl ) )   & 
     213         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or ln_cpl' ) 
    208214      IF( nn_ice == 4 .AND. lk_agrif )   & 
    209215         &   CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' ) 
     
    212218      IF( ( nn_ice /= 3 ) .AND. ( nn_limflx >= 0 ) )   & 
    213219         &   WRITE(numout,*) 'The nn_limflx>=0 option has no effect if sea ice model is not LIM3' 
    214       IF( ( nn_ice == 3 ) .AND. ( lk_cpl ) .AND. ( ( nn_limflx == -1 ) .OR. ( nn_limflx == 1 ) ) )   & 
     220      IF( ( nn_ice == 3 ) .AND. ( ln_cpl ) .AND. ( ( nn_limflx == -1 ) .OR. ( nn_limflx == 1 ) ) )   & 
    215221         &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
    216       IF( ( nn_ice == 3 ) .AND. ( .NOT. lk_cpl ) .AND. ( nn_limflx == 2 ) )   & 
     222      IF( ( nn_ice == 3 ) .AND. ( .NOT. ln_cpl ) .AND. ( nn_limflx == 2 ) )   & 
    217223         &   CALL ctl_stop( 'The chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
    218224 
     
    222228         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
    223229       
    224       IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   & 
    225          &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
    226  
    227230      IF ( ln_wave ) THEN 
    228231      !Activated wave module but neither drag nor stokes drift activated 
     
    240243       
    241244      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
     245      ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl 
     246      ! 
    242247      icpt = 0 
    243248      IF( ln_ana          ) THEN   ;   nsbc = jp_ana    ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation 
     
    246251      IF( ln_blk_core     ) THEN   ;   nsbc = jp_core   ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk       formulation 
    247252      IF( ln_blk_mfs      ) THEN   ;   nsbc = jp_mfs    ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk       formulation 
    248       IF( lk_cpl          ) THEN   ;   nsbc = jp_cpl    ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation 
     253      IF( ll_purecpl      ) THEN   ;   nsbc = jp_cpl    ; icpt = icpt + 1   ;   ENDIF       ! Pure Coupled    formulation 
    249254      IF( cp_cfg == 'gyre') THEN   ;   nsbc = jp_gyre                       ;   ENDIF       ! GYRE analytical formulation 
     255      IF( nn_components == jp_iam_opa ) THEN   ;   nsbc = jp_none  ; icpt = icpt + 1 ;   ENDIF       ! opa coupling via SAS module 
    250256      IF( lk_esopa        )            nsbc = jp_esopa                                      ! esopa test, ALL formulations 
    251257      ! 
     
    265271         IF( nsbc == jp_clio  )   WRITE(numout,*) '              CLIO bulk formulation' 
    266272         IF( nsbc == jp_core  )   WRITE(numout,*) '              CORE bulk formulation' 
    267          IF( nsbc == jp_cpl   )   WRITE(numout,*) '              coupled formulation' 
     273         IF( nsbc == jp_cpl   )   WRITE(numout,*) '              pure coupled formulation' 
    268274         IF( nsbc == jp_mfs   )   WRITE(numout,*) '              MFS Bulk formulation' 
    269       ENDIF 
    270       ! 
     275         IF( nsbc == jp_none  )   WRITE(numout,*) '              OPA coupled to SAS via oasis' 
     276         IF( ln_mixcpl        )   WRITE(numout,*) '              + forced-coupled mixed formulation' 
     277         IF( nn_components/= 0 )  WRITE(numout,*) '              + OASIS coupled SAS' 
     278      ENDIF 
     279      ! 
     280      IF( lk_oasis         )   CALL sbc_cpl_init (nn_ice)   ! OASIS initialisation. must be done before: (1) first time step 
     281      !                                                     !                                            (2) the use of nn_fsbc 
     282 
     283!     nn_fsbc initialization if OPA-SAS coupling via OASIS 
     284!     sas model time step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
     285      IF ( nn_components /= jp_iam_nemo ) THEN 
     286 
     287         IF ( nn_components == jp_iam_opa ) nn_fsbc = cpl_freq('O_SFLX') / NINT(rdt) 
     288         IF ( nn_components == jp_iam_sas ) nn_fsbc = cpl_freq('I_SFLX') / NINT(rdt) 
     289         ! 
     290         IF(lwp)THEN 
     291            WRITE(numout,*) 
     292            WRITE(numout,*)"   OPA-SAS coupled via OASIS : nn_fsbc re-defined from OASIS namcouple ", nn_fsbc 
     293            WRITE(numout,*) 
     294         ENDIF 
     295      ENDIF 
     296 
     297      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
     298          MOD( nstock             , nn_fsbc) /= 0 ) THEN  
     299         WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
     300            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
     301         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     302      ENDIF 
     303      ! 
     304      IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   & 
     305         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
     306      ! 
     307      IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   & 
     308         &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
     309 
     310 
     311      IF( nn_components /= jp_iam_sas ) THEN 
     312 
    271313                               CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
     314      ELSE 
     315      ! 
     316      ! sas currently uses surface temperature and salinity in tsn array 
     317      ! for initialisation 
     318      ! and ub, vb arrays in ice dynamics 
     319      ! so allocate enough of arrays to use 
     320      ! 
     321         ierr3 = 0 
     322         jpm = MAX(jp_tem, jp_sal) 
     323         ALLOCATE( tsn(jpi,jpj,1,jpm), STAT=ierr0 ) 
     324         ALLOCATE( ub(jpi,jpj,1)     , STAT=ierr1 ) 
     325         ALLOCATE( vb(jpi,jpj,1)     , STAT=ierr2 ) 
     326         IF ( nn_ice == 1 ) ALLOCATE( tsb(jpi,jpj,1,jpm), STAT=ierr3 ) 
     327         ierr = ierr0 + ierr1 + ierr2 + ierr3 
     328         IF( ierr > 0 ) THEN 
     329            CALL ctl_stop('sbc_ssm_init: unable to allocate surface arrays') 
     330         ENDIF 
     331 
     332      ENDIF 
    272333      ! 
    273334      IF( ln_ssr           )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
     
    276337 
    277338      IF( nn_ice == 4      )   CALL cice_sbc_init( nsbc )      ! CICE initialisation 
    278       ! 
    279       IF( nsbc   == jp_cpl )   CALL sbc_cpl_init (nn_ice)      ! OASIS initialisation. must be done before first time step 
    280  
     339       
    281340   END SUBROUTINE sbc_init 
    282341 
     
    321380                                                         ! (caution called before sbc_ssm) 
    322381      ! 
    323       CALL sbc_ssm( kt )                                 ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     382      IF( nn_components /= jp_iam_sas ) CALL sbc_ssm( kt )         ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
    324383      !                                                  ! averaged over nf_sbc time-step 
    325384 
     
    333392      CASE( jp_flx   )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
    334393      CASE( jp_clio  )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean 
    335       CASE( jp_core  )   ;   CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
    336       CASE( jp_cpl   )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! coupled formulation 
     394      CASE( jp_core  )    
     395                             IF( nn_components == jp_iam_sas ) & 
     396                                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )     !  OASIS-coupled ice 
     397                             CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
     398                                                                        ! from oce: sea surface variables (sst_m, sss_m,  ssu_m,  ssv_m) 
     399      CASE( jp_cpl   )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
     400                                                                        ! 
    337401      CASE( jp_mfs   )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
     402      CASE( jp_none  )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OASIS-coupled ice 
     403                                                         ! fluxes qsr, qns, emp, sfx,utau, vtau 
     404                                                         ! sss_m, ssu_m, ssv_m) 
    338405      CASE( jp_esopa )                                 
    339406                             CALL sbc_ana     ( kt )                    ! ESOPA, test ALL the formulations 
     
    344411                             CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! 
    345412      END SELECT 
     413 
     414      IF( ln_mixcpl )        CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation 
     415 
    346416 
    347417      !                                            !==  Misc. Options  ==! 
     
    408478         ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b'  , qsr  ) 
    409479         CALL iom_rstput( kt, nitrst, numrow, 'emp_b'  , emp  ) 
    410          CALL iom_rstput( kt, nitrst, numrow, 'sfx_b' , sfx ) 
     480         CALL iom_rstput( kt, nitrst, numrow, 'sfx_b'  , sfx ) 
    411481      ENDIF 
    412482 
     
    423493         CALL iom_put( "qns"   , qns        )                   ! solar heat flux 
    424494         CALL iom_put( "qsr"   ,       qsr  )                   ! solar heat flux 
    425          IF( nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction  
     495         IF( nn_ice > 0 .OR. nn_components == jp_iam_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction  
    426496         CALL iom_put( "taum"  , taum       )                   ! wind stress module  
    427497         CALL iom_put( "wspd"  , wndm       )                   ! wind speed  module over free ocean or leads in presence of sea-ice 
Note: See TracChangeset for help on using the changeset viewer.