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

Changeset 6010


Ignore:
Timestamp:
2015-12-07T14:32:39+01:00 (8 years ago)
Author:
timgraham
Message:

Tidying of DIU code

Location:
branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC
Files:
1 added
5 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r6005 r6010  
    145145      ENDIF 
    146146 
    147       IF(ln_diurnal) THEN 
    148          CALL iom_put( "sst_wl"   , x_dsst               )    ! warm layer 
    149          CALL iom_put( "sst_cs"   , x_csdsst             )    ! cool skin 
    150       ENDIF 
    151         
    152       IF( ln_diurnal_only ) RETURN  
    153        
    154147      IF( .NOT.lk_vvl ) THEN 
    155148         CALL iom_put( "e3t" , fse3t_n(:,:,:) ) 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIU/cool_skin.F90

    r5676 r6010  
    9494      
    9595      INTEGER :: ji,jj 
    96        
     96      
     97      IF ( .NOT. ln_blk_core ) THEN 
     98         CALL ctl_stop("cool_skin.f90: diurnal flux processing only implemented"//& 
     99         &             " for core bulk forcing") 
     100      ENDIF 
     101  
    97102      DO jj = 1,jpj 
    98103         DO ji = 1,jpi 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIU/diurnal_bulk.F90

    r5676 r6010  
    8181   END SUBROUTINE diurnal_sst_bulk_init 
    8282    
    83    SUBROUTINE diurnal_sst_takaya_step(psolflux, pqflux, ptauflux, prho, p_rdt,& 
    84             &                  pla, pthick, pcoolthick, pmu, ld_calcfrac, & 
     83   SUBROUTINE diurnal_sst_takaya_step(kt, psolflux, pqflux, ptauflux, prho, p_rdt,& 
     84            &                  pla, pthick, pcoolthick, pmu, & 
    8585            &                  p_fvel_bkginc, p_hflux_bkginc) 
    8686      !!---------------------------------------------------------------------- 
     
    123123      REAL(wp), INTENT(IN) :: p_rdt                         ! time-step 
    124124       
    125       LOGICAL, OPTIONAL, & 
    126       &     INTENT(IN)  :: ld_calcfrac   ! Set TRUE to recalculate the  
    127                                          ! solar fraction 
    128        
    129125      ! Local variables  
    130126      REAL(wp), DIMENSION(jpi,jpj) :: z_fvel              ! friction velocity      
     
    136132       
    137133      INTEGER :: ji,jj 
     134      INTEGER, INTENT(IN) :: kt                           ! time step 
    138135 
    139136      ! Set optional arguments to their defaults 
     
    158155         zla(:,:) = pla(:,:) 
    159156      ENDIF 
    160       IF ( .NOT. PRESENT(ld_calcfrac) ) THEN 
    161          ll_calcfrac = .FALSE. 
    162       ELSE 
    163          ll_calcfrac = ld_calcfrac 
    164       ENDIF      
    165157       
    166158      ! If not done already, calculate the solar fraction 
    167       IF (ll_calcfrac ) THEN 
     159      IF ( kt==nit000 ) THEN 
    168160         DO jj = 1,jpj 
    169161            DO ji = 1, jpi 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6008 r6010  
    8080   USE lib_mpp         ! distributed memory computing 
    8181   USE diurnal_bulk    ! diurnal bulk SST  
     82   USE stp_diu         ! diurnal bulk SST timestepping if run offline 
    8283#if defined key_iomput 
    8384   USE xios            ! xIOserver 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6008 r6010  
    234234      ! cool skin 
    235235      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
    236       IF ( ln_diurnal ) THEN  
    237          IF ( .NOT. ln_blk_core ) THEN 
    238             CALL ctl_stop("step.f90: diurnal flux processing not implemented"//& 
    239             &             " for direct forcing") 
    240          ENDIF 
    241          CALL diurnal_sst_coolskin_step( &  
    242                     qns, taum, rhop(:,:,1), rdt) 
    243       ENDIF 
     236      IF ( ln_diurnal )  CALL stp_diurnal( kstp ) 
    244237       
    245238      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    256249      ! 
    257250      IF( ln_crs     )   CALL crs_fld       ( kstp )  ! ocean model: online field coarsening & output 
    258        
    259       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    260       ! diurnal warm layer 
    261       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    262       IF ( ln_diurnal ) THEN  
    263          IF( kstp == nit000 )THEN  
    264             CALL diurnal_sst_takaya_step( &  
    265             &    qsr, qns, taum, rhop(:,:,1), & 
    266             &    rdt, ld_calcfrac = .TRUE.)  
    267          ELSE  
    268             CALL diurnal_sst_takaya_step( &  
    269             &    qsr, qns, taum, rhop(:,:,1), rdt )  
    270          ENDIF 
    271       ENDIF      
    272        
    273251       
    274252#if defined key_top 
     
    382360   END SUBROUTINE stp 
    383361    
    384    SUBROUTINE stp_diurnal( kstp )  
    385       INTEGER, INTENT(in) ::   kstp   ! ocean time-step index  
    386       !!----------------------------------------------------------------------  
    387       !!                     ***  ROUTINE stp  ***  
    388       !!                        
    389       !! ** Purpose : - Time stepping of diurnal SST model only  
    390       !!    
    391       !! ** Method  : -1- Update forcings and data    
    392       !!              -2- Update ocean physics    
    393       !!              -3- Compute the t and s trends    
    394       !!              -4- Update t and s    
    395       !!              -5- Compute the momentum trends  
    396       !!              -6- Update the horizontal velocity  
    397       !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)  
    398       !!              -8- Outputs and diagnostics  
    399       !!----------------------------------------------------------------------  
    400       INTEGER ::   jk       ! dummy loop indices 
    401       INTEGER ::   indic    ! error indicator if < 0  
    402       REAL(wp), DIMENSION(jpi,jpj) :: z_fvel_bkginc, z_hflux_bkginc      
    403       !! ---------------------------------------------------------------------  
    404   
    405       indic = 1                                 ! reset to no error condition  
    406   
    407       IF( kstp /= nit000 )   CALL day( kstp )   ! Calendar (day was already called at nit000 in day_init)  
    408   
    409       CALL iom_setkt( kstp - nit000 + 1, cxios_context )   ! tell iom we are at time step kstp 
    410       IF( ln_crs ) THEN 
    411          CALL iom_setkt( kstp - nit000 + 1, TRIM(cxios_context)//"_crs" ) ! tell iom we are at time step kstp 
    412       ENDIF 
    413         
    414       CALL sbc    ( kstp )                      ! Sea Boundary Conditions  
    415       
    416       ! Cool skin 
    417       IF ( .NOT.ln_diurnal ) CALL ctl_stop(  "stp_diurnal: ln_diurnal not set"  ) 
    418           
    419       IF ( .NOT. ln_blk_core ) THEN 
    420          CALL ctl_stop("step.f90: diurnal flux processing not implemented"//& 
    421          &             " for direct forcing")  
    422       ENDIF 
    423  
    424       CALL diurnal_sst_coolskin_step( qns, taum, rhop(:,:,1), rdt) 
    425  
    426       CALL dia_wri( kstp )                            ! ocean model: outputs  
    427         
    428       ! Diurnal warm layer model        
    429             
    430       IF( kstp == nit000 )THEN  
    431          CALL diurnal_sst_takaya_step( &  
    432          &    qsr, qns, taum, rhop(:,:,1), & 
    433          &    rdt, ld_calcfrac = .TRUE.)  
    434       ELSE  
    435          CALL diurnal_sst_takaya_step( &  
    436          &    qsr, qns, taum, rhop(:,:,1), rdt )  
    437       ENDIF 
    438  
    439       IF( ln_diaobs  )         CALL dia_obs( kstp )         ! obs-minus-model (assimilation) diagnostics (call after dynamics update) 
    440       
    441       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>  
    442       ! Control and restarts  
    443       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<  
    444       IF( kstp == nit000   )   CALL iom_close( numror )     ! close input  ocean restart file  
    445       IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file 
    446       
    447       IF( nn_timing == 1 .AND.  kstp == nit000  )   CALL timing_reset  
    448         
    449    END SUBROUTINE stp_diurnal   
    450     
    451    !!====================================================================== 
    452362END MODULE step 
Note: See TracChangeset for help on using the changeset viewer.