Ignore:
Timestamp:
01/21/20 00:16:21 (4 years ago)
Author:
dubos
Message:

devel : bugfix, missing halo exchange before call to physics_column

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/physics/physics_interface.f90

    r741 r1011  
    77  TYPE t_physics_inout 
    88     ! Input, time-independent 
    9      INTEGER :: ngrid 
     9     INTEGER :: ngrid, it 
    1010     REAL(rstd) :: dt_phys 
    11      REAL(rstd), DIMENSION(:), POINTER :: Ai, lon, lat, phis 
     11     REAL(rstd), DIMENSION(:), ALLOCATABLE :: Ai, lon, lat, phis 
    1212     ! Input, time-dependent 
    13      REAL(rstd), DIMENSION(:,:), POINTER :: geopot, p, pk, Temp, ulon, ulat 
    14      REAL(rstd), DIMENSION(:,:,:), POINTER :: q 
     13     REAL(rstd), DIMENSION(:,:), ALLOCATABLE :: geopot, p, pk, Temp, ulon, ulat 
     14     REAL(rstd), DIMENSION(:,:,:), ALLOCATABLE :: q 
    1515     ! Output arrays 
    16      REAL(rstd), DIMENSION(:,:), POINTER :: dTemp, dulon, dulat 
    17      REAL(rstd), DIMENSION(:,:,:), POINTER :: dq 
     16     REAL(rstd), DIMENSION(:,:), ALLOCATABLE :: dTemp, dulon, dulat 
     17     REAL(rstd), DIMENSION(:,:,:), ALLOCATABLE :: dq 
    1818  END TYPE t_physics_inout 
    1919 
     
    165165        
    166166    CASE DEFAULT ! Copy non-halo points only, as contiguous segments (works) 
    167        n=0 
     167       n(:)=0 
    168168       n(jj_begin:jj_end)=COUNT(own(ii_begin:ii_end,jj_begin:jj_end),1) 
    169169       ngrid=SUM(n) 
     
    185185             DO i=ii_begin,ii_end 
    186186                IF(own(i,j)) THEN 
    187                    info%n(jj)=n(j) 
    188                    info%k(jj)=k 
    189                    info%ij(jj) = iim*(j-1)+i 
     187                   info%n(jj)=n(j)              ! size of segment 
     188                   info%k(jj)=k                 ! start index in packed array 
     189                   info%ij(jj) = iim*(j-1)+i    ! start index in unpacked array 
    190190                   IF(COUNT(own(i:i+n(j)-1,j)) /= n(j)) STOP 
    191191                   EXIT 
Note: See TracChangeset for help on using the changeset viewer.