Changeset 1014


Ignore:
Timestamp:
02/28/20 10:07:19 (4 years ago)
Author:
ymipsl
Message:

1j+1j=2j : when restart from a file, in order to do not modify metric, it must

  • do not optimize the metric even if the optim_it getin parameter is set to a value > 0
  • do not call the schimtt tranform, even if the zoom procedure return identity, due to rounding error (probably due to finite decimal of pi)

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/sphere/geometry.f90

    r963 r1014  
    227227    INTEGER :: ind,i,j,n 
    228228    REAL(rstd) :: schmidt_factor, schmidt_lon, schmidt_lat 
     229    LOGICAL :: read_metric=.FALSE. 
     230     
     231    CALL getin('read_metric', read_metric)  
    229232 
    230233    ! Schmidt transform parameters 
     
    241244    schmidt_lat = schmidt_lat * pi/180. 
    242245 
    243     DO ind=1,ndomain 
    244       IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
    245       CALL swap_dimensions(ind) 
    246       CALL swap_geometry(ind) 
    247       DO j=jj_begin,jj_end 
    248         DO i=ii_begin,ii_end 
    249           n=(j-1)*iim+i 
    250           CALL schmidt_transform(xyz_i(n,:), schmidt_factor, schmidt_lon, schmidt_lat) 
     246    IF (.NOT. read_metric) THEN 
     247      DO ind=1,ndomain 
     248        IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     249        CALL swap_dimensions(ind) 
     250        CALL swap_geometry(ind) 
     251        DO j=jj_begin,jj_end 
     252          DO i=ii_begin,ii_end 
     253            n=(j-1)*iim+i 
     254            CALL schmidt_transform(xyz_i(n,:), schmidt_factor, schmidt_lon, schmidt_lat) 
     255          ENDDO 
    251256        ENDDO 
    252257      ENDDO 
    253     ENDDO 
     258    ENDIF 
     259     
    254260  END SUBROUTINE remap_schmidt_loc 
    255261 
     
    263269  USE getin_mod 
    264270  USE omp_para 
     271  USE checksum_mod 
    265272  IMPLICIT NONE 
    266273    INTEGER :: nb_it=0 
     
    271278    REAL(rstd) :: sum 
    272279    LOGICAL    :: check 
    273      
     280    LOGICAL :: read_metric=.FALSE. 
    274281     
    275282    CALL getin('optim_it',nb_it) 
     283    CALL getin('read_metric', read_metric)  
     284    IF (read_metric) nb_it=0 
    276285     
    277286    DO ind=1,ndomain 
     
    425434  USE getin_mod 
    426435  USE omp_para 
     436  USE checksum_mod 
    427437  IMPLICIT NONE 
    428438 
     
    446456    ! so that XIOS gets the right values 
    447457    CALL update_domain 
    448  
     458     
    449459    DO ind=1,ndomain 
    450460      IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master ) CYCLE 
Note: See TracChangeset for help on using the changeset viewer.