source: LMDZ6/trunk/libf/phylmd/create_etat0_limit_unstruct.F90 @ 3981

Last change on this file since 3981 was 3585, checked in by Ehouarn Millour, 5 years ago

Follow-up of r3579 (update of iniaqua) for the unstructured case, along with some code cleanup (use getin_p instead of getin+broadcasts).
EM

File size: 4.0 KB
RevLine 
[3435]1MODULE etat0_limit_unstruct_mod
2
3  LOGICAL, SAVE  :: create_etat0_limit
4!$OMP THREADPRIVATE(create_etat0_limit)
5
6
7
8
9CONTAINS
10 
11  SUBROUTINE init_etat0_limit_unstruct
[3436]12#ifdef CPP_XIOS
[3585]13  USE xios, ONLY: xios_set_axis_attr, xios_set_fieldgroup_attr, &
14                  xios_set_filegroup_attr, xios_set_file_attr
15  USE mod_phys_lmdz_para, ONLY: is_omp_master
16  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
17  USE ioipsl, ONLY : ioget_year_len
18  USE ioipsl_getin_p_mod, ONLY: getin_p
[3435]19  USE time_phylmdz_mod, ONLY : annee_ref
[3585]20  USE create_etat0_unstruct_mod, ONLY: init_create_etat0_unstruct
[3435]21  IMPLICIT NONE
22 
23    INTEGER :: iflag_phys,i
24    INTEGER :: ndays
25    REAL,ALLOCATABLE :: value(:)
26   
27      IF (grid_type==unstructured) THEN
[3585]28        CALL getin_p("iflag_phys",iflag_phys)
[3435]29       
[3585]30        CALL getin_p('create_etat0_limit',create_etat0_limit)
[3435]31       
32        ndays=ioget_year_len(annee_ref)
33        ALLOCATE(value(ndays))
34        DO i=1,ndays
35          value(i)=i-1
36        ENDDO
37       
38        IF (is_omp_master) CALL xios_set_axis_attr("time_year",n_glo=ndays,value=value)
39       
40        IF (create_etat0_limit) THEN
41          IF (iflag_phys<100) THEN
42            IF (is_omp_master) CALL xios_set_fieldgroup_attr("etat0_limit_read",read_access=.TRUE.,enabled=.TRUE.)
43            IF (is_omp_master) CALL xios_set_filegroup_attr("etat0_limit_read",enabled=.TRUE.)
44          ENDIF
45          IF (is_omp_master) CALL xios_set_file_attr("limit_write",enabled=.TRUE.)
[3465]46          CALL init_create_etat0_unstruct
[3435]47        ENDIF
48     
49      ENDIF 
50
[3436]51#endif
[3435]52  END SUBROUTINE init_etat0_limit_unstruct
53 
54  SUBROUTINE create_etat0_limit_unstruct
[3436]55#ifdef CPP_XIOS
[3585]56  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
57  USE create_etat0_unstruct_mod, ONLY: create_etat0_unstruct
58  USE create_limit_unstruct_mod, ONLY: create_limit_unstruct
59  USE phyaqua_mod, ONLY: iniaqua
60  USE phys_cal_mod, only: year_len
61  USE mod_phys_lmdz_para, ONLY: is_omp_master
62  USE ioipsl_getin_p_mod, ONLY: getin_p
63  USE dimphy, ONLY: klon
64  USE xios, ONLY: xios_context_finalize, xios_set_current_context, &
65                  xios_finalize
[3470]66  USE print_control_mod, ONLY: lunout
[3435]67  IMPLICIT NONE
68      INTEGER :: iflag_phys
[3531]69      INTEGER :: ierr
70      CHARACTER (LEN=20) :: modname='create_etat0_limit_unstruct'
71      CHARACTER (LEN=80) :: abort_message
72     
[3435]73      IF (grid_type==unstructured) THEN
74 
[3585]75        CALL getin_p("iflag_phys",iflag_phys)
[3435]76
77        IF (iflag_phys<100) THEN
78          IF ( create_etat0_limit) THEN
79              CALL create_etat0_unstruct
80              CALL create_limit_unstruct
81              IF (is_omp_master)  THEN
82                CALL xios_context_finalize()
83                CALL xios_set_current_context("icosagcm")   ! very bad, need to find an other solution
84                CALL xios_context_finalize()
85                CALL xios_finalize()
[3470]86#ifdef CPP_MPI   
87                CALL MPI_Finalize(ierr)
88#endif
[3531]89                abort_message='create_etat0_limit_unstruct, Initial state file are created, all is fine'
90                CALL abort_physic(modname,abort_message,0)
[3543]91                STOP 0
[3435]92              ENDIF
93!$OMP BARRIER
[3532]94              abort_message='create_etat0_limit_unstruct, Initial state file are created, all is fine'
95              CALL abort_physic(modname,abort_message,0)
[3435]96          ENDIF
97        ELSE
98          IF (create_etat0_limit) THEN
[3585]99            CALL iniaqua(klon,year_len,iflag_phys)
[3435]100              IF (is_omp_master)  THEN
101                CALL xios_context_finalize()
102                CALL xios_set_current_context("icosagcm")   ! very bad, need to find an other solution
103                CALL xios_context_finalize()
104                CALL xios_finalize()
[3470]105#ifdef CPP_MPI
106                CALL MPI_Finalize(ierr)
107#endif
[3435]108              ENDIF
109!$OMP BARRIER
[3531]110              abort_message='create_etat0_limit_unstruct, Initial state file are created, all is fine'
111              CALL abort_physic(modname,abort_message,0)
[3543]112              STOP 0
[3435]113          ENDIF
114        ENDIF
115      ENDIF
116       
[3436]117#endif
[3435]118  END SUBROUTINE create_etat0_limit_unstruct
119 
120END MODULE etat0_limit_unstruct_mod
121
Note: See TracBrowser for help on using the repository browser.