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

Last change on this file since 879 was 847, checked in by dubos, 5 years ago

devel : split etat0 into etat0, etat0_collocated and etat0_isothermal

File size: 6.9 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
[159]65    USE disvert_mod
[345]66    ! Generic interface
[847]67    USE etat0_isothermal_mod, ONLY : getin_etat0_isothermal=>getin_etat0
[344]68    USE etat0_dcmip1_mod, ONLY : getin_etat0_dcmip1=>getin_etat0
69    USE etat0_dcmip2_mod, ONLY : getin_etat0_dcmip2=>getin_etat0
[346]70    USE etat0_dcmip4_mod, ONLY : getin_etat0_dcmip4=>getin_etat0
[203]71    USE etat0_dcmip5_mod, ONLY : getin_etat0_dcmip5=>getin_etat0
[377]72    USE etat0_bubble_mod, ONLY : getin_etat0_bubble=>getin_etat0
[204]73    USE etat0_williamson_mod, ONLY : getin_etat0_williamson=>getin_etat0
[327]74    USE etat0_temperature_mod, ONLY: getin_etat0_temperature=>getin_etat0
[382]75    USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : getin_etat0_dcmip2016_baroclinic_wave=>getin_etat0
[388]76    USE etat0_dcmip2016_cyclone_mod, ONLY : getin_etat0_dcmip2016_cyclone=>getin_etat0
77    USE etat0_dcmip2016_supercell_mod, ONLY : getin_etat0_dcmip2016_supercell=>getin_etat0
[345]78    ! Ad hoc interfaces
[467]79    USE etat0_academic_mod, ONLY : etat0_academic=>etat0
80    USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0
81    USE etat0_venus_mod,  ONLY : etat0_venus=>etat0
82    USE etat0_database_mod, ONLY : etat0_database=>etat0
[266]83    USE etat0_start_file_mod, ONLY : etat0_start_file=>etat0 
[149]84
[17]85    TYPE(t_field),POINTER :: f_ps(:)
[159]86    TYPE(t_field),POINTER :: f_mass(:)
[17]87    TYPE(t_field),POINTER :: f_phis(:)
88    TYPE(t_field),POINTER :: f_theta_rhodz(:)
89    TYPE(t_field),POINTER :: f_u(:)
[366]90    TYPE(t_field),POINTER :: f_geopot(:)
91    TYPE(t_field),POINTER :: f_w(:)
[17]92    TYPE(t_field),POINTER :: f_q(:)
[186]93   
[159]94    REAL(rstd),POINTER :: ps(:), mass(:,:)
[366]95    LOGICAL :: autoinit_mass, autoinit_geopot, collocated
[159]96    INTEGER :: ind,i,j,ij,l
97
98    ! most etat0 routines set ps and not mass
99    ! in that case and if caldyn_eta == eta_lag
100    ! the initial distribution of mass is taken to be the same
101    ! as what the mass coordinate would dictate
[366]102    ! however if etat0_XXX defines mass then the flag autoinit_mass must be set to .FALSE.
[159]103    ! otherwise mass will be overwritten
[366]104    autoinit_mass = (caldyn_eta == eta_lag)
[159]105
[17]106    etat0_type='jablonowsky06'
107    CALL getin("etat0",etat0_type)
108   
[345]109    !------------------- Generic interface ---------------------
[344]110    collocated=.TRUE.
[17]111    SELECT CASE (TRIM(etat0_type))
[199]112    CASE ('isothermal')
113       CALL getin_etat0_isothermal
[327]114    CASE ('temperature_profile')
115       CALL getin_etat0_temperature
[203]116    CASE ('jablonowsky06')
[344]117    CASE ('dcmip1')
118        CALL getin_etat0_dcmip1
119    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
120       CALL getin_etat0_dcmip2
[345]121    CASE ('dcmip3')
[346]122    CASE ('dcmip4')
123        CALL getin_etat0_dcmip4
[344]124    CASE ('dcmip5')
[203]125        CALL getin_etat0_dcmip5
[377]126    CASE ('bubble')
127        CALL getin_etat0_bubble
[168]128    CASE ('williamson91.6')
[366]129       autoinit_mass=.FALSE.
[204]130       CALL getin_etat0_williamson
[382]131    CASE ('dcmip2016_baroclinic_wave')
132        CALL getin_etat0_dcmip2016_baroclinic_wave
[388]133    CASE ('dcmip2016_cyclone')
134        CALL getin_etat0_dcmip2016_cyclone
135    CASE ('dcmip2016_supercell')
136        CALL getin_etat0_dcmip2016_supercell
[344]137    CASE DEFAULT
138       collocated=.FALSE.
[366]139       autoinit_mass = .FALSE.
[344]140    END SELECT
141
[345]142    !------------------- Ad hoc interfaces --------------------
[344]143    SELECT CASE (TRIM(etat0_type))
[467]144     CASE ('database')
145        CALL etat0_database(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[266]146    CASE ('start_file')
147       CALL etat0_start_file(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[54]148    CASE ('academic')
149       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[170]150    CASE ('held_suarez')
151       PRINT *,"Held & Suarez (1994) test case"
[149]152       CALL etat0_heldsz(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[325]153    CASE ('venus')
154       CALL etat0_venus(f_ps, f_phis, f_theta_rhodz, f_u, f_q)
155       PRINT *, "Venus (Lebonnois et al., 2012) test case"
[62]156   CASE DEFAULT
[344]157      IF(collocated) THEN
[366]158         CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q)
[344]159      ELSE
[468]160         PRINT*, 'Bad selector for variable etat0 <',TRIM(etat0_type),'>'// &
161            ' options are  <isothermal>, <temperature_profile>, <jablonowsky06>, <dcmip5>, <williamson91.6>,'& 
162                         //' <start_file>, <database>, <academic>, <held_suarez>, <venus>, <dcmip1>,'         &
163                         //' <dcmip2_mountain,dcmip2_schaer_noshear,dcmip2_schaer_shear>, <dcmip3>, <dcmip4>,'&
164                         //' <dcmip2016_baroclinic_wave>, <dcmip2016_cyclone>, <dcmip2016_supercell>'
[344]165         STOP
166      END IF
[54]167    END SELECT
[159]168
[366]169    IF(autoinit_mass) THEN
[159]170       DO ind=1,ndomain
[568]171          IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
[159]172          CALL swap_dimensions(ind)
173          CALL swap_geometry(ind)
174          mass=f_mass(ind); ps=f_ps(ind)
[366]175          CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps
[159]176       END DO
177    END IF
[366]178 
[54]179  END SUBROUTINE etat0
[199]180
[12]181END MODULE etat0_mod
Note: See TracBrowser for help on using the repository browser.