Ignore:
Timestamp:
Jun 9, 2016 4:25:25 PM (8 years ago)
Author:
suehring
Message:

several bugfixes in particle model and serial mode

File:
1 edited

Legend:

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

    r1919 r1929  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Bugfix: weight_substep for initial call, replace by local variable
    2222!
    2323! Former revisions:
     
    162162    REAL(wp)     ::  threadsum      !<
    163163    REAL(wp)     ::  weight_pres_l  !<
     164    REAL(wp)     ::  weight_substep_l !<
    164165
    165166    REAL(wp), DIMENSION(1:3)   ::  volume_flow_l       !<
     
    178179!
    179180!--    If pres is called before initial time step
    180        weight_pres_l = 1.0_wp
    181        d_weight_pres = 1.0_wp
     181       weight_pres_l    = 1.0_wp
     182       d_weight_pres    = 1.0_wp
     183       weight_substep_l = 1.0_wp
    182184    ELSE
    183        weight_pres_l = weight_pres(intermediate_timestep_count)
    184        d_weight_pres = 1.0_wp / weight_pres(intermediate_timestep_count)
     185       weight_pres_l    = weight_pres(intermediate_timestep_count)
     186       d_weight_pres    = 1.0_wp / weight_pres(intermediate_timestep_count)
     187       weight_substep_l = weight_substep(intermediate_timestep_count)
    185188    ENDIF
    186189
     
    591594       !$OMP PARALLEL PRIVATE (i,j,k)
    592595       !$OMP DO
    593        !$acc kernels present( p, tend, weight_substep )
     596       !$acc kernels present( p, tend, weight_substep_l )
    594597       !$acc loop independent
    595598       DO  i = nxl-1, nxr+1
     
    599602             DO  k = nzb, nzt+1
    600603                p(k,j,i) = tend(k,j,i) * &
    601                            weight_substep(intermediate_timestep_count)
     604                           weight_substep_l
    602605             ENDDO
    603606          ENDDO
     
    609612       !$OMP PARALLEL PRIVATE (i,j,k)
    610613       !$OMP DO
    611        !$acc kernels present( p, tend, weight_substep )
     614       !$acc kernels present( p, tend, weight_substep_l )
    612615       !$acc loop independent
    613616       DO  i = nxl-1, nxr+1
     
    617620             DO  k = nzb, nzt+1
    618621                p(k,j,i) = p(k,j,i) + tend(k,j,i) * &
    619                            weight_substep(intermediate_timestep_count)
     622                           weight_substep_l
    620623             ENDDO
    621624          ENDDO
Note: See TracChangeset for help on using the changeset viewer.