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 2216 – NEMO

Changeset 2216


Ignore:
Timestamp:
2010-10-12T13:36:25+02:00 (14 years ago)
Author:
smasson
Message:

diurnal cycle in coupled mode in dev_r2174_DCY, see ticket:730

Location:
branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r2210 r2216  
    183183#endif 
    184184      !                                                        ! surface ocean fluxes computed with CLIO bulk formulea 
    185       IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce_core( kt, sf, sst_m, ssu_m, ssv_m ) 
     185      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m ) 
    186186      ! 
    187187   END SUBROUTINE sbc_blk_core 
    188188    
    189189    
    190    SUBROUTINE blk_oce_core( kt, sf, pst, pu, pv ) 
     190   SUBROUTINE blk_oce_core( sf, pst, pu, pv ) 
    191191      !!--------------------------------------------------------------------- 
    192192      !!                     ***  ROUTINE blk_core  *** 
     
    209209      !!  ** Nota  :   sf has to be a dummy argument for AGRIF on NEC 
    210210      !!--------------------------------------------------------------------- 
    211       INTEGER ,  INTENT(in)                     ::   kt   ! ocean time step 
    212211      TYPE(fld), INTENT(in), DIMENSION(:)       ::   sf    ! input data 
    213212      REAL(wp),  INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celcius] 
     
    263262      ! ----------------------------------------------------------------------------- ! 
    264263     
    265       IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( kt, sf(jp_qsr)%fnow )   ! modify now Qsr to include the diurnal cycle 
     264      IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow )   ! modify now Qsr to include the diurnal cycle 
    266265      ELSE                  ;   qsr(:,:) = sf(jp_qsr)%fnow(:,:) 
    267266      ENDIF 
  • branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbccpl.F90

    r2090 r2216  
    2323   USE sbc_oce         ! Surface boundary condition: ocean fields 
    2424   USE sbc_ice         ! Surface boundary condition: ice fields 
     25   USE sbcdcy          ! surface boundary condition: diurnal cycle 
    2526   USE phycst          ! physical constants 
    2627#if defined key_lim3 
     
    728729         IF( srcv(jpr_qsroce)%laction )   qsr(:,:) = frcv(:,:,jpr_qsroce)  
    729730         IF( srcv(jpr_qsrmix)%laction )   qsr(:,:) = frcv(:,:,jpr_qsrmix) 
     731         IF( ln_dm2dc )   qsr(:,:) = sbc_dcy( qsr )                           ! modify qsr to include the diurnal cycle 
    730732         ! 
    731733         !                                                       ! total freshwater fluxes over the ocean (emp, emps) 
     
    11591161            &                     + palbi         (:,:,1) * zicefr(:,:,1) ) ) 
    11601162      END SELECT 
     1163      IF( ln_dm2dc ) THEN   ! modify qsr to include the diurnal cycle 
     1164         pqsr_tot(:,:  ) = sbc_dcy( pqsr_tot(:,:  ) ) 
     1165         pqsr_ice(:,:,1) = sbc_dcy( pqsr_ice(:,:,1) ) 
     1166      ENDIF 
    11611167 
    11621168      SELECT CASE( TRIM( cn_rcv_dqnsdt ) ) 
  • branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcdcy.F90

    r2210 r2216  
    2121   IMPLICIT NONE 
    2222   PRIVATE 
    23    INTEGER                      ::   nday_qsr                    ! day when parameters were computed 
     23   INTEGER, PUBLIC              ::   nday_qsr                    ! day when parameters were computed 
    2424   REAL(wp), DIMENSION(jpi,jpj) ::   raa , rbb  , rcc  , rab     ! parameters used to compute the diurnal cycle 
    2525   REAL(wp), DIMENSION(jpi,jpj) ::   rtmd, rdawn, rdusk, rscal   !     -       -         -           -      - 
     
    3434CONTAINS 
    3535 
    36       FUNCTION sbc_dcy( kt, pqsrin ) RESULT( zqsrout ) 
     36      FUNCTION sbc_dcy( pqsrin ) RESULT( zqsrout ) 
    3737      !!---------------------------------------------------------------------- 
    3838      !!                  ***  ROUTINE sbc_dcy  *** 
     
    4848      !!              Part 1: a diurnally forced OGCM. Climate Dynamics 29:6, 575-590. 
    4949      !!---------------------------------------------------------------------- 
    50       INTEGER,                      INTENT(in   ) ::   kt        ! ocean time-step index 
    5150      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   pqsrin    ! input daily QSR flux  
    5251      !! 
     
    7574 
    7675      !                                           
    77       IF( kt == nit000 ) THEN       ! first time step only                
     76      IF( nday_qsr == -1 ) THEN       ! first time step only                
    7877         IF(lwp) THEN 
    7978            WRITE(numout,*) 
     
    8281            WRITE(numout,*) 
    8382         ENDIF 
    84          nday_qsr = 0 
    8583         ! Compute rcc needed to compute the time integral of the diurnal cycle 
    8684         rcc(:,:) = zconvrad * glamt(:,:) - rpi 
     
    140138         rdawn(:,:) = MOD((rdawn(:,:) + 1.), 1.) 
    141139         rdusk(:,:) = MOD((rdusk(:,:) + 1.), 1.) 
    142  
    143140 
    144141         !     2.2 Compute the scalling function: 
  • branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcflx.F90

    r2210 r2216  
    126126      
    127127      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN                        ! update ocean fluxes at each SBC frequency 
    128          IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( kt, sf(jp_qsr)%fnow )   ! modify now Qsr to include the diurnal cycle 
     128         IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow )   ! modify now Qsr to include the diurnal cycle 
    129129         ELSE                  ;   qsr(:,:) = sf(jp_qsr)%fnow(:,:) 
    130130         ENDIF 
  • branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcmod.F90

    r2188 r2216  
    1818   USE sbc_oce          ! Surface boundary condition: ocean fields 
    1919   USE sbc_ice          ! Surface boundary condition: ice fields 
     20   USE sbcdcy           ! surface boundary condition: diurnal cycle 
    2021   USE sbcssm           ! surface boundary condition: sea-surface mean variables 
    2122   USE sbcana           ! surface boundary condition: analytical formulation 
     
    133134         &   CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' ) 
    134135       
     136      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
     137 
    135138      IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) )   & 
    136139         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
Note: See TracChangeset for help on using the changeset viewer.