Ignore:
Timestamp:
06/11/19 14:59:17 (5 years ago)
Author:
ymipsl
Message:

Metric is now write in start.nc/restart.nc
Metric can be read at restart if read_metric=y.

YM

File:
1 edited

Legend:

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

    r581 r882  
    2626    TYPE(t_field),POINTER,SAVE :: f_ulat(:) 
    2727    TYPE(t_field),POINTER,SAVE :: f_theta_rhodz_1d(:) 
     28    TYPE(t_field),POINTER,SAVE :: f_xcell(:),f_ycell(:),f_zcell(:) 
    2829    REAL(rstd), POINTER :: theta_rhodz(:,:,:),theta_rhodz_1d(:,:) 
     30    REAL(rstd), POINTER :: xcell(:), ycell(:), zcell(:) 
    2931    INTEGER :: ind 
    3032     
     
    3335    CALL allocate_field(f_ulat,field_t,type_real,llm,name='ulat') 
    3436    CALL allocate_field(f_theta_rhodz_1d,field_t,type_real,llm,name='theta_rhodz') 
     37    CALL allocate_field(f_xcell,field_t,type_real,name='xcell') 
     38    CALL allocate_field(f_ycell,field_t,type_real,name='ycell') 
     39    CALL allocate_field(f_zcell,field_t,type_real,name='zcell') 
    3540 
    3641!$OMP BARRIER     
    3742    DO ind=1, ndomain 
    3843       IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     44       CALL swap_dimensions(ind) 
     45       CALL swap_geometry(ind) 
    3946       theta_rhodz=f_theta_rhodz(ind) ; theta_rhodz_1d=f_theta_rhodz_1d(ind) 
    4047       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 
    4151    ENDDO 
    4252     
     
    4555 
    4656    IF(hydrostatic) THEN 
    47        CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q) 
     57       CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q, f_xcell, f_ycell, f_zcell ) 
    4858    ELSE 
    49        CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q, f_geopot, f_W) 
     59       CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q, f_geopot, f_W, f_xcell, f_ycell, f_zcell) 
    5060    END IF 
    5161    CALL deallocate_field(f_ulon) 
Note: See TracChangeset for help on using the changeset viewer.