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 4880 for branches/2014/dev_4728_CNRS04_coupled_interface – NEMO

Ignore:
Timestamp:
2014-11-21T10:46:23+01:00 (9 years ago)
Author:
smasson
Message:

dev_4728_CNRS04_coupled_interface: improve readability un the use of nsbc

Location:
branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/CONFIG/cfg.txt

    r4690 r4880  
    11GYRE_PISCES OPA_SRC TOP_SRC 
    22ORCA2_LIM_CFC_C14b OPA_SRC LIM_SRC_2 NST_SRC TOP_SRC 
    3 GYRE OPA_SRC 
    43GYRE_XIOS OPA_SRC 
    54ORCA2_OFF_PISCES OPA_SRC OFF_SRC TOP_SRC 
     
    109GYRE_BFM OPA_SRC TOP_SRC 
    1110ORCA2_LIM_PISCES OPA_SRC LIM_SRC_2 NST_SRC TOP_SRC 
     11GYRE OPA_SRC 
    1212ORCA2_LIM3 OPA_SRC LIM_SRC_3 NST_SRC 
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r4859 r4880  
    6565   ! 
    6666   INTEGER , PUBLIC ::   nn_lsm         !: Number of iteration if seaoverland is applied 
     67   !!---------------------------------------------------------------------- 
     68   !!           switch definition (improve readability) 
     69   !!---------------------------------------------------------------------- 
     70   INTEGER , PUBLIC, PARAMETER ::   jp_gyre    = 0        !: GYRE analytical formulation 
     71   INTEGER , PUBLIC, PARAMETER ::   jp_ana     = 1        !: analytical      formulation 
     72   INTEGER , PUBLIC, PARAMETER ::   jp_flx     = 2        !: flux            formulation 
     73   INTEGER , PUBLIC, PARAMETER ::   jp_clio    = 3        !: CLIO bulk       formulation 
     74   INTEGER , PUBLIC, PARAMETER ::   jp_core    = 4        !: CORE bulk       formulation 
     75   INTEGER , PUBLIC, PARAMETER ::   jp_cpl     = 5        !: Coupled         formulation 
     76   INTEGER , PUBLIC, PARAMETER ::   jp_mfs     = 6        !: MFS  bulk       formulation 
     77   INTEGER , PUBLIC, PARAMETER ::   jp_esopa   = -1       !: esopa test, ALL formulations 
     78    
    6779   !!---------------------------------------------------------------------- 
    6880   !!              Ocean Surface Boundary Condition fields 
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r4857 r4880  
    9595   END FUNCTION sbc_ice_cice_alloc 
    9696 
    97    SUBROUTINE sbc_ice_cice( kt, nsbc ) 
     97   SUBROUTINE sbc_ice_cice( kt, ksbc ) 
    9898      !!--------------------------------------------------------------------- 
    9999      !!                  ***  ROUTINE sbc_ice_cice  *** 
     
    113113      !!--------------------------------------------------------------------- 
    114114      INTEGER, INTENT(in) ::   kt      ! ocean time step 
    115       INTEGER, INTENT(in) ::   nsbc    ! surface forcing type 
     115      INTEGER, INTENT(in) ::   ksbc    ! surface forcing type 
    116116      !!---------------------------------------------------------------------- 
    117117      ! 
     
    123123 
    124124         ! Make sure any fluxes required for CICE are set 
    125          IF ( nsbc == 2 ) THEN 
     125         IF      ( ksbc == jp_flx ) THEN 
    126126            CALL cice_sbc_force(kt) 
    127          ELSE IF ( nsbc == 5 ) THEN 
     127         ELSE IF ( ksbc == jp_cpl ) THEN 
    128128            CALL sbc_cpl_ice_flx( 1.0-fr_i  ) 
    129129         ENDIF 
    130130 
    131          CALL cice_sbc_in ( kt, nsbc ) 
     131         CALL cice_sbc_in  ( kt, ksbc ) 
    132132         CALL CICE_Run 
    133          CALL cice_sbc_out ( kt, nsbc ) 
    134  
    135          IF ( nsbc == 5 )  CALL cice_sbc_hadgam(kt+1) 
     133         CALL cice_sbc_out ( kt, ksbc ) 
     134 
     135         IF ( ksbc == jp_cpl )  CALL cice_sbc_hadgam(kt+1) 
    136136 
    137137      ENDIF                                          ! End sea-ice time step only 
     
    141141   END SUBROUTINE sbc_ice_cice 
    142142 
    143    SUBROUTINE cice_sbc_init (nsbc) 
     143   SUBROUTINE cice_sbc_init (ksbc) 
    144144      !!--------------------------------------------------------------------- 
    145145      !!                    ***  ROUTINE cice_sbc_init  *** 
    146146      !! ** Purpose: Initialise ice related fields for NEMO and coupling 
    147147      !! 
    148       INTEGER, INTENT( in  ) ::   nsbc                ! surface forcing type 
     148      INTEGER, INTENT( in  ) ::   ksbc                ! surface forcing type 
    149149      REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2 
    150150      REAL(wp) ::   zcoefu, zcoefv, zcoeff            ! local scalar 
     
    165165 
    166166! Do some CICE consistency checks 
    167       IF ( (nsbc == 2) .OR. (nsbc == 5) ) THEN 
     167      IF ( (ksbc == jp_flx) .OR. (ksbc == jp_cpl) ) THEN 
    168168         IF ( calc_strair .OR. calc_Tsfc ) THEN 
    169169            CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=F and calc_Tsfc=F in ice_in' ) 
    170170         ENDIF 
    171       ELSEIF (nsbc == 4) THEN 
     171      ELSEIF (ksbc == jp_core) THEN 
    172172         IF ( .NOT. (calc_strair .AND. calc_Tsfc) ) THEN 
    173173            CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=T and calc_Tsfc=T in ice_in' ) 
     
    190190 
    191191      CALL cice2nemo(aice,fr_i, 'T', 1. ) 
    192       IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN 
     192      IF ( (ksbc == jp_flx) .OR. (ksbc == jp_cpl) ) THEN 
    193193         DO jl=1,ncat 
    194194            CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. ) 
     
    232232 
    233233    
    234    SUBROUTINE cice_sbc_in (kt, nsbc) 
     234   SUBROUTINE cice_sbc_in (kt, ksbc) 
    235235      !!--------------------------------------------------------------------- 
    236236      !!                    ***  ROUTINE cice_sbc_in  *** 
     
    238238      !!--------------------------------------------------------------------- 
    239239      INTEGER, INTENT(in   ) ::   kt   ! ocean time step 
    240       INTEGER, INTENT(in   ) ::   nsbc ! surface forcing type 
     240      INTEGER, INTENT(in   ) ::   ksbc ! surface forcing type 
    241241 
    242242      INTEGER  ::   ji, jj, jl                   ! dummy loop indices       
     
    262262! forced and coupled case  
    263263 
    264       IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN 
     264      IF ( (ksbc == jp_flx).OR.(ksbc == jp_cpl) ) THEN 
    265265 
    266266         ztmpn(:,:,:)=0.0 
     
    287287 
    288288! Surface downward latent heat flux (CI_5) 
    289          IF (nsbc == 2) THEN 
     289         IF (ksbc == jp_flx) THEN 
    290290            DO jl=1,ncat 
    291291               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 
     
    316316! GBM conductive flux through ice (CI_6) 
    317317!  Convert to GBM 
    318             IF (nsbc == 2) THEN 
     318            IF (ksbc == jp_flx) THEN 
    319319               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 
    320320            ELSE 
     
    325325! GBM surface heat flux (CI_7) 
    326326!  Convert to GBM 
    327             IF (nsbc == 2) THEN 
     327            IF (ksbc == jp_flx) THEN 
    328328               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)  
    329329            ELSE 
     
    333333         ENDDO 
    334334 
    335       ELSE IF (nsbc == 4) THEN 
     335      ELSE IF (ksbc == jp_core) THEN 
    336336 
    337337! Pass CORE forcing fields to CICE (which will calculate heat fluxes etc itself) 
     
    458458 
    459459 
    460    SUBROUTINE cice_sbc_out (kt,nsbc) 
     460   SUBROUTINE cice_sbc_out (kt,ksbc) 
    461461      !!--------------------------------------------------------------------- 
    462462      !!                    ***  ROUTINE cice_sbc_out  *** 
     
    464464      !!--------------------------------------------------------------------- 
    465465      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    466       INTEGER, INTENT( in  ) ::   nsbc ! surface forcing type 
     466      INTEGER, INTENT( in  ) ::   ksbc ! surface forcing type 
    467467       
    468468      INTEGER  ::   ji, jj, jl                 ! dummy loop indices 
     
    510510! Freshwater fluxes  
    511511 
    512       IF (nsbc == 2) THEN 
     512      IF (ksbc == jp_flx) THEN 
    513513! Note that emp from the forcing files is evap*(1-aice)-(tprecip-aice*sprecip) 
    514514! What we want here is evap*(1-aice)-tprecip*(1-aice) hence manipulation below 
     
    516516! Better to use evap and tprecip? (but for now don't read in evap in this case) 
    517517         emp(:,:)  = emp(:,:)+fr_i(:,:)*(tprecip(:,:)-sprecip(:,:)) 
    518       ELSE IF (nsbc == 4) THEN 
     518      ELSE IF (ksbc == jp_core) THEN 
    519519         emp(:,:)  = (1.0-fr_i(:,:))*emp(:,:)         
    520       ELSE IF (nsbc ==5) THEN 
     520      ELSE IF (ksbc == jp_cpl) THEN 
    521521! emp_tot is set in sbc_cpl_ice_flx (called from cice_sbc_in above)  
    522522! This is currently as required with the coupling fields from the UM atmosphere 
     
    543543! Scale qsr and qns according to ice fraction (bulk formulae only) 
    544544 
    545       IF (nsbc == 4) THEN 
     545      IF (ksbc == jp_core) THEN 
    546546         qsr(:,:)=qsr(:,:)*(1.0-fr_i(:,:)) 
    547547         qns(:,:)=qns(:,:)*(1.0-fr_i(:,:)) 
    548548      ENDIF 
    549549! Take into account snow melting except for fully coupled when already in qns_tot 
    550       IF (nsbc == 5) THEN 
     550      IF (ksbc == jp_cpl) THEN 
    551551         qsr(:,:)= qsr_tot(:,:) 
    552552         qns(:,:)= qns_tot(:,:) 
     
    575575 
    576576      CALL cice2nemo(aice,fr_i,'T', 1. ) 
    577       IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN 
     577      IF ( (ksbc == jp_flx).OR.(ksbc == jp_cpl) ) THEN 
    578578         DO jl=1,ncat 
    579579            CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. ) 
     
    994994CONTAINS 
    995995 
    996    SUBROUTINE sbc_ice_cice ( kt, nsbc )     ! Dummy routine 
     996   SUBROUTINE sbc_ice_cice ( kt, ksbc )     ! Dummy routine 
    997997      WRITE(*,*) 'sbc_ice_cice: You should not have seen this print! error?', kt 
    998998   END SUBROUTINE sbc_ice_cice 
    999999 
    1000    SUBROUTINE cice_sbc_init (nsbc)    ! Dummy routine 
     1000   SUBROUTINE cice_sbc_init (ksbc)    ! Dummy routine 
    10011001      WRITE(*,*) 'cice_sbc_init: You should not have seen this print! error?' 
    10021002   END SUBROUTINE cice_sbc_init 
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r4853 r4880  
    146146 
    147147         SELECT CASE( kblk ) 
    148          CASE( 4 , 5 )   ! CORE and COUPLED bulk formulations 
     148         CASE( jp_core , jp_cpl )   ! CORE and COUPLED bulk formulations 
    149149 
    150150            ! albedo depends on cloud fraction because of non-linear spectral effects 
     
    169169         ! 
    170170         SELECT CASE( kblk ) 
    171          CASE( 3 )                                       ! CLIO bulk formulation 
     171         CASE( jp_clio )                                       ! CLIO bulk formulation 
    172172            CALL blk_ice_clio( t_su , zalb_cs    , zalb_os    , zalb_ice  ,               & 
    173173               &                      utau_ice   , vtau_ice   , qns_ice   , qsr_ice   ,   & 
     
    179179               &                                           dqns_ice, qla_ice, dqla_ice, nn_limflx ) 
    180180 
    181          CASE( 4 )                                       ! CORE bulk formulation 
     181         CASE( jp_core )                                       ! CORE bulk formulation 
    182182            CALL blk_ice_core( t_su , u_ice     , v_ice     , zalb_ice   ,               & 
    183183               &                      utau_ice  , vtau_ice  , qns_ice    , qsr_ice   ,   & 
     
    189189               &                                           dqns_ice, qla_ice, dqla_ice, nn_limflx ) 
    190190            ! 
    191          CASE ( 5 ) 
     191         CASE ( jp_cpl ) 
    192192             
    193193            CALL sbc_cpl_ice_tau( utau_ice , vtau_ice ) 
     
    318318                          ! MV -> seb 
    319319                          SELECT CASE( kblk ) 
    320                              CASE ( 5 ) 
     320                             CASE ( jp_cpl ) 
    321321                             CALL sbc_cpl_ice_flx( p_frld=pfrld, palbi=zalb_ice, psst=sst_m, pist=t_su    ) 
    322322                             IF( nn_limflx == 2 )   CALL ice_lim_flx( t_su, zalb_ice, qns_ice, qsr_ice ,   & 
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r4859 r4880  
    163163         ! 
    164164         SELECT CASE( ksbc ) 
    165          CASE( 3 )           ! CLIO bulk formulation 
     165         CASE( jp_clio )           ! CLIO bulk formulation 
    166166            CALL blk_ice_clio( zsist, zalb_ice_cs, zalb_ice_os,                         & 
    167167               &                      utau_ice   , vtau_ice   , qns_ice    , qsr_ice,   & 
     
    170170               &                      fr1_i0     , fr2_i0     , cp_ice_msh , jpl  ) 
    171171 
    172          CASE( 4 )           ! CORE bulk formulation 
     172         CASE( jp_core )           ! CORE bulk formulation 
    173173            CALL blk_ice_core( zsist, u_ice      , v_ice      , zalb_ice_cs,            & 
    174174               &                      utau_ice   , vtau_ice   , qns_ice    , qsr_ice,   & 
     
    178178            IF( ltrcdm2dc_ice )   CALL blk_ice_meanqsr( zalb_ice_cs, qsr_ice_mean, jpl ) 
    179179 
    180          CASE( 5 )           ! Coupled formulation : atmosphere-ice stress only (fluxes provided after ice dynamics) 
     180         CASE( jp_cpl )            ! Coupled formulation : atmosphere-ice stress only (fluxes provided after ice dynamics) 
    181181            CALL sbc_cpl_ice_tau( utau_ice , vtau_ice ) 
    182182         END SELECT 
     
    207207         END IF 
    208208         !                                             ! Ice surface fluxes in coupled mode  
    209          IF( ksbc == 5 )   THEN 
     209         IF( ksbc == jp_cpl )   THEN 
    210210            a_i(:,:,1)=fr_i 
    211211            CALL sbc_cpl_ice_flx( frld,                                              & 
  • branches/2014/dev_4728_CNRS04_coupled_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r4859 r4880  
    231231      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    232232      icpt = 0 
    233       IF( ln_ana          ) THEN   ;   nsbc =  1   ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation 
    234       IF( ln_flx          ) THEN   ;   nsbc =  2   ; icpt = icpt + 1   ;   ENDIF       ! flux            formulation 
    235       IF( ln_blk_clio     ) THEN   ;   nsbc =  3   ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk       formulation 
    236       IF( ln_blk_core     ) THEN   ;   nsbc =  4   ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk       formulation 
    237       IF( ln_blk_mfs      ) THEN   ;   nsbc =  6   ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk       formulation 
    238       IF( lk_cpl          ) THEN   ;   nsbc =  5   ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation 
    239       IF( cp_cfg == 'gyre') THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation 
    240       IF( lk_esopa        )            nsbc = -1                                       ! esopa test, ALL formulations 
     233      IF( ln_ana          ) THEN   ;   nsbc = jp_ana    ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation 
     234      IF( ln_flx          ) THEN   ;   nsbc = jp_flx    ; icpt = icpt + 1   ;   ENDIF       ! flux            formulation 
     235      IF( ln_blk_clio     ) THEN   ;   nsbc = jp_clio   ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk       formulation 
     236      IF( ln_blk_core     ) THEN   ;   nsbc = jp_core   ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk       formulation 
     237      IF( ln_blk_mfs      ) THEN   ;   nsbc = jp_mfs    ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk       formulation 
     238      IF( lk_cpl          ) THEN   ;   nsbc = jp_cpl    ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation 
     239      IF( cp_cfg == 'gyre') THEN   ;   nsbc = jp_gyre                       ;   ENDIF       ! GYRE analytical formulation 
     240      IF( lk_esopa        )            nsbc = jp_esopa                                      ! esopa test, ALL formulations 
    241241      ! 
    242242      IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN 
     
    249249      IF(lwp) THEN 
    250250         WRITE(numout,*) 
    251          IF( nsbc == -1 )   WRITE(numout,*) '              ESOPA test All surface boundary conditions' 
    252          IF( nsbc ==  0 )   WRITE(numout,*) '              GYRE analytical formulation' 
    253          IF( nsbc ==  1 )   WRITE(numout,*) '              analytical formulation' 
    254          IF( nsbc ==  2 )   WRITE(numout,*) '              flux formulation' 
    255          IF( nsbc ==  3 )   WRITE(numout,*) '              CLIO bulk formulation' 
    256          IF( nsbc ==  4 )   WRITE(numout,*) '              CORE bulk formulation' 
    257          IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation' 
    258          IF( nsbc ==  6 )   WRITE(numout,*) '              MFS Bulk formulation' 
    259       ENDIF 
    260       ! 
    261                           CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
    262       ! 
    263       IF( ln_ssr      )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
    264       ! 
    265       IF( nn_ice == 4 )   CALL cice_sbc_init( nsbc )      ! CICE initialisation 
    266       ! 
    267       IF( nsbc   == 5 )   CALL sbc_cpl_init (nn_ice)      ! OASIS initialisation. must be done before first time step 
     251         IF( nsbc == jp_esopa )   WRITE(numout,*) '              ESOPA test All surface boundary conditions' 
     252         IF( nsbc == jp_gyre )   WRITE(numout,*) '              GYRE analytical formulation' 
     253         IF( nsbc == jp_ana  )   WRITE(numout,*) '              analytical formulation' 
     254         IF( nsbc == jp_flx  )   WRITE(numout,*) '              flux formulation' 
     255         IF( nsbc == jp_clio )   WRITE(numout,*) '              CLIO bulk formulation' 
     256         IF( nsbc == jp_core )   WRITE(numout,*) '              CORE bulk formulation' 
     257         IF( nsbc == jp_cpl  )   WRITE(numout,*) '              coupled formulation' 
     258         IF( nsbc == jp_mfs  )   WRITE(numout,*) '              MFS Bulk formulation' 
     259      ENDIF 
     260      ! 
     261                               CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
     262      ! 
     263      IF( ln_ssr           )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
     264      ! 
     265      IF( nn_ice == 4      )   CALL cice_sbc_init( nsbc )      ! CICE initialisation 
     266      ! 
     267      IF( nsbc   == jp_cpl )   CALL sbc_cpl_init (nn_ice)      ! OASIS initialisation. must be done before first time step 
    268268 
    269269   END SUBROUTINE sbc_init 
     
    317317      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    318318      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx) 
    319       CASE(  0 )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
    320       CASE(  1 )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc 
    321       CASE(  2 )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
    322       CASE(  3 )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean 
    323       CASE(  4 )   ;   CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
    324       CASE(  5 )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! coupled formulation 
    325       CASE(  6 )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
    326       CASE( -1 )                                 
    327                        CALL sbc_ana     ( kt )                    ! ESOPA, test ALL the formulations 
    328                        CALL sbc_gyre    ( kt )                    ! 
    329                        CALL sbc_flx     ( kt )                    ! 
    330                        CALL sbc_blk_clio( kt )                    ! 
    331                        CALL sbc_blk_core( kt )                    ! 
    332                        CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! 
     319      CASE( jp_gyre )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
     320      CASE( jp_ana  )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc 
     321      CASE( jp_flx  )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
     322      CASE( jp_clio )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean 
     323      CASE( jp_core )   ;   CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
     324      CASE( jp_cpl  )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! coupled formulation 
     325      CASE( jp_mfs  )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
     326      CASE( jp_esopa )                                 
     327                             CALL sbc_ana     ( kt )                    ! ESOPA, test ALL the formulations 
     328                             CALL sbc_gyre    ( kt )                    ! 
     329                             CALL sbc_flx     ( kt )                    ! 
     330                             CALL sbc_blk_clio( kt )                    ! 
     331                             CALL sbc_blk_core( kt )                    ! 
     332                             CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! 
    333333      END SELECT 
    334334 
Note: See TracChangeset for help on using the changeset viewer.