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 8561 for branches/UKMO/AMM15_v3_6_STABLE_package/NEMOGCM/NEMO/OPA_SRC/DIA/dia25h.F90 – NEMO

Ignore:
Timestamp:
2017-09-22T17:45:41+02:00 (7 years ago)
Author:
jgraham
Message:

Updates for operational diagnostics:
25h mean diagnostics - bottom temperature (and insitu temp)
Operational foam diagnostics - diaopfoam and DIU routines added.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/AMM15_v3_6_STABLE_package/NEMOGCM/NEMO/OPA_SRC/DIA/dia25h.F90

    r8059 r8561  
    2020   USE zdf_oce, ONLY: en 
    2121#endif 
     22   USE diatmb 
    2223 
    2324   IMPLICIT NONE 
     
    3031  !! * variables for calculating 25-hourly means 
    3132   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   tn_25h  , sn_25h, rinsitu_t_25h   
    32    REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:)   ::   sshn_25h  
     33   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:)   ::   sshn_25h, insitu_bot_25h, temp_bot_25h  
    3334   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   un_25h  , vn_25h  , wn_25h 
    3435   REAL(wp),SAVE, ALLOCATABLE,   DIMENSION(:,:,:) ::   avt_25h , avm_25h 
     
    6364      INTEGER ::   ios                 ! Local integer output status for namelist read 
    6465      INTEGER ::   ierror              ! Local integer for memory allocation 
     66      REAL(wp), DIMENSION(jpi,jpj,3)   ::   zwtmb                                 ! temporary workspace 
    6567      ! 
    6668      NAMELIST/nam_dia25h/ ln_dia25h 
     
    99101         CALL ctl_stop( 'dia_25h: unable to allocate rinsitu_t_25h' )   ;   RETURN 
    100102      ENDIF 
     103      ALLOCATE( insitu_bot_25h(jpi,jpj), STAT=ierror ) 
     104      IF( ierror > 0 ) THEN 
     105         CALL ctl_stop( 'dia_25h: unable to allocate insitu_bot_25h' )   ;   RETURN 
     106      ENDIF       
     107      ALLOCATE( temp_bot_25h(jpi,jpj), STAT=ierror ) 
     108      IF( ierror > 0 ) THEN 
     109         CALL ctl_stop( 'dia_25h: unable to allocate temp_bot_25h' )   ;   RETURN 
     110      ENDIF                            
    101111      ALLOCATE( un_25h(jpi,jpj,jpk), STAT=ierror ) 
    102112      IF( ierror > 0 ) THEN 
     
    143153      CALL theta2t 
    144154      rinsitu_t_25h(:,:,:) = rinsitu_t(:,:,:) 
     155      CALL dia_calctmb( rinsitu_t(:,:,:),zwtmb ) 
     156      insitu_bot_25h(:,:) = zwtmb(:,:,3) 
     157      CALL dia_calctmb( tn_25h(:,:,:),zwtmb ) 
     158      temp_bot_25h(:,:) = zwtmb(:,:,3) 
    145159      sshn_25h(:,:) = sshb(:,:) 
    146160      un_25h(:,:,:) = ub(:,:,:) 
     
    237251         CALL theta2t 
    238252         rinsitu_t_25h(:,:,:)  = rinsitu_t_25h(:,:,:) + rinsitu_t(:,:,:) 
     253         CALL dia_calctmb( rinsitu_t(:,:,:),zwtmb ) 
     254         insitu_bot_25h(:,:)  = insitu_bot_25h(:,:) + zwtmb(:,:,3) 
     255         zw3d(:,:,:)          = tsn(:,:,:,jp_tem) 
     256         CALL dia_calctmb( zw3d,zwtmb ) 
     257         temp_bot_25h(:,:)    = temp_bot_25h(:,:) + zwtmb(:,:,3) 
    239258         sshn_25h(:,:)        = sshn_25h(:,:) + sshn (:,:) 
    240259         un_25h(:,:,:)        = un_25h(:,:,:) + un(:,:,:) 
     
    268287            sn_25h(:,:,:)        = sn_25h(:,:,:) / 25.0_wp 
    269288            rinsitu_t_25h(:,:,:)  = rinsitu_t_25h(:,:,:) / 25.0_wp 
     289            insitu_bot_25h(:,:)  = insitu_bot_25h(:,:) / 25.0_wp  
     290            temp_bot_25h(:,:)    = temp_bot_25h(:,:) /25.0_wp 
    270291            sshn_25h(:,:)        = sshn_25h(:,:) / 25.0_wp 
    271292            un_25h(:,:,:)        = un_25h(:,:,:) / 25.0_wp 
     
    289310            zw3d(:,:,:) = rinsitu_t_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    290311            CALL iom_put("tempis25h", zw3d)   ! in-situ temperature 
     312            zw2d(:,:) = insitu_bot_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1)) 
     313            CALL iom_put("tempisbot25h", zw2d) ! bottom in-situ temperature 
     314            zw2d(:,:) = temp_bot_25h(:,:)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1)) 
     315            CALL iom_put("temperbot25h",zw2d) ! bottom potential temperature 
    291316            zw3d(:,:,:) = sn_25h(:,:,:)*tmask(:,:,:) + zmdi*(1.0-tmask(:,:,:)) 
    292317            CALL iom_put( "salin25h", zw3d  )   ! salinity 
     
    321346            CALL theta2t 
    322347            rinsitu_t_25h(:,:,:) = rinsitu_t(:,:,:) 
     348            CALL dia_calctmb( rinsitu_t(:,:,:),zwtmb ) 
     349            insitu_bot_25h(:,:) = zwtmb(:,:,3) 
     350            CALL dia_calctmb( tn_25h(:,:,:),zwtmb) 
     351            temp_bot_25h(:,:) = zwtmb(:,:,3) 
    323352            sshn_25h(:,:) = sshn (:,:) 
    324353            un_25h(:,:,:) = un(:,:,:) 
Note: See TracChangeset for help on using the changeset viewer.