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

Changeset 6005


Ignore:
Timestamp:
2015-12-04T17:22:59+01:00 (8 years ago)
Author:
timgraham
Message:

Merged diurnal sst branch

Location:
branches/2015/dev_MetOffice_merge_2015
Files:
10 edited
3 copied

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_MetOffice_merge_2015/DOC/NEMO_book.tex

    r5405 r6005  
    302302\include{./TexFiles/Chapters/Chap_STO}          % Stochastic param. 
    303303 
     304\include{./TexFiles/Chapters/Chap_DIU}          % Diurnal SST models. 
     305 
    304306\include{./TexFiles/Chapters/Chap_MISC}         % Miscellaneous topics 
    305307 
  • branches/2015/dev_MetOffice_merge_2015/DOC/TexFiles/Biblio/Biblio.bib

    r5120 r6005  
    149149  volume = {36}, 
    150150  pages = {1502--1522} 
     151} 
     152 
     153@ARTICLE{Artale_al_JGR02, 
     154  author={V. Artale and D. Iudicone and R. Santoleri and V. Rupolo and S. Marullo 
     155          and F. {D'O}rtenzio}, 
     156  title={{Role of surface fluxes in ocean general circulation models using satellite 
     157          sea surface temperature: Validation of and sensitivity to the forcing 
     158          frequency of the Mediterranean thermohaline circulation}}, 
     159  journal=JGR, 
     160  year={2002}, 
     161  volume={107}, 
     162  pages={1978-2012}, 
     163  doi = {10.1029/2000JC000452}, 
    151164} 
    152165 
     
    10611074} 
    10621075 
     1076@Article{Gentemann_al_JGR09, 
     1077  author =   {C. L. Gentemann  and P. J. Minnett and B. Ward}, 
     1078  title =        {Profiles of Ocean Surface heating ({POSH}): A new model  
     1079                  of upper ocean diurnal warming}, 
     1080  journal =     JGR, 
     1081  year =     {2009}, 
     1082  Volume =   {114}, 
     1083  Pages =    {C07017}, 
     1084  doi =   {10.1029/2008JC004825}, 
     1085  OPTannote =   {} 
     1086} 
     1087 
    10631088@ARTICLE{Gerdes1993a, 
    10641089  author = {R. Gerdes}, 
     
    25162541} 
    25172542 
     2543@ARTICLE{Saunders_JAS82, 
     2544  author={P. M. Saunders}, 
     2545  title={{The Temperature at the Ocean-air Interface}}, 
     2546  journal=JAS, 
     2547  year={1967}, 
     2548  volume={24}, 
     2549  pages={269-273}, 
     2550  doi = {10.1175/1520-0469(1967)024<0269:TTATOA>2.0.CO;2}, 
     2551} 
     2552 
    25182553@BOOK{Shchepetkin_McWilliams_Bk08, 
    25192554  author = {A. F. Shchepetkin and J. C. McWilliams}, 
     
    26882723  volume = {359}, 
    26892724  pages = {123--129} 
     2725} 
     2726 
     2727@ARTICLE{Takaya_al_JGR10, 
     2728  author =   {Y. Takaya and J-R. Bidlot and A. C. M. Beljaars and  
     2729                  P. A. E. M. Janssen}, 
     2730  title =        {Refinements to a prognostic scheme of sea surface skin temperature}, 
     2731  journal =     JGR, 
     2732  year =     {2010}, 
     2733  Volume =   {115}, 
     2734  Pages =    {C06009}, 
     2735  doi =   {10.1029/2009JC005985}, 
    26902736} 
    26912737 
     
    27912837  volume = {27},  number = {4}, 
    27922838  pages = {567--580} 
     2839} 
     2840 
     2841@ARTICLE{Tu_Tsuang_GRL05, 
     2842  title={{Cool-skin simulation by a one-column ocean model}}, 
     2843  author={{C-Y}. Tu  and {B-J}. Tsuang}, 
     2844  journal=GRL, 
     2845  year={2005}, 
     2846  volume={32}, 
     2847  pages={L22602}, 
     2848  doi = {10.1029/2005GL024252}, 
    27932849} 
    27942850 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/CONFIG/SHARED/field_def.xml

    r5930 r6005  
    4040         <field id="sstgrad2"     long_name="square of module of sst gradient"                                                        unit="degC2/m2" /> 
    4141         <field id="sbt"          long_name="sea bottom temperature"                                                                  unit="degC"     /> 
    42      
     42         <field id="sst_wl"       long_name="Delta SST of warm layer"                                                                 unit="degC"     /> 
     43         <field id="sst_cs"       long_name="Delta SST of cool skin"                                                                  unit="degC"     /> 
     44    <field id="temp_3m"      long_name="temperature at 3m"                                                                       unit="degC"     /> 
     45          
    4346         <field id="sss"          long_name="sea surface salinity"             standard_name="sea_surface_salinity"   unit="1e-3" /> 
    4447         <field id="sss2"         long_name="square of sea surface salinity"                                          unit="1e-6"  > sss * sss </field > 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/CONFIG/SHARED/namelist_ref

    r5998 r6005  
    12411241   rn_htrmax         =  200.0   ! max. depth of transition range 
    12421242/ 
     1243!----------------------------------------------------------------------- 
     1244&namdiu !   Cool skin and warm layer modesl 
     1245!----------------------------------------------------------------------- 
     1246   ln_diurnal = .false. 
     1247   ln_diurnal_only = .false. 
     1248/ 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r5930 r6005  
    5353   USE lib_mpp         ! MPP library 
    5454   USE timing          ! preformance summary 
     55   USE diurnal_bulk    ! diurnal warm layer 
     56   USE cool_skin       ! Cool skin 
    5557   USE wrk_nemo        ! working array 
    5658 
     
    143145      ENDIF 
    144146 
     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       
    145154      IF( .NOT.lk_vvl ) THEN 
    146155         CALL iom_put( "e3t" , fse3t_n(:,:,:) ) 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r5836 r6005  
    2727   USE in_out_manager  ! I/O manager 
    2828   USE iom             ! I/O module 
    29  
     29   USE diurnal_bulk 
     30    
    3031   IMPLICIT NONE 
    3132   PRIVATE 
     
    128129                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step 
    129130                     CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step 
    130  
     131      IF ( .NOT. ln_diurnal_only ) THEN 
    131132                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields 
    132133                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        ) 
     
    141142                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      ) 
    142143                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      ) 
     144      ENDIF 
     145       
     146      IF (ln_diurnal) CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst    )   
     147       
    143148      IF( kt == nitrst ) THEN 
    144149         CALL iom_close( numrow )     ! close the restart file (only at last time step) 
     
    218223         IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    219224      ENDIF 
    220       !  
     225        
     226       
     227      ! Diurnal DSST  
     228      IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst  )  
     229      IF ( ln_diurnal_only ) THEN  
     230         IF(lwp) WRITE( numout, * ) & 
     231         &   "rst_read:- ln_diurnal_only set, setting rhop=rau0"  
     232         rhop = rau0 
     233         CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,1,jp_tem) )  
     234         RETURN  
     235      ENDIF   
     236       
    221237      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN 
    222238         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r5836 r6005  
    5454   USE bdy_par          ! Require lk_bdy 
    5555 
     56   USE diurnal_bulk, ONLY: & 
     57      & ln_diurnal_only  
     58 
    5659   IMPLICIT NONE 
    5760   PRIVATE 
     
    383386      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    384387 
    385       IF( nn_closea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain  
    386       !                                                           ! (update freshwater fluxes) 
     388      ! treatment of closed sea in the model domain  
     389      ! (update freshwater fluxes) 
     390      ! Should not be ran if ln_diurnal_only 
     391      IF( .NOT.(ln_diurnal_only) .AND. (nn_closea == 1) )   CALL sbc_clo( kt )    
     392 
    387393!RBbug do not understand why see ticket 667 
    388394!clem: it looks like it is necessary for the north fold (in certain circumstances). Don't know why. 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r5998 r6005  
    7979#endif 
    8080   USE lib_mpp         ! distributed memory computing 
     81   USE diurnal_bulk    ! diurnal bulk SST  
    8182#if defined key_iomput 
    8283   USE xios            ! xIOserver 
     
    172173            CALL stp                         ! AGRIF: time stepping 
    173174#else 
    174             CALL stp( istp )                 ! standard time stepping 
     175            IF ( .NOT. ln_diurnal_only ) THEN  
     176               CALL stp( istp )                 ! standard time stepping  
     177            ELSE  
     178               CALL stp_diurnal( istp )        ! time step only the diurnal SST  
     179            ENDIF  
    175180#endif 
    176181            istp = istp + 1 
     
    399404      IF( ln_nnogather )    CALL nemo_northcomms! northfold neighbour lists (must be done after the masks are defined) 
    400405      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
     406       
     407      CALL diurnal_sst_bulk_init            ! diurnal sst 
     408      IF ( ln_diurnal ) CALL diurnal_sst_coolskin_init   ! cool skin    
     409       
     410      ! IF ln_diurnal_only, then we only want a subset of the initialisation routines 
     411      IF ( ln_diurnal_only ) THEN 
     412         CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
     413         CALL     sbc_init   ! Forcings : surface module 
     414         CALL tra_qsr_init   ! penetrative solar radiation qsr 
     415         IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
     416            CALL dia_obs_init            ! Initialize observational data 
     417            CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
     418         ENDIF      
     419         !                                     ! Assimilation increments 
     420         IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
     421                  
     422         IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
     423         RETURN 
     424      ENDIF 
     425       
    401426                            CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    402427 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/step.F90

    r5998 r6005  
    4040   PRIVATE 
    4141 
    42    PUBLIC   stp   ! called by nemogcm.F90 
     42   PUBLIC   stp, stp_diurnal   ! called by nemogcm.F90 
    4343 
    4444   !! * Substitutions 
     
    232232 
    233233      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    234       ! diagnostics and outputs              
     234      ! cool skin 
     235      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
     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 
     244       
     245      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     246      ! diagnostics and outputs             (ua, va, tsa used as workspace) 
    235247      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    236248      IF( lk_floats  )   CALL flo_stp( kstp )         ! drifting Floats 
     
    244256      ! 
    245257      IF( ln_crs     )   CALL crs_fld       ( kstp )  ! ocean model: online field coarsening & output 
    246  
     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       
     273       
    247274#if defined key_top 
    248275      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    354381      ! 
    355382   END SUBROUTINE stp 
    356  
     383    
     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( lk_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    
    357451   !!====================================================================== 
    358452END MODULE step 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/step_oce.F90

    r5960 r6005  
    7272   USE zdfmxl           ! Mixed-layer depth                (zdf_mxl routine) 
    7373 
     74   USE diurnal_bulk    ! diurnal SST bulk routines  (diurnal_sst_takaya routine)  
     75   USE cool_skin       ! diurnal cool skin correction (diurnal_sst_coolskin routine)    
     76   USE sbc_oce         ! surface fluxes   
     77    
    7478   USE zpshde           ! partial step: hor. derivative     (zps_hde routine) 
    7579 
Note: See TracChangeset for help on using the changeset viewer.