Changeset 1013


Ignore:
Timestamp:
02/28/20 09:56:31 (4 years ago)
Author:
ymipsl
Message:

1j+1j=2j : (x / r) * r /= x due to rounding error. So at restart a run did not have exactly the same metric than the previous run.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/output/write_etat0.f90

    r882 r1013  
    1313  USE omp_para 
    1414  USE xios_mod 
     15  USE checksum_mod 
    1516  IMPLICIT NONE 
    1617    INTEGER,INTENT(IN)    :: it 
     
    2930    REAL(rstd), POINTER :: theta_rhodz(:,:,:),theta_rhodz_1d(:,:) 
    3031    REAL(rstd), POINTER :: xcell(:), ycell(:), zcell(:) 
    31     INTEGER :: ind 
     32    INTEGER :: ind,n,i,j 
    3233     
    3334     
     
    4142!$OMP BARRIER     
    4243    DO ind=1, ndomain 
    43        IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
    44        CALL swap_dimensions(ind) 
    45        CALL swap_geometry(ind) 
    46        theta_rhodz=f_theta_rhodz(ind) ; theta_rhodz_1d=f_theta_rhodz_1d(ind) 
    47        theta_rhodz_1d(:,:)=theta_rhodz(:,:,1) 
    48        xcell=f_xcell(ind) ; xcell=xyz_i(:,1)/radius 
    49        ycell=f_ycell(ind) ; ycell=xyz_i(:,2)/radius 
    50        zcell=f_zcell(ind) ; zcell=xyz_i(:,3)/radius 
     44      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     45      CALL swap_dimensions(ind) 
     46      CALL swap_geometry(ind) 
     47      theta_rhodz=f_theta_rhodz(ind) ; theta_rhodz_1d=f_theta_rhodz_1d(ind) 
     48      theta_rhodz_1d(:,:)=theta_rhodz(:,:,1) 
     49    
     50      xcell=f_xcell(ind) ; ! xcell=xyz_i(:,1)/radius  => cannot use due to rounding error 
     51      ycell=f_ycell(ind) ; ! ycell=xyz_i(:,2)/radius  => for 1+1=2 
     52      zcell=f_zcell(ind) ; ! zcell=xyz_i(:,3)/radius 
     53 
     54      DO j=jj_begin,jj_end 
     55        DO i=ii_begin,ii_end 
     56          n=(j-1)*iim+i 
     57          xcell(n) = domain(ind)%xyz(1,i,j) ! not the best but for now it works 
     58          ycell(n) = domain(ind)%xyz(2,i,j)  
     59          zcell(n) = domain(ind)%xyz(3,i,j)  
     60        ENDDO 
     61      ENDDO        
    5162    ENDDO 
    5263     
Note: See TracChangeset for help on using the changeset viewer.