Changeset 2350 for palm/trunk


Ignore:
Timestamp:
Aug 15, 2017 11:48:26 AM (7 years ago)
Author:
kanani
Message:

bugfixes and workarounds for nopointer version

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

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

    r2339 r2350  
    2525! -----------------
    2626! $Id$
     27! Bugfix in nopointer version
     28!
     29! 2339 2017-08-07 13:55:26Z gronemeier
    2730! corrected timestamp in header
    2831!
     
    616619                          qc(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                &
    617620                          qc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),              &
    618                           tnc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg)
     621                          tnc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),             &
    619622                          tqc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    620623#else
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r2318 r2350  
    2626! -----------------
    2727! $Id$
     28! Bugfix and error message for nopointer version.
     29!
     30! 2318 2017-07-20 17:27:44Z suehring
    2831! Get topography top index via Function call
    2932!
     
    171174#if defined( __nopointer )
    172175    USE arrays_3d,                                                             &
    173         ONLY:  dzu, dzw, e, e_p, nc, nr, pt, pt_p, q, q_p, qc, qr, u, u_p, v,  &
    174                v_p, w, w_p, zu, zw
     176        ONLY:  dzu, dzw, e, e_p, nc, nr, pt, pt_p, q, q_p, qc, qr, s, u, u_p,  &
     177               v, v_p, w, w_p, zu, zw
    175178#else
    176179   USE arrays_3d,                                                              &
     
    504507    INTEGER(iwp)         ::  pmc_status   !:
    505508
     509!
     510!-- NOPOINTER version not implemented yet
     511#if defined( __nopointer )
     512    message_string = 'The pmc interface only runs with POINTER version'
     513    CALL message( 'pmc_interface_mod', 'PA0420', 1, 2, 0, 6, 0 )
     514#endif
    506515
    507516    CALL pmc_init_model( world_comm, nesting_datatransfer_mode, nesting_mode,   &
  • palm/trunk/SOURCE/swap_timelevel.f90

    r2292 r2350  
    2525! -----------------
    2626! $Id$
     27! Bugfix in nopointer version
     28!
     29! 2292 2017-06-20 09:51:42Z schwenkel
    2730! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
    2831! includes two more prognostic equations for cloud drop concentration (nc) 
     
    108111#if defined( __nopointer )
    109112    USE arrays_3d,                                                             &
    110         ONLY:  e, e_p, nc, nc_p, nr, nr_p, pt, pt_p, q, q_p, qc, qc_p qr, qr_p,&
    111                s, s_p, sa, sa_p, u, u_p, v, v_p, w, w_p
     113        ONLY:  e, e_p, nc, nc_p, nr, nr_p, pt, pt_p, q, q_p, qc, qc_p, qr,     &
     114               qr_p, s, s_p, sa, sa_p, u, u_p, v, v_p, w, w_p
    112115#else
    113116    USE arrays_3d,                                                             &
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r2318 r2350  
    2626! -----------------
    2727! $Id$
     28! Bugfix and error message for nopointer version.
     29! Additional "! defined(__nopointer)" as workaround to enable compilation of
     30! nopointer version.
     31!
     32! 2318 2017-07-20 17:27:44Z suehring
    2833! Get topography top index via Function call
    2934!
     
    135140 MODULE urban_surface_mod
    136141
     142#if ! defined( __nopointer )
    137143    USE arrays_3d,                                                             &
    138144        ONLY:  zu, pt, pt_1, pt_2, p, u, v, w, hyp, tend
     145#endif
    139146
    140147    USE cloud_parameters,                                                      &
     
    441448
    442449#if defined( __nopointer )
    443     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
    444     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_wall_h_av          !< Average of t_wall
    445     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
     450    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
     451    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av          !< Average of t_wall
     452    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
    446453
    447454    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v             !< Wall temperature (K)
     
    31563163        INTEGER(iwp) ::  i, j, k, l, m            !< running indices
    31573164        REAL(wp)     ::  c, d, tin, exn
    3158        
     3165
     3166!
     3167!-- NOPOINTER version not implemented yet
     3168#if defined( __nopointer )
     3169    message_string = 'The urban surface module only runs with POINTER version'
     3170    CALL message( 'urban_surface_mod', 'PA0452', 1, 2, 0, 6, 0 )
     3171#endif
    31593172
    31603173        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
     
    32213234!--         At horizontal surfaces. Please note, t_surf_h is defined on a
    32223235!--         different data type, but with the same dimension.
     3236#if ! defined( __nopointer )
    32233237            DO  m = 1, surf_usm_h%ns
    32243238               i = surf_usm_h%i(m)           
     
    32393253               ENDDO
    32403254            ENDDO
    3241 
     3255#endif
    32423256     
    32433257!--         initial values for t_wall
     
    35193533        INTEGER(iwp), DIMENSION(0:3) :: reorder = (/ 1, 0, 3, 2 /)
    35203534       
    3521        
     3535#if ! defined( __nopointer )
    35223536        IF ( plant_canopy )  THEN
    35233537            pchf_prep(:) = r_d * (hyp(nzub:nzut) / 100000.0_wp)**0.286_wp &
    35243538                        / (cp * hyp(nzub:nzut) * dx*dy*dz) !< equals to 1 / (rho * c_p * Vbox * T)
    35253539        ENDIF
    3526 
     3540#endif
    35273541        sun_direction = .TRUE.
    35283542        CALL calc_zenith  !< required also for diffusion radiation
     
    37823796
    37833797!--     push heat flux absorbed by plant canopy to respective 3D arrays
     3798#if ! defined( __nopointer )
    37843799        IF ( plant_canopy )  THEN
    37853800            pc_heating_rate(:,:,:) = 0._wp
     
    37953810            ENDDO
    37963811        ENDIF
     3812#endif
    37973813!
    37983814!--     Transfer radiation arrays required for energy balance to the respective data types
     
    42934309                                              t_surf_h, tmp_surf_h,            &
    42944310                                              surf_usm_h%start_index )
    4295                       ENDIF
    42964311#else                     
    42974312                      IF ( kk == 1 )  THEN
     
    43154330                                              t_surf_v(0)%t, tmp_surf_v(0)%t,  &
    43164331                                              surf_usm_v(0)%start_index )
    4317                       ENDIF
    43184332#else                     
    43194333                      IF ( kk == 1 )  THEN
     
    44594473                                              t_wall_v(2)%t, tmp_wall_v(2)%t,  &
    44604474                                              surf_usm_v(2)%start_index )
    4461                       ENDIF
    44624475#else
    44634476                      IF ( kk == 1 )  THEN
     
    48124825
    48134826           IF ( usm_par(5,jw,iw) == 0 )  THEN
     4827#if ! defined( __nopointer )
    48144828              IF ( zu(kw) >= roof_height_limit )  THEN
    48154829                 surf_usm_h%isroof_surf(m)   = .TRUE.
     
    48194833                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
    48204834              ENDIF
     4835#endif
    48214836              surf_usm_h%albedo_surf(m)    = -1.0_wp
    48224837              surf_usm_h%thickness_wall(m) = -1.0_wp
     
    50385053
    50395054        dxdir = (/dz,dy,dy,dx,dx/)
    5040        
     5055#if ! defined( __nopointer )
    50415056        exn(:) = (hyp(nzub:nzut) / 100000.0_wp )**0.286_wp          !< Exner function
     5057#endif
    50425058!       
    50435059!--     First, treat horizontal surface elements
     
    50585074              lambda_surface = surf_usm_h%lambda_surf(m)
    50595075           ENDIF
    5060            
     5076#if ! defined( __nopointer )
    50615077           pt1  = pt(k,j,i)
    50625078!
    50635079!--        calculate rho * cp coefficient at surface layer
    50645080           rho_cp  = cp * hyp(k) / ( r_d * pt1 * exn(k) )
     5081#endif
    50655082!
    50665083!--        Calculate aerodyamic resistance.
     
    51385155!--        pt(k,j,i) is calculated for all directions in diffusion_s
    51395156!--        using surface and wall heat fluxes
     5157#if ! defined( __nopointer )
    51405158           pt(k-1,j,i) = t_surf_h_p(m) / exn(k)  ! not for vertical surfaces
     5159#endif
    51415160
    51425161!--        calculate fluxes
     
    51725191!--          stratification is not considered in this case.
    51735192             lambda_surface = surf_usm_v(l)%lambda_surf(m)
    5174            
     5193#if ! defined( __nopointer )         
    51755194             pt1  = pt(k,j,i)
    51765195!
    51775196!--          calculate rho * cp coefficient at surface layer
    51785197             rho_cp  = cp * hyp(k) / ( r_d * pt1 * exn(k) )
     5198#endif
    51795199
    51805200!--          Calculation of r_a for vertical surfaces
     
    52015221!--          obtained by simple linear interpolation. ( An alternative would
    52025222!--          be an logarithmic interpolation. )
     5223#if ! defined( __nopointer )
    52035224             u1 = ( u(k,j,i) + u(k,j,i+1) ) * 0.5_wp
    52045225             v1 = ( v(k,j,i) + v(k,j+1,i) ) * 0.5_wp
    52055226             w1 = ( w(k,j,i) + w(k-1,j,i) ) * 0.5_wp
     5227#endif
    52065228               
    52075229             Ueff   = SQRT( u1**2 + v1**2 + w1**2 )
     
    53175339!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
    53185340!--     get the borders from neighbours
     5341#if ! defined( __nopointer )
    53195342        CALL exchange_horiz( pt, nbgp )
     5343#endif
    53205344
    53215345
Note: See TracChangeset for help on using the changeset viewer.