Changeset 3014 for palm/trunk


Ignore:
Timestamp:
May 9, 2018 8:42:38 AM (6 years ago)
Author:
maronga
Message:

series of bugfixes

Location:
palm/trunk/SOURCE
Files:
15 edited

Legend:

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

    r3004 r3014  
    2727! -----------------
    2828! $Id$
     29! Bugfix: nzb_do and nzt_do were not used for 3d data output
     30!
     31! 3004 2018-04-27 12:33:25Z Giersch
    2932! Comment concerning averaged data output added
    3033!
     
    11521155
    11531156
    1154    SUBROUTINE chem_data_output_3d( av, variable, found, local_pf, fill_value )
     1157   SUBROUTINE chem_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    11551158
    11561159
     
    11631166
    11641167      CHARACTER (LEN=*) ::  variable !<
     1168
     1169      INTEGER(iwp) ::  av    !<
     1170      INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
     1171      INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
     1172
    11651173      LOGICAL      ::  found !<
    1166       INTEGER(iwp) ::  av    !<
    11671174
    11681175      REAL(wp) ::  fill_value !<
    1169       REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf
     1176      REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf
    11701177
    11711178
     
    11891196                DO  i = nxl, nxr
    11901197                   DO  j = nys, nyn
    1191                       DO  k = nzb, nzt+1
     1198                      DO  k = nzb_do, nzt_do
    11921199                          local_pf(i,j,k) = MERGE(                             &
    11931200                                              chem_species(lsp)%conc(k,j,i),   &
     
    12011208                DO  i = nxl, nxr
    12021209                   DO  j = nys, nyn
    1203                       DO  k = nzb, nzt+1
     1210                      DO  k = nzb_do, nzt_do
    12041211                          local_pf(i,j,k) = MERGE(                             &
    12051212                                              chem_species(lsp)%conc_av(k,j,i),&
  • palm/trunk/SOURCE/data_output_2d.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Added nzb_do and nzt_do for some modules for 2d output
     28!
     29! 3004 2018-04-27 12:33:25Z Giersch
    2730! precipitation_rate removed, case prr*_xy removed, to_be_resorted have to point
    2831! to ql_vp_av and not to ql_vp, allocation checks implemented (averaged data
     
    13951398                IF ( .NOT. found  .AND.  radiation )  THEN
    13961399                   CALL radiation_data_output_2d( av, do2d(av,if), found, grid,&
    1397                                                   mode, local_pf, two_d  )
     1400                                                  mode, local_pf, two_d,       &
     1401                                                  nzb_do, nzt_do  )
    13981402                ENDIF
    13991403
  • palm/trunk/SOURCE/data_output_3d.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Added nzb_do and nzt_do for some modules for 3d output
     28!
     29! 3004 2018-04-27 12:33:25Z Giersch
    2730! Allocation checks implemented (averaged data will be assigned to fill values
    2831! if no allocation happened so far)
     
    779782
    780783             IF ( .NOT. found )  THEN
    781                 CALL tcm_data_output_3d( av, do3d(av,if), found, local_pf )
     784                CALL tcm_data_output_3d( av, do3d(av,if), found, local_pf,     &
     785                                         nzb_do, nzt_do )
    782786                resorted = .TRUE.
    783787             ENDIF
     
    787791             IF ( .NOT. found  .AND.  radiation )  THEN
    788792                CALL radiation_data_output_3d( av, do3d(av,if), found,         &
    789                                                local_pf )
     793                                               local_pf, nzb_do, nzt_do )
    790794                resorted = .TRUE.
    791795             ENDIF
     
    803807             IF ( .NOT. found  .AND.  air_chemistry )  THEN
    804808                CALL chem_data_output_3d( av, do3d(av,if), found,              &
    805                                           local_pf, fill_value )
     809                                          local_pf, fill_value, nzb_do, nzt_do )
    806810                resorted = .TRUE.
    807811             ENDIF
     
    811815             IF ( .NOT. found  .AND.  plant_canopy )  THEN
    812816                CALL pcm_data_output_3d( av, do3d(av,if), found, local_pf,     &
    813                                          fill_value )
     817                                         fill_value, nzb_do, nzt_do )
    814818                resorted = .TRUE.
    815819             ENDIF
  • palm/trunk/SOURCE/gust_mod.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: domain bounds of local_pf corrected
     28!
     29!
    2730! Interfaces concerning data output updated
    2831!
     
    408411       REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    409412
    410        REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     413       REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    411414
    412415
  • palm/trunk/SOURCE/init_3d_model.f90

    r3011 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: initialization of ts_value missing
     28!
     29! 3011 2018-05-07 14:38:42Z schwenkel
    2730! removed redundant if statement
    2831!
     
    11271130
    11281131!
     1132!-- Initialize time series
     1133    ts_value = 0.0_wp
     1134
     1135!
    11291136!-- Initialize local summation arrays for routine flow_statistics.
    11301137!-- This is necessary because they may not yet have been initialized when they
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: set some initial values
     28! Bugfix: domain bounds of local_pf corrected
     29!
     30! 3004 2018-04-27 12:33:25Z Giersch
    2731! Further allocation checks implemented (averaged data will be assigned to fill
    2832! values if no allocation happened so far)
     
    46394643       surf_lsm_h%pavement_surface     = .FALSE.
    46404644       surf_lsm_h%vegetation_surface   = .FALSE.
     4645
     4646!
     4647!--    Set default values
     4648       surf_lsm_h%r_canopy_min = 0.0_wp
     4649
    46414650!
    46424651!--    Vertical surfaces
     
    46714680          surf_lsm_v(l)%vegetation_surface   = .FALSE.
    46724681         
     4682
     4683!
     4684!--       Set default values
     4685          surf_lsm_v(l)%r_canopy_min = 0.0_wp
     4686       
    46734687       ENDDO
    46744688
     
    56325646    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    56335647
    5634     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     5648    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    56355649
    56365650
  • palm/trunk/SOURCE/modules.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Added default values of u_max, v_max, and w_max to avoid floating invalid
     28! during spinup
     29!
     30! 3004 2018-04-27 12:33:25Z Giersch
    2731! precipitation_rate removed
    2832!
     
    20432047                                                  !< (after each timestep)
    20442048   
    2045     REAL(wp) ::  u_max !< maximum of absolute u-veloctiy in entire domain
    2046     REAL(wp) ::  v_max !< maximum of absolute v-veloctiy in entire domain
    2047     REAL(wp) ::  w_max !< maximum of absolute w-veloctiy in entire domain
     2049    REAL(wp) ::  u_max = 0.0_wp !< maximum of absolute u-veloctiy in entire domain
     2050    REAL(wp) ::  v_max = 0.0_wp !< maximum of absolute v-veloctiy in entire domain
     2051    REAL(wp) ::  w_max = 0.0_wp !< maximum of absolute w-veloctiy in entire domain
    20482052
    20492053    REAL(wp), DIMENSION(2) ::  z_i  !< inversion height
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r2977 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: nzb_do and nzt_do were not used for 3d data output
     28! Added pc_transpiration_rate
     29!
     30! 2977 2018-04-17 10:27:57Z kanani
    2731! Implement changes from branch radiation (r2948-2971) with minor modifications,
    2832! plus some formatting.
     
    230234    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s            !< lad on scalar-grid
    231235    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pc_heating_rate  !< plant canopy heating rate
     236    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pc_transpiration_rate  !< plant canopy transpiration rate
    232237
    233238    SAVE
     
    243248!
    244249!-- Public variables and constants
    245     PUBLIC pc_heating_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s,   &
     250    PUBLIC pc_heating_rate, pc_transpiration_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s,   &
    246251           pch_index
    247252           
     
    315320          unit = 'K s-1'
    316321   
     322       CASE ( 'pcm_transpirationrate' )
     323          unit = 'kg kg-1 s-1'
     324
    317325       CASE ( 'pcm_lad' )
    318326          unit = 'm2 m-3'
     
    404412!> Subroutine defining 3D output variables
    405413!------------------------------------------------------------------------------!
    406  SUBROUTINE pcm_data_output_3d( av, variable, found, local_pf, fill_value )
    407  
    408     USE control_parameters,                                                    &
    409         ONLY :  nz_do3d
    410  
     414 SUBROUTINE pcm_data_output_3d( av, variable, found, local_pf, fill_value,     &
     415                                nzb_do, nzt_do )
     416 
    411417    USE indices
    412418
     
    423429    INTEGER(iwp) ::  k      !<
    424430    INTEGER(iwp) ::  k_topo !< topography top index
     431    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
     432    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    425433
    426434    LOGICAL      ::  found !<
    427435
    428436    REAL(wp)     ::  fill_value
    429     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb:nz_do3d) ::  local_pf !<
     437    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    430438
    431439
     
    449457            ENDDO
    450458         ENDIF
    451    
     459   
     460       CASE ( 'pcm_transpirationrate' )
     461         IF ( av == 0 )  THEN
     462            DO  i = nxl, nxr
     463               DO  j = nys, nyn
     464                  IF ( pch_index_ji(j,i) /= 0 )  THEN
     465                     k_topo = get_topography_top_index_ji( j, i, 's' )
     466                     DO  k = k_topo, k_topo + pch_index_ji(j,i)
     467                        local_pf(i,j,k) = pc_transpiration_rate(k-k_topo,j,i)
     468                     ENDDO
     469                  ENDIF
     470               ENDDO
     471            ENDDO
     472         ENDIF
    452473   
    453474      CASE ( 'pcm_lad' )
     
    497518     SELECT CASE ( TRIM( var ) )
    498519
    499         CASE ( 'pcm_heatrate', 'pcm_lad' )
     520        CASE ( 'pcm_heatrate', 'pcm_lad', 'pcm_transpirationrate')
    500521           grid_x = 'x'
    501522           grid_y = 'y'
     
    873894
    874895          ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                 &
    875                     pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     896                    pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg),            &
     897                    pc_transpiration_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    876898!
    877899!--       Piecewise calculation of the cumulative leaf area index by vertical
     
    13971419
    13981420                      kk = k - k_wall   !- lad arrays are defined flat
    1399                       tend(k,j,i) = tend(k,j,i) -                              &
    1400                                        lsec *                                  &
    1401                                        lad_s(kk,j,i) *                         &
     1421                      pc_transpiration_rate(kk,j,i) =  - lsec                  &
     1422                                       * lad_s(kk,j,i) *                       &
    14021423                                       SQRT( ( 0.5_wp * ( u(k,j,i) +           &
    14031424                                                          u(k,j,i+1) )         &
     
    14111432                                           ) *                                 &
    14121433                                       ( q(k,j,i) - lsc )
     1434
     1435                      tend(k,j,i) = tend(k,j,i) + pc_transpiration_rate(kk,j,i)
    14131436                   ENDDO
    14141437                ENDDO
     
    17281751
    17291752             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
    1730 
    1731                 kk = k - k_wall
    1732                 tend(k,j,i) = tend(k,j,i) -                                    &
    1733                                  lsec *                                        &
    1734                                  lad_s(kk,j,i) *                               &
     1753                kk = k - k_wall  !- lad arrays are defined flat
     1754
     1755                pc_transpiration_rate(kk,j,i) = - lsec                         &
     1756                                 * lad_s(kk,j,i) *                             &
    17351757                                 SQRT( ( 0.5_wp * ( u(k,j,i) +                 &
    17361758                                                    u(k,j,i+1) )               &
     
    17441766                                     ) *                                       &
    17451767                                 ( q(k,j,i) - lsc )
     1768
     1769                tend(k,j,i) = tend(k,j,i) + pc_transpiration_rate(kk,j,i)
     1770
    17461771             ENDDO   
    17471772
  • palm/trunk/SOURCE/prognostic_equations.f90

    r2815 r3014  
    2525! -----------------
    2626! $Id$
     27! Fixed a bug in the IF condition to call pcm_tendency in case of
     28! potential temperature
     29!
     30! 2815 2018-02-19 11:29:57Z kanani
    2731! Rename chem_tendency to chem_prognostic_equations,
    2832! implement vector version for air chemistry
     
    298302               timestep_scheme, tsc, use_subsidence_tendencies,                &
    299303               use_upstream_for_tke, wind_turbine, ws_scheme_mom,              &
    300                ws_scheme_sca
     304               ws_scheme_sca, urban_surface, land_surface
    301305
    302306    USE cpulog,                                                                &
     
    759763!
    760764!--          Consideration of heat sources within the plant canopy
    761              IF ( plant_canopy  .AND.  cthf /= 0.0_wp )  THEN
     765             IF ( plant_canopy  .AND.                                          &
     766                (cthf /= 0.0_wp  .OR. urban_surface  .OR.  land_surface) )  THEN
    762767                CALL pcm_tendency( i, j, 4 )
    763768             ENDIF
     
    13251330
    13261331
    1327 
    1328 
    13291332    CALL cpu_log( log_point(32), 'all progn.equations', 'stop' )
    13301333
     
    16711674!
    16721675!--    Consideration of heat sources within the plant canopy
    1673        IF ( plant_canopy .AND. ( cthf /= 0.0_wp ) ) THEN
     1676       IF ( plant_canopy  .AND.                                          &
     1677            (cthf /= 0.0_wp  .OR. urban_surface  .OR.  land_surface) )  THEN
    16741678          CALL pcm_tendency( 4 )
    16751679       ENDIF
     
    17181722          ENDDO
    17191723       ENDDO
    1720 
    17211724!
    17221725!--    Calculate tendencies for the next Runge-Kutta step
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r3004 r3014  
    2828! -----------------
    2929! $Id$
     30! Introduced plant canopy height similar to urban canopy height to limit
     31! the memory requirement to allocate lad.
     32! Deactivated automatic setting of minimum raytracing distance.
     33!
     34! 3004 2018-04-27 12:33:25Z Giersch
    3035! Further allocation checks implemented (averaged data will be assigned to fill
    3136! values if no allocation happened so far)
     
    329334
    330335    USE cloud_parameters,                                                      &
    331         ONLY:  cp, l_d_cp, r_d, rho_l
     336        ONLY:  cp, l_d_cp, l_v, r_d, rho_l
    332337
    333338    USE constants,                                                             &
     
    372377
    373378    USE plant_canopy_model_mod,                                                &
    374         ONLY:  pc_heating_rate, lad_s
     379        ONLY:  lad_s, pc_heating_rate, pc_transpiration_rate
    375380
    376381    USE pegrid
     
    646651!-- Parameters of urban and land surface models
    647652    INTEGER(iwp)                                   ::  nzu                                !< number of layers of urban surface (will be calculated)
     653    INTEGER(iwp)                                   ::  nzp                                !< number of layers of plant canopy (will be calculated)
    648654    INTEGER(iwp)                                   ::  nzub,nzut                          !< bottom and top layer of urban surface (will be calculated)
     655    INTEGER(iwp)                                   ::  nzpt                               !< top layer of plant canopy (will be calculated)
    649656!-- parameters of urban and land surface models
    650657    INTEGER(iwp), PARAMETER                        ::  nzut_free = 3                      !< number of free layers above top of of topography
     
    43244331     REAL(wp), DIMENSION(3)            :: sunorig_grid       !< grid squashed solar direction unit vector (zyx)
    43254332     REAL(wp), DIMENSION(0:nsurf_type) :: costheta           !< direct irradiance factor of solar angle
    4326      REAL(wp), DIMENSION(nzub:nzut)    :: pchf_prep          !< precalculated factor for canopy temp tendency
     4333     REAL(wp), DIMENSION(nzub:nzut)    :: pchf_prep          !< precalculated factor for canopy temperature tendency
     4334     REAL(wp), DIMENSION(nzub:nzut)    :: pctf_prep          !< precalculated factor for canopy transpiration tendency
    43274335     REAL(wp), PARAMETER               :: alpha = 0._wp      !< grid rotation (TODO: add to namelist or remove)
    43284336     REAL(wp)                          :: pc_box_area, pc_abs_frac, pc_abs_eff
     
    43454353     REAL(wp)                          :: area_surf          !< total area of surfaces in all processor
    43464354
     4355
     4356
    43474357#if ! defined( __nopointer )
    43484358     IF ( plant_canopy )  THEN
    43494359         pchf_prep(:) = r_d * (hyp(nzub:nzut) / 100000.0_wp)**0.286_wp &
    43504360                     / (cp * hyp(nzub:nzut) * dx*dy*dz) !< equals to 1 / (rho * c_p * Vbox * T)
     4361         pctf_prep(:) = r_d * (hyp(nzub:nzut) / 100000.0_wp)**0.286_wp &
     4362                     / (l_v * hyp(nzub:nzut) * dx*dy*dz)
    43514363     ENDIF
    43524364#endif
     
    46194631!--  push heat flux absorbed by plant canopy to respective 3D arrays
    46204632     IF ( npcbl > 0 )  THEN
    4621          pc_heating_rate(:,:,:) = 0._wp
     4633         pc_heating_rate(:,:,:) = 0.0_wp
     4634         pc_transpiration_rate(:,:,:) = 0.0_wp
    46224635         DO ipcgb = 1, npcbl
    46234636                 
     
    46304643             pc_heating_rate(kk, j, i) = (pcbinsw(ipcgb) + pcbinlw(ipcgb)) &
    46314644                 * pchf_prep(k) * pt(k, j, i) !-- = dT/dt
     4645
     4646!             pc_transpiration_rate(kk,j,i) = 0.75_wp* (pcbinsw(ipcgb) + pcbinlw(ipcgb)) &
     4647!                 * pctf_prep(k) * pt(k, j, i) !-- = dq/dt
     4648
    46324649         ENDDO
    46334650     ENDIF
     
    49955012       INTEGER(iwp) :: k_topo     !< vertical index indicating topography top for given (j,i)
    49965013       INTEGER(iwp) :: k_topo2    !< vertical index indicating topography top for given (j,i)
    4997        INTEGER(iwp) :: nzubl, nzutl, isurf, ipcgb
     5014       INTEGER(iwp) :: nzptl, nzubl, nzutl, isurf, ipcgb
    49985015       INTEGER(iwp) :: procid
    49995016       REAL(wp)     :: mrl
     
    50405057
    50415058           nzutl = MAX( nzutl, MAXVAL( pct ) )
     5059           nzptl = MAXVAL( pct )
    50425060!--        code of plant canopy model uses parameter pch_index
    50435061!--        we need to setup it here to right value
     
    50585076       CALL MPI_AllReduce(nzubl, nzub, 1, MPI_INTEGER, MPI_MIN, comm2d, ierr )
    50595077       CALL MPI_AllReduce(nzutl, nzut, 1, MPI_INTEGER, MPI_MAX, comm2d, ierr )
     5078       CALL MPI_AllReduce(nzptl, nzpt, 1, MPI_INTEGER, MPI_MAX, comm2d, ierr )
    50605079#else
    50615080       nzub = nzubl
    50625081       nzut = nzutl
     5082       nzpt = nzptl
    50635083#endif
    50645084!
    5065 !--    global number of urban layers
     5085!--    global number of urban and plant layers
    50665086       nzu = nzut - nzub + 1
     5087       nzp = nzpt - nzub + 1
    50675088!
    50685089!--    check max_raytracing_dist relative to urban surface layer height
    5069        mrl = 2.0_wp * nzu * dz
    5070        IF ( max_raytracing_dist <= mrl ) THEN
    5071           IF ( max_raytracing_dist /= -999.0_wp ) THEN
    5072 !--          max_raytracing_dist too low
    5073              WRITE(message_string, '(a,f6.1)') 'Max_raytracing_dist too low, ' &
    5074                    // 'override to value ', mrl
    5075              CALL message('radiation_interaction_init', 'PA0521', 0, 0, -1, 6, 0)
    5076           ENDIF
    5077           max_raytracing_dist = mrl
    5078        ENDIF
     5090!        mrl = 2.0_wp * nzu * dz
     5091!        IF ( max_raytracing_dist <= mrl ) THEN
     5092!           IF ( max_raytracing_dist /= -999.0_wp ) THEN
     5093! !--          max_raytracing_dist too low
     5094!              WRITE(message_string, '(a,f6.1)') 'Max_raytracing_dist too low, ' &
     5095!                    // 'override to value ', mrl
     5096!              CALL message('radiation_interaction_init', 'PA0521', 0, 0, -1, 6, 0)
     5097!           ENDIF
     5098!           max_raytracing_dist = mrl
     5099!        ENDIF
    50795100!
    50805101!--    allocate urban surfaces grid
     
    51035124       IF ( npcbl > 0 )  THEN
    51045125           ALLOCATE( pcbl(iz:ix, 1:npcbl) )
    5105            ALLOCATE( gridpcbl(nzub:nzut,nys:nyn,nxl:nxr) )
     5126           ALLOCATE( gridpcbl(nzub:nzpt,nys:nyn,nxl:nxr) )
    51065127           pcbl = -1
    51075128           gridpcbl(:,:,:) = 0
     
    53885409        IF ( plant_canopy )  THEN
    53895410            ALLOCATE( plantt(0:(nx+1)*(ny+1)-1) )
    5390             maxboxesg = nx + ny + nzu + 1
     5411            maxboxesg = nx + ny + nzp + 1
    53915412            max_track_len = nx + ny + 1
    53925413!--         temporary arrays storing values for csf calculation during raytracing
     
    54165437!--             optimization of memory should be done
    54175438!--             Argument X of function STORAGE_SIZE(X) needs arbitrary REAL(wp) value, set to 1.0_wp for now
    5418                 size_lad_rma = STORAGE_SIZE(1.0_wp)/8*nnx*nny*nzu
     5439                size_lad_rma = STORAGE_SIZE(1.0_wp)/8*nnx*nny*nzp
    54195440                CALL MPI_Win_allocate(size_lad_rma, STORAGE_SIZE(1.0_wp)/8, minfo, comm2d, &
    54205441                                        lad_s_rma_p, win_lad, ierr)
    5421                 CALL c_f_pointer(lad_s_rma_p, lad_s_rma, (/ nzu, nny, nnx /))
     5442                CALL c_f_pointer(lad_s_rma_p, lad_s_rma, (/ nzp, nny, nnx /))
    54225443                sub_lad(nzub:, nys:, nxl:) => lad_s_rma(:,:,:)
    54235444            ELSE
    5424                 ALLOCATE(sub_lad(nzub:nzut, nys:nyn, nxl:nxr))
     5445                ALLOCATE(sub_lad(nzub:nzpt, nys:nyn, nxl:nxr))
    54255446            ENDIF
    54265447#else
    54275448            plantt = RESHAPE( pct(nys:nyn,nxl:nxr), (/(nx+1)*(ny+1)/) )
    5428             ALLOCATE(sub_lad(nzub:nzut, nys:nyn, nxl:nxr))
     5449            ALLOCATE(sub_lad(nzub:nzpt, nys:nyn, nxl:nxr))
    54295450#endif
    54305451            plantt_max = MAXVAL(plantt)
     
    54375458                    k = get_topography_top_index_ji( j, i, 's' )
    54385459
    5439                     sub_lad(k:nzut, j, i) = lad_s(0:nzut-k, j, i)
     5460                    sub_lad(k:nzpt, j, i) = lad_s(0:nzpt-k, j, i)
    54405461                ENDDO
    54415462            ENDDO
     
    54465467                CALL MPI_Win_lock_all(0, win_lad, ierr)
    54475468            ELSE
    5448                 ALLOCATE( sub_lad_g(0:(nx+1)*(ny+1)*nzu-1) )
    5449                 CALL MPI_AllGather( sub_lad, nnx*nny*nzu, MPI_REAL, &
    5450                                     sub_lad_g, nnx*nny*nzu, MPI_REAL, comm2d, ierr )
     5469                ALLOCATE( sub_lad_g(0:(nx+1)*(ny+1)*nzp-1) )
     5470                CALL MPI_AllGather( sub_lad, nnx*nny*nzp, MPI_REAL, &
     5471                                    sub_lad_g, nnx*nny*nzp, MPI_REAL, comm2d, ierr )
    54515472            ENDIF
    54525473#endif
     
    61426163#if defined( __parallel )
    61436164                        lad_ip(ncsb) = ip
    6144                         lad_disp(ncsb) = (box(3)-px*nnx)*(nny*nzu) + (box(2)-py*nny)*nzu + box(1)-nzub
     6165                        lad_disp(ncsb) = (box(3)-px*nnx)*(nny*nzp) + (box(2)-py*nny)*nzp + box(1)-nzub
    61456166#endif
    61466167                    ENDIF
     
    61856206                    lad_s_target = lad_s_ray(i)
    61866207                ELSE
    6187                     lad_s_target = sub_lad_g(lad_ip(i)*nnx*nny*nzu + lad_disp(i))
     6208                    lad_s_target = sub_lad_g(lad_ip(i)*nnx*nny*nzp + lad_disp(i))
    61886209                ENDIF
    61896210#else
     
    63876408               ig = ip*nnx*nny + (rt2_track(2,i)-px*nnx)*nny + rt2_track(1,i)-py*nny
    63886409               IF ( plantt(ig) <= nzterr(ig) )  CYCLE
    6389                wdisp = (rt2_track(2,i)-px*nnx)*(nny*nzu) + (rt2_track(1,i)-py*nny)*nzu + nzterr(ig)+1-nzub
     6410               wdisp = (rt2_track(2,i)-px*nnx)*(nny*nzp) + (rt2_track(1,i)-py*nny)*nzp + nzterr(ig)+1-nzub
    63906411               wcount = plantt(ig)-nzterr(ig)
    63916412               ! TODO send request ASAP - even during raytracing
     
    64116432               py = rt2_track(1,i)/nny
    64126433               ip = px*pdims(2)+py
    6413                ig = ip*nnx*nny*nzu + (rt2_track(2,i)-px*nnx)*(nny*nzu) + (rt2_track(1,i)-py*nny)*nzu
     6434               ig = ip*nnx*nny*nzp + (rt2_track(2,i)-px*nnx)*(nny*nzp) + (rt2_track(1,i)-py*nny)*nzp
    64146435               rt2_track_lad(nzub:plantt_max, i) = sub_lad_g(ig:ig+nly-1)
    64156436            ENDDO
     
    64296450         !--Assert that we have space allocated for CSFs
    64306451         !--
    6431          maxboxes = (ntrack + MAX(origin(1) - nzub, nzut - origin(1))) * SIZE(zdirs, 1)
     6452         maxboxes = (ntrack + MAX(origin(1) - nzub, nzpt - origin(1))) * SIZE(zdirs, 1)
    64326453         IF ( ncsfl + maxboxes > ncsfla )  THEN
    64336454!--         use this code for growing by fixed exponential increments (equivalent to case where ncsfl always increases by 1)
     
    68146835              ENDIF       
    68156836!
    6816 !--           Close binary file                
     6837!--           Close binary file               
    68176838              CALL close_file( fsvf )
    68186839               
     
    76177638!------------------------------------------------------------------------------!
    76187639 SUBROUTINE radiation_data_output_2d( av, variable, found, grid, mode,         &
    7619                                       local_pf, two_d )
     7640                                      local_pf, two_d, nzb_do, nzt_do )
    76207641 
    76217642    USE indices
     
    76357656    INTEGER(iwp) ::  k  !<
    76367657    INTEGER(iwp) ::  m  !< index of surface element at grid point (j,i)
     7658    INTEGER(iwp) ::  nzb_do   !<
     7659    INTEGER(iwp) ::  nzt_do   !<
    76377660
    76387661    LOGICAL      ::  found !<
     
    76417664    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    76427665
    7643     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     7666    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    76447667
    76457668    found = .TRUE.
     
    76857708             DO  i = nxl, nxr
    76867709                DO  j = nys, nyn
    7687                    DO  k = nzb, nzt+1
     7710                   DO  k = nzb_do, nzt_do
    76887711                      local_pf(i,j,k) = rad_lw_in(k,j,i)
    76897712                   ENDDO
     
    76977720             DO  i = nxl, nxr
    76987721                DO  j = nys, nyn
    7699                    DO  k = nzb, nzt+1
     7722                   DO  k = nzb_do, nzt_do
    77007723                      local_pf(i,j,k) = rad_lw_in_av(k,j,i)
    77017724                   ENDDO
     
    77097732             DO  i = nxl, nxr
    77107733                DO  j = nys, nyn
    7711                    DO  k = nzb, nzt+1
     7734                   DO  k = nzb_do, nzt_do
    77127735                      local_pf(i,j,k) = rad_lw_out(k,j,i)
    77137736                   ENDDO
     
    77217744             DO  i = nxl, nxr
    77227745                DO  j = nys, nyn
    7723                    DO  k = nzb, nzt+1
     7746                   DO  k = nzb_do, nzt_do
    77247747                      local_pf(i,j,k) = rad_lw_out_av(k,j,i)
    77257748                   ENDDO
     
    77337756             DO  i = nxl, nxr
    77347757                DO  j = nys, nyn
    7735                    DO  k = nzb, nzt+1
     7758                   DO  k = nzb_do, nzt_do
    77367759                      local_pf(i,j,k) = rad_lw_cs_hr(k,j,i)
    77377760                   ENDDO
     
    77457768             DO  i = nxl, nxr
    77467769                DO  j = nys, nyn
    7747                    DO  k = nzb, nzt+1
     7770                   DO  k = nzb_do, nzt_do
    77487771                      local_pf(i,j,k) = rad_lw_cs_hr_av(k,j,i)
    77497772                   ENDDO
     
    77577780             DO  i = nxl, nxr
    77587781                DO  j = nys, nyn
    7759                    DO  k = nzb, nzt+1
     7782                   DO  k = nzb_do, nzt_do
    77607783                      local_pf(i,j,k) = rad_lw_hr(k,j,i)
    77617784                   ENDDO
     
    77697792             DO  i = nxl, nxr
    77707793                DO  j = nys, nyn
    7771                    DO  k = nzb, nzt+1
     7794                   DO  k = nzb_do, nzt_do
    77727795                      local_pf(i,j,k) = rad_lw_hr_av(k,j,i)
    77737796                   ENDDO
     
    77817804             DO  i = nxl, nxr
    77827805                DO  j = nys, nyn
    7783                    DO  k = nzb, nzt+1
     7806                   DO  k = nzb_do, nzt_do
    77847807                      local_pf(i,j,k) = rad_sw_in(k,j,i)
    77857808                   ENDDO
     
    77937816             DO  i = nxl, nxr
    77947817                DO  j = nys, nyn
    7795                    DO  k = nzb, nzt+1
     7818                   DO  k = nzb_do, nzt_do
    77967819                      local_pf(i,j,k) = rad_sw_in_av(k,j,i)
    77977820                   ENDDO
     
    78057828             DO  i = nxl, nxr
    78067829                DO  j = nys, nyn
    7807                    DO  k = nzb, nzt+1
     7830                   DO  k = nzb_do, nzt_do
    78087831                      local_pf(i,j,k) = rad_sw_out(k,j,i)
    78097832                   ENDDO
     
    78297852             DO  i = nxl, nxr
    78307853                DO  j = nys, nyn
    7831                    DO  k = nzb, nzt+1
     7854                   DO  k = nzb_do, nzt_do
    78327855                      local_pf(i,j,k) = rad_sw_cs_hr(k,j,i)
    78337856                   ENDDO
     
    78417864             DO  i = nxl, nxr
    78427865                DO  j = nys, nyn
    7843                    DO  k = nzb, nzt+1
     7866                   DO  k = nzb_do, nzt_do
    78447867                      local_pf(i,j,k) = rad_sw_cs_hr_av(k,j,i)
    78457868                   ENDDO
     
    78537876             DO  i = nxl, nxr
    78547877                DO  j = nys, nyn
    7855                    DO  k = nzb, nzt+1
     7878                   DO  k = nzb_do, nzt_do
    78567879                      local_pf(i,j,k) = rad_sw_hr(k,j,i)
    78577880                   ENDDO
     
    78657888             DO  i = nxl, nxr
    78667889                DO  j = nys, nyn
    7867                    DO  k = nzb, nzt+1
     7890                   DO  k = nzb_do, nzt_do
    78687891                      local_pf(i,j,k) = rad_sw_hr_av(k,j,i)
    78697892                   ENDDO
     
    78887911!> Subroutine defining 3D output variables
    78897912!------------------------------------------------------------------------------!
    7890  SUBROUTINE radiation_data_output_3d( av, variable, found, local_pf )
     7913 SUBROUTINE radiation_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
    78917914 
    78927915
     
    79047927    INTEGER(iwp) ::  j     !<
    79057928    INTEGER(iwp) ::  k     !<
     7929    INTEGER(iwp) ::  nzb_do   !<
     7930    INTEGER(iwp) ::  nzt_do   !<
    79067931
    79077932    LOGICAL      ::  found !<
     
    79097934    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    79107935
    7911     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     7936    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    79127937
    79137938
     
    79217946            DO  i = nxl, nxr
    79227947               DO  j = nys, nyn
    7923                   DO  k = nzb, nzt+1
     7948                  DO  k = nzb_do, nzt_do
    79247949                     local_pf(i,j,k) = rad_sw_in(k,j,i)
    79257950                  ENDDO
     
    79337958            DO  i = nxl, nxr
    79347959               DO  j = nys, nyn
    7935                   DO  k = nzb, nzt+1
     7960                  DO  k = nzb_do, nzt_do
    79367961                     local_pf(i,j,k) = rad_sw_in_av(k,j,i)
    79377962                  ENDDO
     
    79447969            DO  i = nxl, nxr
    79457970               DO  j = nys, nyn
    7946                   DO  k = nzb, nzt+1
     7971                  DO  k = nzb_do, nzt_do
    79477972                     local_pf(i,j,k) = rad_sw_out(k,j,i)
    79487973                  ENDDO
     
    79567981            DO  i = nxl, nxr
    79577982               DO  j = nys, nyn
    7958                   DO  k = nzb, nzt+1
     7983                  DO  k = nzb_do, nzt_do
    79597984                     local_pf(i,j,k) = rad_sw_out_av(k,j,i)
    79607985                  ENDDO
     
    79677992            DO  i = nxl, nxr
    79687993               DO  j = nys, nyn
    7969                   DO  k = nzb, nzt+1
     7994                  DO  k = nzb_do, nzt_do
    79707995                     local_pf(i,j,k) = rad_sw_cs_hr(k,j,i)
    79717996                  ENDDO
     
    79798004            DO  i = nxl, nxr
    79808005               DO  j = nys, nyn
    7981                   DO  k = nzb, nzt+1
     8006                  DO  k = nzb_do, nzt_do
    79828007                     local_pf(i,j,k) = rad_sw_cs_hr_av(k,j,i)
    79838008                  ENDDO
     
    79908015            DO  i = nxl, nxr
    79918016               DO  j = nys, nyn
    7992                   DO  k = nzb, nzt+1
     8017                  DO  k = nzb_do, nzt_do
    79938018                     local_pf(i,j,k) = rad_sw_hr(k,j,i)
    79948019                  ENDDO
     
    80028027            DO  i = nxl, nxr
    80038028               DO  j = nys, nyn
    8004                   DO  k = nzb, nzt+1
     8029                  DO  k = nzb_do, nzt_do
    80058030                     local_pf(i,j,k) = rad_sw_hr_av(k,j,i)
    80068031                  ENDDO
     
    80138038            DO  i = nxl, nxr
    80148039               DO  j = nys, nyn
    8015                   DO  k = nzb, nzt+1
     8040                  DO  k = nzb_do, nzt_do
    80168041                     local_pf(i,j,k) = rad_lw_in(k,j,i)
    80178042                  ENDDO
     
    80258050            DO  i = nxl, nxr
    80268051               DO  j = nys, nyn
    8027                   DO  k = nzb, nzt+1
     8052                  DO  k = nzb_do, nzt_do
    80288053                     local_pf(i,j,k) = rad_lw_in_av(k,j,i)
    80298054                  ENDDO
     
    80368061            DO  i = nxl, nxr
    80378062               DO  j = nys, nyn
    8038                   DO  k = nzb, nzt+1
     8063                  DO  k = nzb_do, nzt_do
    80398064                     local_pf(i,j,k) = rad_lw_out(k,j,i)
    80408065                  ENDDO
     
    80488073            DO  i = nxl, nxr
    80498074               DO  j = nys, nyn
    8050                   DO  k = nzb, nzt+1
     8075                  DO  k = nzb_do, nzt_do
    80518076                     local_pf(i,j,k) = rad_lw_out_av(k,j,i)
    80528077                  ENDDO
     
    80598084            DO  i = nxl, nxr
    80608085               DO  j = nys, nyn
    8061                   DO  k = nzb, nzt+1
     8086                  DO  k = nzb_do, nzt_do
    80628087                     local_pf(i,j,k) = rad_lw_cs_hr(k,j,i)
    80638088                  ENDDO
     
    80718096            DO  i = nxl, nxr
    80728097               DO  j = nys, nyn
    8073                   DO  k = nzb, nzt+1
     8098                  DO  k = nzb_do, nzt_do
    80748099                     local_pf(i,j,k) = rad_lw_cs_hr_av(k,j,i)
    80758100                  ENDDO
     
    80828107            DO  i = nxl, nxr
    80838108               DO  j = nys, nyn
    8084                   DO  k = nzb, nzt+1
     8109                  DO  k = nzb_do, nzt_do
    80858110                     local_pf(i,j,k) = rad_lw_hr(k,j,i)
    80868111                  ENDDO
     
    80948119            DO  i = nxl, nxr
    80958120               DO  j = nys, nyn
    8096                   DO  k = nzb, nzt+1
     8121                  DO  k = nzb_do, nzt_do
    80978122                     local_pf(i,j,k) = rad_lw_hr_av(k,j,i)
    80988123                  ENDDO
  • palm/trunk/SOURCE/time_integration.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Fixed bug in IF statement
     28! Ensure that the time when calling the radiation to be the time step of the
     29! pre-calculated time when first calculate the positions of the sun
     30!
     31! 3004 2018-04-27 12:33:25Z Giersch
    2732! First call of flow_statistics has been removed. It is already called in
    2833! run_control itself
     
    491496
    492497    CHARACTER (LEN=9) ::  time_to_string          !<
    493     INTEGER           ::  n
    494     INTEGER           ::  lsp
     498    INTEGER(iwp)      ::  it
     499    INTEGER(iwp)      ::  lsp
     500    INTEGER(iwp)      ::  n
     501
    495502
    496503    REAL(wp) ::  dt_3d_old  !< temporary storage of timestep to be used for
    497504                            !< steering of run control output interval
     505    REAL(wp) ::  tsrp_org   !< original value of time_since_reference_point
    498506!
    499507!-- At beginning determine the first time step
     
    10401048                ENDIF
    10411049
     1050!
     1051!--             Adjust the current_ time to the time step of the radiation model.
     1052!--             Needed since radiation is pre-calculated and stored only on apparent
     1053!--             solar positions
     1054                it = FLOOR(time_since_reference_point/dt_radiation)
     1055                tsrp_org = time_since_reference_point
     1056                time_since_reference_point = REAL(it,wp) * dt_radiation
     1057
    10421058                CALL radiation_control
    10431059
     
    10501066                   CALL cpu_log( log_point(75), 'radiation_interaction', 'stop' )
    10511067                ENDIF
     1068   
     1069!
     1070!--             Return the current time to its original value
     1071                time_since_reference_point = tsrp_org
    10521072
    10531073             ENDIF
  • palm/trunk/SOURCE/turbulence_closure_mod.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: nzb_do and nzt_do were not used for 3d data output
     28!
     29! 3004 2018-04-27 12:33:25Z Giersch
    2730! Further allocation checks implemented
    2831!
     
    626629    REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
    627630
    628     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !< local
     631    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !< local
    629632       !< array to which output data is resorted to
    630633
     
    723726!> Define 3D output variables.
    724727!------------------------------------------------------------------------------!
    725  SUBROUTINE tcm_data_output_3d( av, variable, found, local_pf )
     728 SUBROUTINE tcm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
    726729 
    727730
     
    733736    CHARACTER (LEN=*) ::  variable   !<
    734737
    735     INTEGER(iwp) ::  av   !<
    736     INTEGER(iwp) ::  i    !<
    737     INTEGER(iwp) ::  j    !<
    738     INTEGER(iwp) ::  k    !<
     738    INTEGER(iwp) ::  av     !<
     739    INTEGER(iwp) ::  i      !<
     740    INTEGER(iwp) ::  j      !<
     741    INTEGER(iwp) ::  k      !<
     742    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
     743    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    739744
    740745    LOGICAL ::  found   !<
     
    742747    REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
    743748
    744     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf   !< local
     749    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf   !< local
    745750       !< array to which output data is resorted to
    746751
     
    756761             DO  i = nxl, nxr
    757762                DO  j = nys, nyn
    758                    DO  k = nzb, nzt+1
     763                   DO  k = nzb_do, nzt_do
    759764                      local_pf(i,j,k) = diss(k,j,i)
    760765                   ENDDO
     
    768773             DO  i = nxl, nxr
    769774                DO  j = nys, nyn
    770                    DO  k = nzb, nzt+1
     775                   DO  k = nzb_do, nzt_do
    771776                      local_pf(i,j,k) = diss_av(k,j,i)
    772777                   ENDDO
     
    779784             DO  i = nxl, nxr
    780785                DO  j = nys, nyn
    781                    DO  k = nzb, nzt+1
     786                   DO  k = nzb_do, nzt_do
    782787                      local_pf(i,j,k) = kh(k,j,i)
    783788                   ENDDO
     
    791796             DO  i = nxl, nxr
    792797                DO  j = nys, nyn
    793                    DO  k = nzb, nzt+1
     798                   DO  k = nzb_do, nzt_do
    794799                      local_pf(i,j,k) = kh_av(k,j,i)
    795800                   ENDDO
     
    802807             DO  i = nxl, nxr
    803808                DO  j = nys, nyn
    804                    DO  k = nzb, nzt+1
     809                   DO  k = nzb_do, nzt_do
    805810                      local_pf(i,j,k) = km(k,j,i)
    806811                   ENDDO
     
    814819             DO  i = nxl, nxr
    815820                DO  j = nys, nyn
    816                    DO  k = nzb, nzt+1
     821                   DO  k = nzb_do, nzt_do
    817822                      local_pf(i,j,k) = km_av(k,j,i)
    818823                   ENDDO
     
    825830             DO  i = nxl, nxr
    826831                DO  j = nys, nyn
    827                    DO  k = nzb, nzt+1
     832                   DO  k = nzb_do, nzt_do
    828833                      local_pf(i,j,k) = dummy1(k,j,i)
    829834                   ENDDO
     
    836841             DO  i = nxl, nxr
    837842                DO  j = nys, nyn
    838                    DO  k = nzb, nzt+1
     843                   DO  k = nzb_do, nzt_do
    839844                      local_pf(i,j,k) = dummy2(k,j,i)
    840845                   ENDDO
     
    847852             DO  i = nxl, nxr
    848853                DO  j = nys, nyn
    849                    DO  k = nzb, nzt+1
     854                   DO  k = nzb_do, nzt_do
    850855                      local_pf(i,j,k) = dummy3(k,j,i)
    851856                   ENDDO
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r2977 r3014  
    2828! -----------------
    2929! $Id$
     30! Added pc_transpiration_rate
     31!
     32! 2977 2018-04-17 10:27:57Z kanani
    3033! Implement changes from branch radiation (r2948-2971) with minor modifications.
    3134! (moh.hefny):
     
    264267!>       by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?!
    265268!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
     269!> @todo Move plant canopy stuff into plant canopy code
    266270!------------------------------------------------------------------------------!
    267271 MODULE urban_surface_mod
     
    309313   
    310314    USE plant_canopy_model_mod,                                                &
    311         ONLY:  pc_heating_rate
     315        ONLY:  pc_heating_rate, pc_transpiration_rate
    312316   
    313317    USE radiation_model_mod,                                                   &
     
    23612365        INTEGER(iwp)                                           :: ids,idsint,idsidx,isurf,isvf,isurfs,isurflt
    23622366        INTEGER(iwp)                                           :: is,js,ks,i,j,k,iwl,istat, l, m
    2363         INTEGER(iwp)                                           ::  k_topo    !< topography top index
     2367        INTEGER(iwp)                                           :: k_topo    !< topography top index
    23642368
    23652369        dirstart = (/ startland, startwall, startwall, startwall, startwall /)
     
    45394543!--             in case of cthf /= 0 => we need to allocate it for our use here
    45404544                ALLOCATE( pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     4545
     4546                pc_heating_rate = 0.0_wp
     4547
     4548            ENDIF
     4549
     4550            IF ( .NOT.  ALLOCATED( pc_transpiration_rate) )  THEN
     4551!--             then pc_heating_rate is allocated in init_plant_canopy
     4552!--             in case of cthf /= 0 => we need to allocate it for our use here
     4553                ALLOCATE( pc_transpiration_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     4554
     4555                pc_transpiration_rate = 0.0_wp
     4556
     4557
    45414558            ENDIF
    45424559        ENDIF
  • palm/trunk/SOURCE/user_data_output_2d.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: domain bounds of local_pf corrected
     28!
     29! 3004 2018-04-27 12:33:25Z Giersch
    2730! Further allocation checks implemented (averaged data will be assigned to fill
    2831! values if no allocation happened so far)
     
    100103    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    101104
    102     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     105    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    103106
    104107
  • palm/trunk/SOURCE/uv_exposure_model_mod.f90

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: domain bounds of local_pf corrected
     28!
     29! 3004 2018-04-27 12:33:25Z Giersch
    2730! Further allocation checks implemented (averaged data will be assigned to fill
    2831! values if no allocation happened so far)
     
    337340    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    338341
    339     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     342    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    340343
    341344
Note: See TracChangeset for help on using the changeset viewer.