Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/data_output_3d.f90

    r1319 r1320  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    5965! Bugfix: missing calculation of ql_vp added
    6066!
    61 ! 790 2011-11-29 03:11:20Z raasch
    62 ! bugfix: calculation of 'pr' must depend on the particle weighting factor,
    63 ! nzt+1 replaced by nz_do3d for 'pr'
    64 !
    65 ! 771 2011-10-27 10:56:21Z heinze
    66 ! +lpt
    67 !
    68 ! 759 2011-09-15 13:58:31Z raasch
    69 ! Splitting of parallel I/O
    70 !
    71 ! 727 2011-04-20 20:05:25Z suehring
    72 ! Exchange ghost layers also for p_av.
    73 !
    74 ! 725 2011-04-11 09:37:01Z suehring
    75 ! Exchange ghost layers for p regardless of used pressure solver (except SOR).
    76 !
    77 ! 691 2011-03-04 08:45:30Z maronga
    78 ! Replaced simulated_time by time_since_reference_point
    79 !
    80 ! 673 2011-01-18 16:19:48Z suehring
    81 ! When using Multigrid or SOR solver an additional CALL exchange_horiz is
    82 ! is needed for pressure output.
    83 !
    84 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    85 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
    86 ! allocation of arrays.  Calls of exchange_horiz are modified.
    87 ! Skip-value skip_do_avs changed to a dynamic adaption of ghost points.
    88 !
    89 ! 646 2010-12-15 13:03:52Z raasch
    90 ! bugfix: missing define statements for netcdf added
    91 !
    92 ! 493 2010-03-01 08:30:24Z raasch
    93 ! netCDF4 support (parallel output)
    94 !
    95 ! 355 2009-07-17 01:03:01Z letzel
    96 ! simulated_time in netCDF output replaced by time_since_reference_point.
    97 ! Output of netCDF messages with aid of message handling routine.
    98 ! Output of messages replaced by message handling routine.
    99 ! Bugfix: to_be_resorted => s_av for time-averaged scalars
    100 !
    101 ! 96 2007-06-04 08:07:41Z raasch
    102 ! Output of density and salinity
    103 !
    104 ! 75 2007-03-22 09:54:05Z raasch
    105 ! 2nd+3rd argument removed from exchange horiz
    106 !
    107 ! RCS Log replace by Id keyword, revision history cleaned up
    108 !
    109 ! Revision 1.3  2006/06/02 15:18:59  raasch
    110 ! +argument "found", -argument grid in call of routine user_data_output_3d
    111 !
    112 ! Revision 1.2  2006/02/23 10:23:07  raasch
    113 ! Former subroutine plot_3d renamed data_output_3d, pl.. renamed do..,
    114 ! .._anz renamed .._n,
    115 ! output extended to (almost) all quantities, output of user-defined quantities
    116 !
    11767! Revision 1.1  1997/09/03 06:29:36  raasch
    11868! Initial revision
     
    12474!------------------------------------------------------------------------------!
    12575
    126     USE arrays_3d
     76    USE arrays_3d,                                                             &
     77        ONLY:  e, nr, p, pt, q, qc, ql, ql_c, ql_v, qr, rho, sa, tend, u, v,   &
     78               vpt, w
     79       
    12780    USE averaging
    128     USE cloud_parameters
    129     USE control_parameters
    130     USE cpulog
    131     USE indices
     81       
     82    USE cloud_parameters,                                                      &
     83        ONLY:  l_d_cp, prr, pt_d_t
     84       
     85    USE control_parameters,                                                    &
     86        ONLY:  avs_data_file,avs_output, cloud_physics, do3d, do3d_avs_n,      &
     87               do3d_compress, do3d_no, do3d_time_count, io_blocks, io_group,   &
     88               message_string, netcdf_output, netcdf_data_format, ntdim_3d,    &
     89               nz_do3d, plot_3d_precision, psolver, simulated_time,            &
     90               simulated_time_chr, skip_do_avs, time_since_reference_point
     91       
     92    USE cpulog,                                                                &
     93        ONLY:  log_point, cpu_log
     94       
     95    USE indices,                                                               &
     96        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzt,  &
     97               nzb
     98       
     99    USE kinds
     100   
    132101    USE netcdf_control
    133     USE particle_attributes
     102       
     103    USE particle_attributes,                                                   &
     104        ONLY:  particles, prt_count, prt_start_index
     105       
    134106    USE pegrid
    135     USE precision_kind
    136107
    137108    IMPLICIT NONE
    138109
    139     CHARACTER (LEN=9) ::  simulated_time_mod
    140 
    141     INTEGER           ::  av, i, if, j, k, n, pos, prec, psi
    142 
    143     LOGICAL           ::  found, resorted
    144 
    145     REAL              ::  mean_r, s_r3, s_r4
    146 
    147     REAL(spk), DIMENSION(:,:,:), ALLOCATABLE  ::  local_pf
    148 
    149     REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
     110    CHARACTER (LEN=9) ::  simulated_time_mod  !:
     111
     112    INTEGER(iwp) ::  av        !:
     113    INTEGER(iwp) ::  i         !:
     114    INTEGER(iwp) ::  if        !:
     115    INTEGER(iwp) ::  j         !:
     116    INTEGER(iwp) ::  k         !:
     117    INTEGER(iwp) ::  n         !:
     118    INTEGER(iwp) ::  pos       !:
     119    INTEGER(iwp) ::  prec      !:
     120    INTEGER(iwp) ::  psi       !:
     121
     122    LOGICAL      ::  found     !:
     123    LOGICAL      ::  resorted  !:
     124
     125    REAL(wp)     ::  mean_r    !:
     126    REAL(wp)     ::  s_r3      !:
     127    REAL(wp)     ::  s_r4      !:
     128
     129    REAL(sp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf  !:
     130
     131    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !:
    150132
    151133!
     
    202184    IF ( myid == 0 )  THEN
    203185       IF ( netcdf_output )  THEN
    204           nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av), &
    205                                   (/ time_since_reference_point /),  &
    206                                   start = (/ do3d_time_count(av) /), &
     186          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av),           &
     187                                  (/ time_since_reference_point /),            &
     188                                  start = (/ do3d_time_count(av) /),           &
    207189                                  count = (/ 1 /) )
    208190          CALL handle_netcdf_error( 'data_output_3d', 376 )
     
    288270                         s_r4 = 0.0
    289271                         DO  n = psi, psi+prt_count(k,j,i)-1
    290                          s_r3 = s_r3 + particles(n)%radius**3 * &
     272                         s_r3 = s_r3 + particles(n)%radius**3 *                &
    291273                                       particles(n)%weight_factor
    292                          s_r4 = s_r4 + particles(n)%radius**4 * &
     274                         s_r4 = s_r4 + particles(n)%radius**4 *                &
    293275                                       particles(n)%weight_factor
    294276                         ENDDO
     
    346328                      DO  j = nysg, nyng
    347329                         DO  k = nzb, nz_do3d
    348                             local_pf(i,j,k) = pt(k,j,i) + l_d_cp *    &
    349                                                           pt_d_t(k) * &
     330                            local_pf(i,j,k) = pt(k,j,i) + l_d_cp *             &
     331                                                          pt_d_t(k) *          &
    350332                                                          ql(k,j,i)
    351333                         ENDDO
     
    400382                         psi = prt_start_index(k,j,i)
    401383                         DO  n = psi, psi+prt_count(k,j,i)-1
    402                             tend(k,j,i) = tend(k,j,i) + &
    403                                           particles(n)%weight_factor / &
     384                            tend(k,j,i) = tend(k,j,i) +                        &
     385                                          particles(n)%weight_factor /         &
    404386                                          prt_count(k,j,i)
    405387                         ENDDO
     
    494476!
    495477!--          User defined quantity
    496              CALL user_data_output_3d( av, do3d(av,if), found, local_pf, &
     478             CALL user_data_output_3d( av, do3d(av,if), found, local_pf,       &
    497479                                       nz_do3d )
    498480             resorted = .TRUE.
    499481
    500482             IF ( .NOT. found )  THEN
    501                 message_string =  'no output available for: ' //   &
     483                message_string =  'no output available for: ' //               &
    502484                                  TRIM( do3d(av,if) )
    503485                CALL message( 'data_output_3d', 'PA0182', 0, 0, 0, 6, 0 )
     
    532514
    533515          IF ( av == 0 )  THEN
    534              WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
    535                                  skip_do_avs, TRIM( do3d(av,if) ), &
     516             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ),            &
     517                                 skip_do_avs, TRIM( do3d(av,if) ),             &
    536518                                 TRIM( simulated_time_mod )
    537519          ELSE
    538              WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ), &
    539                                  skip_do_avs, TRIM( do3d(av,if) ) // &
     520             WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ),            &
     521                                 skip_do_avs, TRIM( do3d(av,if) ) //           &
    540522                                 ' averaged', TRIM( simulated_time_mod )
    541523          ENDIF
     
    543525!--       Determine the Skip-value for the next array. Record end and start
    544526!--       require 4 byte each.
    545           skip_do_avs = skip_do_avs + ( ( ( nx+2*nbgp ) * ( ny+2*nbgp ) * &
     527          skip_do_avs = skip_do_avs + ( ( ( nx+2*nbgp ) * ( ny+2*nbgp ) *      &
    546528                                          ( nz_do3d+1 ) ) * 4 + 8 )
    547529       ENDIF
     
    553535!--       Compression, output of compression information on FLD-file and output
    554536!--       of compressed data.
    555           CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys, &
     537          CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys,   &
    556538                                 nzb, nz_do3d, prec, nbgp )
    557539       ELSE
     
    586568!--             boundaries of the total domain.
    587569                IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    588                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
    589                                      local_pf(nxl:nxr+1,nys:nyn,nzb:nz_do3d), &
    590                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
     570                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     571                                     local_pf(nxl:nxr+1,nys:nyn,nzb:nz_do3d),  &
     572                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    591573                      count = (/ nxr-nxl+2, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
    592574                ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    593                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
    594                                      local_pf(nxl:nxr,nys:nyn+1,nzb:nz_do3d), &
    595                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
     575                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     576                                     local_pf(nxl:nxr,nys:nyn+1,nzb:nz_do3d),  &
     577                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    596578                      count = (/ nxr-nxl+1, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
    597579                ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    598                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
    599                                    local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d), &
    600                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
     580                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     581                                   local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
     582                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    601583                      count = (/ nxr-nxl+2, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
    602584                ELSE
    603                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if), &
    604                                        local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d), &
    605                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /), &
     585                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     586                                       local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d),  &
     587                      start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    606588                      count = (/ nxr-nxl+1, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
    607589                ENDIF
     
    617599          IF ( netcdf_output )  THEN
    618600
    619              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),    &
    620                                local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
    621                                start = (/ 1, 1, 1, do3d_time_count(av) /), &
     601             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),        &
     602                               local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),      &
     603                               start = (/ 1, 1, 1, do3d_time_count(av) /),     &
    622604                               count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
    623605             CALL handle_netcdf_error( 'data_output_3d', 446 )
     
    641623!
    642624!-- Formats.
    643 3300 FORMAT ('variable ',I4,'  file=',A,'  filetype=unformatted  skip=',I12/ &
     6253300 FORMAT ('variable ',I4,'  file=',A,'  filetype=unformatted  skip=',I12/   &
    644626             'label = ',A,A)
    645627
Note: See TracChangeset for help on using the changeset viewer.