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 11831 for NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/DIA/diawri.F90 – NEMO

Ignore:
Timestamp:
2019-10-29T18:14:49+01:00 (4 years ago)
Author:
laurent
Message:

Update the branch to r11830 of the trunk!

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/DIA/diawri.F90

    r10425 r11831  
    210210      ENDIF 
    211211 
     212      IF( ln_zad_Aimp ) wn = wn + wi               ! Recombine explicit and implicit parts of vertical velocity for diagnostic output 
     213      ! 
    212214      CALL iom_put( "woce", wn )                   ! vertical velocity 
    213215      IF( iom_use('w_masstr') .OR. iom_use('w_masstr2') ) THEN   ! vertical mass transport & its square value 
     
    220222         IF( iom_use('w_masstr2') )   CALL iom_put( "w_masstr2", z3d(:,:,:) * z3d(:,:,:) ) 
    221223      ENDIF 
     224      ! 
     225      IF( ln_zad_Aimp ) wn = wn - wi               ! Remove implicit part of vertical velocity that was added for diagnostic output 
    222226 
    223227      CALL iom_put( "avt" , avt )                  ! T vert. eddy diff. coef. 
     
    426430      !!      define all the NETCDF files and fields 
    427431      !!      At each time step call histdef to compute the mean if ncessary 
    428       !!      Each nwrite time step, output the instantaneous or mean fields 
     432      !!      Each nn_write time step, output the instantaneous or mean fields 
    429433      !!---------------------------------------------------------------------- 
    430434      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     
    442446      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zw3d       ! 3D workspace 
    443447      !!---------------------------------------------------------------------- 
    444       !  
    445       IF( ln_timing )   CALL timing_start('dia_wri') 
    446448      ! 
    447449      IF( ninist == 1 ) THEN     !==  Output the initial state and forcings  ==! 
     
    450452      ENDIF 
    451453      ! 
     454      IF( nn_write == -1 )   RETURN   ! we will never do any output 
     455      !  
     456      IF( ln_timing )   CALL timing_start('dia_wri') 
     457      ! 
    452458      ! 0. Initialisation 
    453459      ! ----------------- 
     
    459465      clop = "x"         ! no use of the mask value (require less cpu time and otherwise the model crashes) 
    460466#if defined key_diainstant 
    461       zsto = nwrite * rdt 
     467      zsto = nn_write * rdt 
    462468      clop = "inst("//TRIM(clop)//")" 
    463469#else 
     
    465471      clop = "ave("//TRIM(clop)//")" 
    466472#endif 
    467       zout = nwrite * rdt 
     473      zout = nn_write * rdt 
    468474      zmax = ( nitend - nit000 + 1 ) * rdt 
    469475 
     
    496502         ! WRITE root name in date.file for use by postpro 
    497503         IF(lwp) THEN 
    498             CALL dia_nam( clhstnam, nwrite,' ' ) 
     504            CALL dia_nam( clhstnam, nn_write,' ' ) 
    499505            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    500506            WRITE(inum,*) clhstnam 
     
    504510         ! Define the T grid FILE ( nid_T ) 
    505511 
    506          CALL dia_nam( clhstnam, nwrite, 'grid_T' ) 
     512         CALL dia_nam( clhstnam, nn_write, 'grid_T' ) 
    507513         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    508514         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    540546         ! Define the U grid FILE ( nid_U ) 
    541547 
    542          CALL dia_nam( clhstnam, nwrite, 'grid_U' ) 
     548         CALL dia_nam( clhstnam, nn_write, 'grid_U' ) 
    543549         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    544550         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
     
    553559         ! Define the V grid FILE ( nid_V ) 
    554560 
    555          CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename 
     561         CALL dia_nam( clhstnam, nn_write, 'grid_V' )                   ! filename 
    556562         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    557563         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
     
    566572         ! Define the W grid FILE ( nid_W ) 
    567573 
    568          CALL dia_nam( clhstnam, nwrite, 'grid_W' )                   ! filename 
     574         CALL dia_nam( clhstnam, nn_write, 'grid_W' )                   ! filename 
    569575         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    570576         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    657663         ENDIF 
    658664 
    659          IF( .NOT. ln_cpl ) THEN 
     665         IF( ln_ssr ) THEN 
    660666            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    661667               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    665671               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    666672         ENDIF 
    667  
    668          IF( ln_cpl .AND. nn_ice <= 1 ) THEN 
    669             CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    670                &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    671             CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
    672                &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    673             CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
    674                &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    675          ENDIF 
    676           
     673        
    677674         clmx ="l_max(only(x))"    ! max index on a period 
    678675!         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX  
     
    750747      ! donne le nombre d'elements, et ndex la liste des indices a sortir 
    751748 
    752       IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN  
     749      IF( lwp .AND. MOD( itmod, nn_write ) == 0 ) THEN  
    753750         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step' 
    754751         WRITE(numout,*) '~~~~~~ ' 
     
    814811      ENDIF 
    815812 
    816       IF( .NOT. ln_cpl ) THEN 
     813      IF( ln_ssr ) THEN 
    817814         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    818815         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    819          IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    820          CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    821       ENDIF 
    822       IF( ln_cpl .AND. nn_ice <= 1 ) THEN 
    823          CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    824          CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    825          IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
     816         zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    826817         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    827818      ENDIF 
     
    842833      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress 
    843834 
    844       CALL histwrite( nid_W, "vovecrtz", it, wn             , ndim_T, ndex_T )    ! vert. current 
     835      IF( ln_zad_Aimp ) THEN 
     836         CALL histwrite( nid_W, "vovecrtz", it, wn + wi     , ndim_T, ndex_T )    ! vert. current 
     837      ELSE 
     838         CALL histwrite( nid_W, "vovecrtz", it, wn          , ndim_T, ndex_T )    ! vert. current 
     839      ENDIF 
    845840      CALL histwrite( nid_W, "votkeavt", it, avt            , ndim_T, ndex_T )    ! T vert. eddy diff. coef. 
    846841      CALL histwrite( nid_W, "votkeavm", it, avm            , ndim_T, ndex_T )    ! T vert. eddy visc. coef. 
     
    903898      CALL iom_rstput( 0, 0, inum, 'vozocrtx', un                )    ! now i-velocity 
    904899      CALL iom_rstput( 0, 0, inum, 'vomecrty', vn                )    ! now j-velocity 
    905       CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn                )    ! now k-velocity 
     900      IF( ln_zad_Aimp ) THEN 
     901         CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn + wi        )    ! now k-velocity 
     902      ELSE 
     903         CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn             )    ! now k-velocity 
     904      ENDIF 
    906905      IF( ALLOCATED(ahtu) ) THEN 
    907906         CALL iom_rstput( 0, 0, inum,  'ahtu', ahtu              )    ! aht at u-point 
Note: See TracChangeset for help on using the changeset viewer.