Ignore:
Timestamp:
Feb 27, 2020 11:23:01 PM (4 years ago)
Author:
gronemeier
Message:

diagnostic_output_quantities: added wspeed and wdir output; bugfix: set fill_value in case of masked output

File:
1 edited

Legend:

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

    r4360 r4431  
    2525! -----------------
    2626! $Id$
     27! added u_center_av, v_center_av, wspeed_av
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Change automatic arrays to allocatable ones in rrd_local, in order to avoid
    28 ! memory problems due to too small stack size for large jobs with intel 
     31! memory problems due to too small stack size for large jobs with intel
    2932! compiler. (J.Resler)
    30 ! 
     33!
    3134! 4331 2019-12-10 18:25:02Z suehring
    3235! Enable restart data for 2-m potential temperature output
    33 ! 
     36!
    3437! 4301 2019-11-22 12:09:09Z oliver.maas
    3538! removed recycling_yshift
    36 ! 
     39!
    3740! 4227 2019-09-10 18:04:34Z gronemeier
    3841! implement new palm_date_time_mod and increased binary version
    39 ! 
     42!
    4043! 4146 2019-08-07 07:47:36Z gronemeier
    4144! Corrected "Former revisions" section
    42 ! 
     45!
    4346! 4131 2019-08-02 11:06:18Z monakurppa
    4447! Allocate hom and hom_sum to allow profile output for salsa variables.
    45 ! 
     48!
    4649! 4101 2019-07-17 15:14:26Z gronemeier
    4750! remove old_dt
    48 ! 
     51!
    4952! 4039 2019-06-18 10:32:41Z suehring
    5053! input of uu_av, vv_av, ww_av added
    51 ! 
     54!
    5255! 4017 2019-06-06 12:16:46Z schwenkel
    5356! bugfix for r3998, allocation of 3d temporary arrays of various dimensions revised
    54 ! 
     57!
    5558! 3998 2019-05-23 13:38:11Z suehring
    5659! Formatting adjustment
    57 ! 
     60!
    5861! 3994 2019-05-22 18:08:09Z suehring
    5962! output of turbulence intensity added
    60 ! 
     63!
    6164! 3988 2019-05-22 11:32:37Z kanani
    6265! + time_virtual_measurement (to enable steering of output interval)
    63 ! 
     66!
    6467! 3936 2019-04-26 15:38:02Z kanani
    6568! Enable time-averaged output of theta_2m* with restarts
    66 ! 
     69!
    6770! 3767 2019-02-27 08:18:02Z raasch
    6871! unused variables removed from rrd-subroutines parameter list
    69 ! 
     72!
    7073! 3766 2019-02-26 16:23:41Z raasch
    7174! first argument removed from module_interface_rrd_*
    72 ! 
     75!
    7376! 3668 2019-01-14 12:49:24Z maronga
    7477! Removed most_method and increased binary version
    75 ! 
     78!
    7679! 3655 2019-01-07 16:51:22Z knoop
    7780! Implementation of the PALM module interface
    78 ! 
     81!
    7982! 2894 2018-03-15 09:17:58Z Giersch
    8083! Initial revision
    81 ! 
     84!
    8285!
    8386! Description:
     
    111114        ONLY:  pt_2m_av,                                                       &
    112115               ti_av,                                                          &
     116               u_center_av,                                                    &
    113117               uu_av,                                                          &
    114118               uv_10m_av,                                                      &
     119               v_center_av,                                                    &
    115120               vv_av,                                                          &
     121               wspeed_av,                                                      &
    116122               ww_av
    117123
     
    191197! Description:
    192198! ------------
    193 !> Reads values of global control variables from restart-file (binary format) 
     199!> Reads values of global control variables from restart-file (binary format)
    194200!> created by PE0 of the previous run
    195201!------------------------------------------------------------------------------!
     
    199205       CHARACTER (LEN=10) ::  binary_version_global, version_on_file
    200206
    201        LOGICAL ::  found 
     207       LOGICAL ::  found
    202208
    203209
     
    773779                   WRITE( message_string, * ) 'unknown variable named "',      &
    774780                                           restart_string(1:length),           &
    775                                           '" found in global data from ',      & 
     781                                          '" found in global data from ',      &
    776782                                          'prior run on PE ', myid
    777783                CALL message( 'rrd_global', 'PA0302', 1, 2, 0, 6, 0 )
    778  
     784
    779785                ENDIF
    780786
     
    783789!--       Read next string
    784790          READ ( 13 )  length
    785           READ ( 13 )  restart_string(1:length)   
     791          READ ( 13 )  restart_string(1:length)
    786792
    787793       ENDDO
    788  
     794
    789795
    790796    CALL close_file( 13 )
    791797
    792    
     798
    793799    END SUBROUTINE rrd_global
    794800
     
    10131019! Description:
    10141020! ------------
    1015 !> Reads processor specific data of variables and arrays from restart file 
     1021!> Reads processor specific data of variables and arrays from restart file
    10161022!> (binary format).
    10171023!------------------------------------------------------------------------------!
     
    10761082    CALL cpu_log( log_point_s(14), 'rrd_local', 'start' )
    10771083!
    1078 !-- Allocate temporary buffer arrays. In previous versions, there were 
     1084!-- Allocate temporary buffer arrays. In previous versions, there were
    10791085!-- declared as automated arrays, causing memory problems when these
    10801086!-- were allocate on stack.
     
    11091115!--    matches another time(s) in the current subdomain by shifting it
    11101116!--    for nx_on_file+1, ny_on_file+1 respectively
    1111    
     1117
    11121118       shift_y = 0
    11131119       j       = 0
    11141120       DO WHILE (  nyspr+shift_y <= nyn-offset_y )
    1115          
    1116           IF ( nynpr+shift_y >= nys-offset_y ) THEN 
     1121
     1122          IF ( nynpr+shift_y >= nys-offset_y ) THEN
    11171123
    11181124             shift_x = 0
    11191125             DO WHILE ( nxlpr+shift_x <= nxr-offset_x )
    1120                
     1126
    11211127                IF ( nxrpr+shift_x >= nxl-offset_x ) THEN
    11221128                   j = j +1
     
    11331139                      file_list(files_to_be_opened) = i-1
    11341140                   ENDIF
    1135                      
     1141
    11361142                   offset_xa(files_to_be_opened,j) = offset_x + shift_x
    11371143                   offset_ya(files_to_be_opened,j) = offset_y + shift_y
     
    11471153                shift_x = shift_x + ( nx_on_file + 1 )
    11481154             ENDDO
    1149        
     1155
    11501156          ENDIF
    1151              
    1152           shift_y = shift_y + ( ny_on_file + 1 )             
     1157
     1158          shift_y = shift_y + ( ny_on_file + 1 )
    11531159       ENDDO
    1154          
     1160
    11551161       IF ( j > 0 )  overlap_count(files_to_be_opened) = j
    1156          
     1162
    11571163    ENDDO
    1158    
     1164
    11591165!
    11601166!-- Save the id-string of the current process, since myid_char may now be used
     
    11721178!-- Read data from all restart files determined above
    11731179    DO  i = 1, files_to_be_opened
    1174  
     1180
    11751181       j = file_list(i)
    11761182!
     
    12311237                                     '&= ', hor_index_bounds_previous_run(3,j),                    &
    12321238                                     '&from the index bound information array'
    1233           CALL message( 'rrd_local', 'PA0289', 2, 2, -1, 6, 1 ) 
     1239          CALL message( 'rrd_local', 'PA0289', 2, 2, -1, 6, 1 )
    12341240       ENDIF
    12351241
     
    12401246                                     '&= ', hor_index_bounds_previous_run(4,j),                    &
    12411247                                     '&from the index bound information array'
    1242           CALL message( 'rrd_local', 'PA0290', 2, 2, -1, 6, 1 ) 
     1248          CALL message( 'rrd_local', 'PA0290', 2, 2, -1, 6, 1 )
    12431249       ENDIF
    12441250
     
    12481254                                     '&nzb on file = ', nzb_on_file,                               &
    12491255                                     '&nzb         = ', nzb
    1250           CALL message( 'rrd_local', 'PA0291', 1, 2, 0, 6, 0 ) 
     1256          CALL message( 'rrd_local', 'PA0291', 1, 2, 0, 6, 0 )
    12511257       ENDIF
    12521258
     
    12561262                                     '&nzt on file = ', nzt_on_file,                               &
    12571263                                     '&nzt         = ', nzt
    1258           CALL message( 'rrd_local', 'PA0292', 1, 2, 0, 6, 0 ) 
     1264          CALL message( 'rrd_local', 'PA0292', 1, 2, 0, 6, 0 )
    12591265       ENDIF
    12601266
     
    12671273!
    12681274!--    Read arrays
    1269 !--    ATTENTION: If the following read commands have been altered, the 
    1270 !--    ---------- version number of the variable binary_version_local must 
    1271 !--               be altered, too. Furthermore, the output list of arrays in 
    1272 !--               wrd_write_local must also be altered 
     1275!--    ATTENTION: If the following read commands have been altered, the
     1276!--    ---------- version number of the variable binary_version_local must
     1277!--               be altered, too. Furthermore, the output list of arrays in
     1278!--               wrd_write_local must also be altered
    12731279!--               accordingly.
    12741280       READ ( 13 )  length
    12751281       READ ( 13 )  restart_string(1:length)
    1276        
     1282
    12771283
    12781284!
     
    12851291
    12861292             found = .FALSE.
    1287              
     1293
    12881294!
    12891295!--          Get the index range of the subdomain on file which overlap with
     
    13171323                   IF ( .NOT. ALLOCATED( e_av ) )  THEN
    13181324                      ALLOCATE( e_av(nzb:nzt+1,nys-nbgp:nyn+nbgp,                                  &
    1319                                      nxl-nbgp:nxr+nbgp) )   
     1325                                     nxl-nbgp:nxr+nbgp) )
    13201326                   ENDIF
    13211327                   IF ( k == 1 )  READ ( 13 )  tmp_3d
     
    14281434                   IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
    14291435                      ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
    1430                    ENDIF 
     1436                   ENDIF
    14311437                   IF ( k == 1 )  READ ( 13 )  tmp_2d
    14321438                   qsws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                             &
     
    14881494                   shf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
    14891495                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1490                    
     1496
    14911497                CASE ( 'ssws_av' )
    14921498                   IF ( .NOT. ALLOCATED( ssws_av ) )  THEN
    14931499                      ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
    1494                    ENDIF 
     1500                   ENDIF
    14951501                   IF ( k == 1 )  READ ( 13 )  tmp_2d
    14961502                   ssws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                             &
     
    15361542                   u_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
    15371543                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1538                      
     1544
     1545                CASE ( 'u_center_av' )
     1546                   IF ( .NOT. ALLOCATED( u_center_av ) )  THEN
     1547                      ALLOCATE( u_center_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
     1548                   ENDIF
     1549                   IF ( k == 1 )  THEN
     1550                      ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
     1551                                                    nxl_on_file:nxr_on_file) )
     1552                      READ ( 13 )  tmp_3d_non_standard
     1553                   ENDIF
     1554                   u_center_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
     1555
    15391556                CASE ( 'uu_av' )
    15401557                   IF ( .NOT. ALLOCATED( uu_av ) )  THEN
     
    16161633                   v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
    16171634                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1618                      
     1635
     1636                CASE ( 'v_center_av' )
     1637                   IF ( .NOT. ALLOCATED( v_center_av ) )  THEN
     1638                      ALLOCATE( v_center_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
     1639                   ENDIF
     1640                   IF ( k == 1 )  THEN
     1641                      ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
     1642                                                    nxl_on_file:nxr_on_file) )
     1643                      READ ( 13 )  tmp_3d_non_standard
     1644                   ENDIF
     1645                   v_center_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
     1646
    16191647                CASE ( 'vv_av' )
    16201648                   IF ( .NOT. ALLOCATED( vv_av ) )  THEN
     
    16931721                   w_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
    16941722                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1695                      
     1723
    16961724                CASE ( 'ww_av' )
    16971725                   IF ( .NOT. ALLOCATED( ww_av ) )  THEN
     
    17441772                      w_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
    17451773                   ENDIF
     1774
     1775                CASE ( 'wspeed_av' )
     1776                   IF ( .NOT. ALLOCATED( wspeed_av ) )  THEN
     1777                      ALLOCATE( wspeed_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
     1778                   ENDIF
     1779                   IF ( k == 1 )  THEN
     1780                      ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
     1781                                                    nxl_on_file:nxr_on_file) )
     1782                      READ ( 13 )  tmp_3d_non_standard
     1783                   ENDIF
     1784                   wspeed_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
    17461785
    17471786                CASE ( 'z0_av' )
     
    17911830                                                'from prior run on PE ', myid
    17921831                      CALL message( 'rrd_local', 'PA0302', 1, 2, 0, 6, 0 )
    1793  
     1832
    17941833                   ENDIF
    17951834
    17961835             END SELECT
    17971836
    1798           ENDDO ! overlaploop 
     1837          ENDDO ! overlaploop
    17991838
    18001839!
Note: See TracChangeset for help on using the changeset viewer.