source: codes/icosagcm/devel/src/initial/etat0.f90 @ 915

Last change on this file since 915 was 906, checked in by dubos, 5 years ago

devel : compute_rhodz for unstructured mesh

File size: 7.0 KB
RevLine 
[12]1MODULE etat0_mod
[199]2  USE icosa
[847]3  USE etat0_collocated_mod
[344]4  IMPLICIT NONE         
[199]5  PRIVATE
6
[847]7  PUBLIC :: etat0, init_etat0
[12]8
[568]9! Important notes for OpenMP
10! When etat0 is called, vertical OpenMP parallelism is deactivated.
11! Therefore only the omp_level_master thread must work, i.e. :
12!   !$OMP BARRIER
13!    DO ind=1,ndomain
14!      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
15!      ...
16!    END DO
17!   !$OMP BARRIER
18! There MUST be NO OMP BARRIER inside the DO-LOOP or any routine it calls.
19
[17]20CONTAINS
21 
[467]22  SUBROUTINE init_etat0
[568]23    USE etat0_database_mod, ONLY: init_etat0_database => init_etat0 
24    USE etat0_start_file_mod, ONLY: init_etat0_start_file => init_etat0 
25    USE etat0_heldsz_mod, ONLY: init_etat0_held_suarez => init_etat0 
26   
[467]27    CALL getin("etat0",etat0_type)
28
29    SELECT CASE (TRIM(etat0_type))
30      CASE ('isothermal')
31      CASE ('temperature_profile')
32      CASE ('jablonowsky06')
33      CASE ('dcmip5')
34      CASE ('williamson91.6')
35      CASE ('start_file')
[483]36        CALL init_etat0_start_file
[467]37      CASE ('database')
38        CALL init_etat0_database
39      CASE ('academic')
40      CASE ('held_suarez')
[549]41         CALL init_etat0_held_suarez
[467]42      CASE ('venus')
43      CASE ('dcmip1')
44      CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
45      CASE ('dcmip3')
46      CASE ('dcmip4')
[468]47      CASE ('dcmip2016_baroclinic_wave')
48      CASE ('dcmip2016_cyclone')
49      CASE ('dcmip2016_supercell')
[499]50      CASE ('bubble')
[467]51      CASE DEFAULT
[468]52         PRINT*, 'Bad selector for variable etat0 <',TRIM(etat0_type),'>'// &
53            ' options are  <isothermal>, <temperature_profile>, <jablonowsky06>, <dcmip5>, <williamson91.6>,'& 
54                         //' <start_file>, <database>, <academic>, <held_suarez>, <venus>, <dcmip1>,'         &
55                         //' <dcmip2_mountain,dcmip2_schaer_noshear,dcmip2_schaer_shear>, <dcmip3>, <dcmip4>,'&
[499]56                         //' <dcmip2016_baroclinic_wave>, <dcmip2016_cyclone>, <dcmip2016_supercell>', 'bubble'
[467]57         STOP
58    END SELECT
59
60  END SUBROUTINE init_etat0
61
[366]62  SUBROUTINE etat0(f_ps,f_mass,f_phis,f_theta_rhodz,f_u, f_geopot,f_w, f_q)
[847]63    USE omp_para, ONLY : is_omp_level_master
[192]64    USE mpipara, ONLY : is_mpi_root
[906]65    USE disvert_mod, ONLY : caldyn_eta, eta_lag
66    USE compute_diagnostics_mod, ONLY : compute_rhodz
[345]67    ! Generic interface
[847]68    USE etat0_isothermal_mod, ONLY : getin_etat0_isothermal=>getin_etat0
[344]69    USE etat0_dcmip1_mod, ONLY : getin_etat0_dcmip1=>getin_etat0
70    USE etat0_dcmip2_mod, ONLY : getin_etat0_dcmip2=>getin_etat0
[346]71    USE etat0_dcmip4_mod, ONLY : getin_etat0_dcmip4=>getin_etat0
[203]72    USE etat0_dcmip5_mod, ONLY : getin_etat0_dcmip5=>getin_etat0
[377]73    USE etat0_bubble_mod, ONLY : getin_etat0_bubble=>getin_etat0
[204]74    USE etat0_williamson_mod, ONLY : getin_etat0_williamson=>getin_etat0
[327]75    USE etat0_temperature_mod, ONLY: getin_etat0_temperature=>getin_etat0
[382]76    USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : getin_etat0_dcmip2016_baroclinic_wave=>getin_etat0
[388]77    USE etat0_dcmip2016_cyclone_mod, ONLY : getin_etat0_dcmip2016_cyclone=>getin_etat0
78    USE etat0_dcmip2016_supercell_mod, ONLY : getin_etat0_dcmip2016_supercell=>getin_etat0
[345]79    ! Ad hoc interfaces
[467]80    USE etat0_academic_mod, ONLY : etat0_academic=>etat0
81    USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0
82    USE etat0_venus_mod,  ONLY : etat0_venus=>etat0
83    USE etat0_database_mod, ONLY : etat0_database=>etat0
[266]84    USE etat0_start_file_mod, ONLY : etat0_start_file=>etat0 
[149]85
[17]86    TYPE(t_field),POINTER :: f_ps(:)
[159]87    TYPE(t_field),POINTER :: f_mass(:)
[17]88    TYPE(t_field),POINTER :: f_phis(:)
89    TYPE(t_field),POINTER :: f_theta_rhodz(:)
90    TYPE(t_field),POINTER :: f_u(:)
[366]91    TYPE(t_field),POINTER :: f_geopot(:)
92    TYPE(t_field),POINTER :: f_w(:)
[17]93    TYPE(t_field),POINTER :: f_q(:)
[186]94   
[159]95    REAL(rstd),POINTER :: ps(:), mass(:,:)
[366]96    LOGICAL :: autoinit_mass, autoinit_geopot, collocated
[159]97    INTEGER :: ind,i,j,ij,l
98
99    ! most etat0 routines set ps and not mass
100    ! in that case and if caldyn_eta == eta_lag
101    ! the initial distribution of mass is taken to be the same
102    ! as what the mass coordinate would dictate
[366]103    ! however if etat0_XXX defines mass then the flag autoinit_mass must be set to .FALSE.
[159]104    ! otherwise mass will be overwritten
[366]105    autoinit_mass = (caldyn_eta == eta_lag)
[159]106
[17]107    etat0_type='jablonowsky06'
108    CALL getin("etat0",etat0_type)
109   
[345]110    !------------------- Generic interface ---------------------
[344]111    collocated=.TRUE.
[17]112    SELECT CASE (TRIM(etat0_type))
[199]113    CASE ('isothermal')
114       CALL getin_etat0_isothermal
[327]115    CASE ('temperature_profile')
116       CALL getin_etat0_temperature
[203]117    CASE ('jablonowsky06')
[344]118    CASE ('dcmip1')
119        CALL getin_etat0_dcmip1
120    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
121       CALL getin_etat0_dcmip2
[345]122    CASE ('dcmip3')
[346]123    CASE ('dcmip4')
124        CALL getin_etat0_dcmip4
[344]125    CASE ('dcmip5')
[203]126        CALL getin_etat0_dcmip5
[377]127    CASE ('bubble')
128        CALL getin_etat0_bubble
[168]129    CASE ('williamson91.6')
[366]130       autoinit_mass=.FALSE.
[204]131       CALL getin_etat0_williamson
[382]132    CASE ('dcmip2016_baroclinic_wave')
133        CALL getin_etat0_dcmip2016_baroclinic_wave
[388]134    CASE ('dcmip2016_cyclone')
135        CALL getin_etat0_dcmip2016_cyclone
136    CASE ('dcmip2016_supercell')
137        CALL getin_etat0_dcmip2016_supercell
[344]138    CASE DEFAULT
139       collocated=.FALSE.
[366]140       autoinit_mass = .FALSE.
[344]141    END SELECT
142
[345]143    !------------------- Ad hoc interfaces --------------------
[344]144    SELECT CASE (TRIM(etat0_type))
[467]145     CASE ('database')
146        CALL etat0_database(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[266]147    CASE ('start_file')
148       CALL etat0_start_file(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[54]149    CASE ('academic')
150       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[170]151    CASE ('held_suarez')
152       PRINT *,"Held & Suarez (1994) test case"
[149]153       CALL etat0_heldsz(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[325]154    CASE ('venus')
155       CALL etat0_venus(f_ps, f_phis, f_theta_rhodz, f_u, f_q)
156       PRINT *, "Venus (Lebonnois et al., 2012) test case"
[62]157   CASE DEFAULT
[344]158      IF(collocated) THEN
[366]159         CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q)
[344]160      ELSE
[468]161         PRINT*, 'Bad selector for variable etat0 <',TRIM(etat0_type),'>'// &
162            ' options are  <isothermal>, <temperature_profile>, <jablonowsky06>, <dcmip5>, <williamson91.6>,'& 
163                         //' <start_file>, <database>, <academic>, <held_suarez>, <venus>, <dcmip1>,'         &
164                         //' <dcmip2_mountain,dcmip2_schaer_noshear,dcmip2_schaer_shear>, <dcmip3>, <dcmip4>,'&
165                         //' <dcmip2016_baroclinic_wave>, <dcmip2016_cyclone>, <dcmip2016_supercell>'
[344]166         STOP
167      END IF
[54]168    END SELECT
[159]169
[366]170    IF(autoinit_mass) THEN
[159]171       DO ind=1,ndomain
[568]172          IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
[159]173          CALL swap_dimensions(ind)
174          CALL swap_geometry(ind)
175          mass=f_mass(ind); ps=f_ps(ind)
[366]176          CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps
[159]177       END DO
178    END IF
[366]179 
[54]180  END SUBROUTINE etat0
[199]181
[12]182END MODULE etat0_mod
Note: See TracBrowser for help on using the repository browser.