source: trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90 @ 4008

Last change on this file since 4008 was 4008, checked in by aslmd, 2 weeks ago

MESOSCALE: use precompiling flags to hide instructions related to parallel computations (we consider physics as being like a 1D model without any attached dynamical core when we compile).

File size: 6.7 KB
Line 
1MODULE phys_state_var_init_mod
2
3CONTAINS
4
5      SUBROUTINE phys_state_var_init(ngrid,nlayer,nq,tname, &
6                                     day_ini,day_end,hour_ini,pdaysec,ptimestep, &
7                                     prad,pg,pr,pcpp, &
8                                     dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
9
10!=======================================================================
11!
12!   purpose:
13!   -------
14!
15!   Allocate arrays in modules
16!   Fill geometrical arrays
17!   Fill a first set of physical constants
18!   -- was done previously in inifis
19!
20!=======================================================================
21!   
22!   authors: Ehouarn Millour and Aymeric Spiga
23!            14/04/2014
24!
25!   arguments:
26!   ----------
27!
28!   input:
29!   ------
30!
31!    ngrid                 Size of the horizontal grid.
32!    nlayer                Number of vertical layers.
33!    nq                    Number of tracers.
34!
35!=======================================================================
36
37      use init_print_control_mod, only: init_print_control
38      use slope_mod, only: ini_slope_mod,end_slope_mod
39      use comsaison_h, only: ini_comsaison_h,end_comsaison_h
40      use surfdat_h, only: ini_surfdat_h,end_surfdat_h
41      use comgeomfi_h, only: ini_comgeomfi_h,end_comgeomfi_h
42      use comsoil_h, only: ini_comsoil_h,end_comsoil_h
43      use dimradmars_mod, only: ini_dimradmars_mod,end_dimradmars_mod
44      use yomlw_h, only: ini_yomlw_h,end_yomlw_h
45      use conc_mod, only: ini_conc_mod,end_conc_mod
46      use turb_mod, only: ini_turb_mod,end_turb_mod
47      use comcstfi_h, only: init_comcstfi_h
48      use tracer_mod, only: ini_tracer_mod,end_tracer_mod
49      use time_phylmdz_mod, only: init_time
50      use compute_dtau_mod, only: ini_compute_dtau_mod, &
51                                  end_compute_dtau_mod
52      use rocketduststorm_mod, only: ini_rocketduststorm_mod, &
53                                     end_rocketduststorm_mod
54      use calchim_mod, only: ini_calchim_mod,end_calchim_mod
55      use watercloud_mod, only: ini_watercloud_mod, &
56                                end_watercloud_mod
57      use nonoro_gwd_ran_mod, only: ini_nonoro_gwd_ran, &
58                                    end_nonoro_gwd_ran
59      use nonoro_gwd_mix_mod, only: ini_nonoro_gwd_mix, &
60                                    end_nonoro_gwd_mix
61      use dust_param_mod, only: ini_dust_param_mod, &
62                                end_dust_param_mod
63      use dust_rad_adjust_mod, only: ini_dust_rad_adjust_mod, &
64                                     end_dust_rad_adjust_mod
65      use comslope_mod, ONLY: nslope,end_comslope_h,ini_comslope_h
66      use paleoclimate_mod, ONLY: end_paleoclimate_h,ini_paleoclimate_h
67      use netcdf
68#ifndef MESOSCALE
69      USE mod_phys_lmdz_para, ONLY: is_master,bcast
70#endif
71
72      IMPLICIT NONE
73     
74      integer,      intent(in) :: ngrid, nlayer, nq
75      character(*), intent(in) :: tname(nq)
76      integer,      intent(in) :: day_ini, day_end
77      real,         intent(in) :: hour_ini
78      real,         intent(in) :: pdaysec, ptimestep, prad, pg, pr, pcpp
79!MVals isotopes
80      integer,      intent(in) :: dyn_nqperes
81      integer,      intent(in) :: dyn_nqfils(nq)
82      character(10) :: filename  ! name of the startfi.nc
83      integer       :: ncid, status, nslope_dim_id
84      integer       :: nslope_read
85
86
87      filename = "startfi.nc"
88#ifndef MESOSCALE
89      if(is_master) then
90#endif
91        status = nf90_open(filename, nf90_nowrite, ncid)
92        if (status /= nf90_noerr) then
93          nslope=1
94        else
95          status = nf90_inq_dimid(ncid, "nslope", nslope_dim_id)
96          if (status /= nf90_noerr) then
97            nslope=1
98          else
99            status = nf90_inquire_dimension(ncid, nslope_dim_id, len = nslope_read)
100            if (status /= nf90_noerr) then
101              call abort_physic("phys_state_var_init","nslope present but not readable",1)
102            else
103              nslope=nslope_read
104            endif
105          endif
106        endif
107#ifndef MESOSCALE
108      endif
109      call bcast(nslope)
110#endif
111
112      ! set dimension and allocate arrays in tracer_mod
113      call end_tracer_mod
114      call ini_tracer_mod(nq,tname,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
115
116      ! initialize "print_control" constants/flags ("prt_level","lunout", etc.)
117      call init_print_control
118     
119      ! set parameters in comcstfi_h
120      call init_comcstfi_h(prad,pcpp,pg,pr)
121
122      ! Initialize some "temporal and calendar" related variables
123      call init_time(day_ini,day_end,hour_ini,pdaysec,ptimestep)
124
125      ! allocate "slope_mod" arrays
126      call end_slope_mod
127      call ini_slope_mod(ngrid)
128
129      ! allocate "comsaison_h" arrays
130      call end_comsaison_h
131      call ini_comsaison_h(ngrid)
132
133      ! allocate "surfdat_h" arrays
134      call end_surfdat_h
135      call ini_surfdat_h(ngrid,nq,nslope)
136
137      ! allocate "comgeomfi_h" arrays
138      call end_comgeomfi_h
139      call ini_comgeomfi_h(ngrid)
140
141      ! allocate "comsoil_h" arrays
142      call end_comsoil_h
143      call ini_comsoil_h(ngrid,nslope)
144
145      ! set some variables in "dimradmars_mod"
146      call end_dimradmars_mod
147      call ini_dimradmars_mod(ngrid,nlayer,nslope)
148
149      ! allocate arrays in "yomlw_h"
150      call end_yomlw_h
151      call ini_yomlw_h(ngrid)
152
153      ! allocate arrays in "conc_mod" (aeronomars)
154      call end_conc_mod
155      call ini_conc_mod(ngrid,nlayer)
156
157      ! allocate arrays in "turb_mod"
158      call end_turb_mod
159      call ini_turb_mod(ngrid,nlayer)
160
161      ! allocate arrays in "compute_dtau_mod":
162      call end_compute_dtau_mod
163      call ini_compute_dtau_mod(ngrid)
164
165      ! allocate arrays in "rocketduststorm_mod":
166      call end_rocketduststorm_mod
167      call ini_rocketduststorm_mod(ngrid)
168
169      ! allocate arrays in "calchim_mod" (aeronomars)
170      call end_calchim_mod
171      call ini_calchim_mod(ngrid,nlayer,nq)
172
173      ! allocate arrays in "watercloud_mod"
174      call end_watercloud_mod
175      call ini_watercloud_mod(ngrid,nlayer,nq)
176
177      ! allocate arrays in "nonoro_gwd_ran_mod"
178      call end_nonoro_gwd_ran
179      call ini_nonoro_gwd_ran(ngrid,nlayer)
180
181      ! allocate arrays in "nonoro_gwd_mix_mod"
182      call end_nonoro_gwd_mix
183      call ini_nonoro_gwd_mix(ngrid,nlayer,nq)
184
185      ! allocate arrays in "dust_param_mod"
186      call end_dust_param_mod
187      call ini_dust_param_mod(ngrid)
188     
189      ! allocate arrays in "dust_rad_adjust_mod"
190      call end_dust_rad_adjust_mod
191      call ini_dust_rad_adjust_mod(ngrid)
192
193      ! allocate arrays in "comslope_mod"
194      call end_comslope_h
195      call ini_comslope_h(ngrid,nslope)
196
197      ! allocate arrays in "paleoclimate_mod"
198      call end_paleoclimate_h
199      call ini_paleoclimate_h(ngrid,nslope)
200
201      END SUBROUTINE phys_state_var_init
202
203END MODULE phys_state_var_init_mod
Note: See TracBrowser for help on using the repository browser.