source: codes/icosagcm/trunk/src/read_metric.f90 @ 882

Last change on this file since 882 was 882, checked in by ymipsl, 5 years ago

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

YM

File size: 1.5 KB
Line 
1MODULE read_metric_mod
2
3CONTAINS
4
5
6  SUBROUTINE read_metric
7  USE icosa
8  USE xios_mod
9  USE omp_para
10  IMPLICIT NONE
11    TYPE(t_field),POINTER,SAVE :: f_xcell(:),f_ycell(:),f_zcell(:)
12    REAL(rstd), POINTER :: xcell(:), ycell(:), zcell(:)
13    TYPE(t_domain),POINTER :: d
14    INTEGER :: ind,i,j,n
15    CHARACTER(len=255) :: etat0_type
16    LOGICAL :: read_metric_
17   
18    CALL getin('etat0',etat0_type)
19    CALL getin('read_metric', read_metric_) 
20   
21    CALL allocate_field(f_xcell,field_t,type_real,name='xcell')
22    CALL allocate_field(f_ycell,field_t,type_real,name='ycell')
23    CALL allocate_field(f_zcell,field_t,type_real,name='zcell')
24
25    CALL xios_set_context_input
26    CALL xios_init_write_field_input 
27
28    IF (TRIM(etat0_type)=='start_file' .AND. read_metric_) THEN
29   
30      CALL xios_read_field("xcell_start",f_xcell)
31      CALL xios_read_field("ycell_start",f_ycell)
32      CALL xios_read_field("zcell_start",f_zcell)
33
34      DO ind=1,ndomain
35        IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master) CYCLE
36        d=>domain(ind)
37        CALL swap_dimensions(ind)
38        xcell=f_xcell(ind) 
39        ycell=f_ycell(ind) 
40        zcell=f_zcell(ind) 
41     
42        DO j=jj_begin,jj_end
43          DO i=ii_begin,ii_end
44            n=(j-1)*iim+i
45            d%xyz(1,i,j) = xcell(n) 
46            d%xyz(2,i,j) = ycell(n) 
47            d%xyz(3,i,j) = zcell(n) 
48          ENDDO
49        ENDDO
50      ENDDO
51    ENDIF
52
53    CALL xios_set_context
54
55  END SUBROUTINE read_metric
56
57
58
59END MODULE read_metric_mod
Note: See TracBrowser for help on using the repository browser.