Ignore:
Timestamp:
Nov 14, 2018 1:36:44 PM (5 years ago)
Author:
raasch
Message:

unused variables removed, missing working precision added, missing preprocessor directives added, bugfix concerning allocation of t_surf_wall_v in nopointer case, declaration statements rearranged to avoid compile time errors, mpi_abort arguments replaced to avoid compile errors

File:
1 edited

Legend:

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

    r3484 r3524  
    2525! -----------------
    2626! $Id$
     27! declaration statements rearranged to avoid compile time errors
     28!
     29! 3484 2018-11-02 14:41:25Z hellstea
    2730! Introduction of reversibility correction to the interpolation routines in order to
    2831! guarantee mass and scalar conservation through the nest boundaries. Several errors
     
    54165419      IMPLICIT NONE
    54175420
     5421      INTEGER(iwp) ::  nzt_topo_nestbc   !<
     5422
    54185423      REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    54195424                                      INTENT(INOUT) ::  f       !<
     
    54485453!AH      INTEGER(iwp), DIMENSION(0:kct,jcs:jcn,icl:icr), INTENT(IN) :: ijkfc !< number of child grid points contributing to a parent grid box
    54495454      INTEGER(iwp), DIMENSION(0:cg%nz+1,jcs:jcn,icl:icr), INTENT(IN) :: ijkfc !< number of child grid points contributing to a parent grid box
    5450 
    5451       INTEGER(iwp) ::  nzt_topo_nestbc   !<
    54525455
    54535456      CHARACTER(LEN=1), INTENT(IN) ::  edge   !<
     
    57065709      IMPLICIT NONE
    57075710
     5711      INTEGER(iwp) ::  nzt_topo_nestbc   !<
     5712
    57085713      REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    57095714                                      INTENT(INOUT) ::  f             !<
     
    57375742!AH      INTEGER(iwp), DIMENSION(0:kct,jcs:jcn,icl:icr), INTENT(IN) :: ijkfc !< number of child grid points contributing to a parent grid box
    57385743      INTEGER(iwp), DIMENSION(0:cg%nz+1,jcs:jcn,icl:icr), INTENT(IN) :: ijkfc !< number of child grid points contributing to a parent grid box
    5739 
    5740       INTEGER(iwp) ::  nzt_topo_nestbc   !<
    57415744
    57425745      CHARACTER(LEN=1), INTENT(IN) ::  edge   !<
Note: See TracChangeset for help on using the changeset viewer.