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

Last change on this file since 3118 was 3095, checked in by emillour, 14 months ago

Mars PCM:
Some code tidying:
Made pi in module comcstfi_h a parameter (and not a variable recomputed at
various points by various routines) and added module routine init_comcstfi_h
to cleanly initialize module variables.
Moved iniorbit.F to be a module routine of planete_h since it initializes
(some of ) the module variables it contains.
EM

File size: 6.3 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 dust_param_mod, only: ini_dust_param_mod, &
60                                end_dust_param_mod
61      use dust_rad_adjust_mod, only: ini_dust_rad_adjust_mod, &
62                                     end_dust_rad_adjust_mod
63      use comslope_mod, ONLY: nslope,end_comslope_h,ini_comslope_h
64      use paleoclimate_mod, ONLY: end_paleoclimate_h,ini_paleoclimate_h
65      use netcdf
66      USE mod_phys_lmdz_para, ONLY: is_master,bcast
67
68      IMPLICIT NONE
69     
70      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
71      CHARACTER(len=*),INTENT(IN) :: tname(nq)
72      INTEGER,INTENT(IN) :: day_ini, day_end
73      REAL,INTENT(IN) :: hour_ini
74      REAL,INTENT(IN) :: pdaysec,ptimestep,prad,pg,pr,pcpp
75!MVals isotopes
76      INTEGER,INTENT(in) :: dyn_nqperes
77      INTEGER,INTENT(in) :: dyn_nqfils(nq)
78      character(len=10) :: filename  ! name of the startfi.nc
79      integer :: ncid, status, nslope_dim_id
80      integer :: nslope_read
81
82      filename="startfi.nc"
83      if(is_master) then
84        status = nf90_open(filename, nf90_nowrite, ncid)
85        if (status /= nf90_noerr) then
86          nslope=1
87        else
88          status = nf90_inq_dimid(ncid, "nslope", nslope_dim_id)
89          if (status /= nf90_noerr) then
90            nslope=1
91          else
92            status = nf90_inquire_dimension(ncid, nslope_dim_id, len = nslope_read)
93            if (status /= nf90_noerr) then
94              call abort_physic("phys_state_var_init","nslope present but not readable",1)
95            else
96              nslope=nslope_read
97            endif
98          endif
99        endif
100      endif
101      call bcast(nslope)
102
103      ! set dimension and allocate arrays in tracer_mod
104      call end_tracer_mod
105      call ini_tracer_mod(nq,tname,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
106
107      ! initialize "print_control" constants/flags ("prt_level","lunout", etc.)
108      call init_print_control
109     
110      ! set parameters in comcstfi_h
111      call init_comcstfi_h(prad,pcpp,pg,pr)
112
113      ! Initialize some "temporal and calendar" related variables
114      call init_time(day_ini,day_end,hour_ini,pdaysec,ptimestep)
115
116      ! allocate "slope_mod" arrays
117      call end_slope_mod
118      call ini_slope_mod(ngrid)
119
120      ! allocate "comsaison_h" arrays
121      call end_comsaison_h
122      call ini_comsaison_h(ngrid)
123
124      ! allocate "surfdat_h" arrays
125      call end_surfdat_h
126      call ini_surfdat_h(ngrid,nq,nslope)
127
128      ! allocate "comgeomfi_h" arrays
129      call end_comgeomfi_h
130      call ini_comgeomfi_h(ngrid)
131
132      ! allocate "comsoil_h" arrays
133      call end_comsoil_h
134      call ini_comsoil_h(ngrid,nslope)
135
136      ! set some variables in "dimradmars_mod"
137      call end_dimradmars_mod
138      call ini_dimradmars_mod(ngrid,nlayer,nslope)
139
140      ! allocate arrays in "yomlw_h"
141      call end_yomlw_h
142      call ini_yomlw_h(ngrid)
143
144      ! allocate arrays in "conc_mod" (aeronomars)
145      call end_conc_mod
146      call ini_conc_mod(ngrid,nlayer)
147
148      ! allocate arrays in "turb_mod"
149      call end_turb_mod
150      call ini_turb_mod(ngrid,nlayer)
151
152      ! allocate arrays in "compute_dtau_mod":
153      call end_compute_dtau_mod
154      call ini_compute_dtau_mod(ngrid)
155
156      ! allocate arrays in "rocketduststorm_mod":
157      call end_rocketduststorm_mod
158      call ini_rocketduststorm_mod(ngrid)
159
160      ! allocate arrays in "calchim_mod" (aeronomars)
161      call end_calchim_mod
162      call ini_calchim_mod(ngrid,nlayer,nq)
163
164      ! allocate arrays in "watercloud_mod"
165      call end_watercloud_mod
166      call ini_watercloud_mod(ngrid,nlayer,nq)
167
168      ! allocate arrays in "nonoro_gwd_ran_mod"
169      call end_nonoro_gwd_ran
170      call ini_nonoro_gwd_ran(ngrid,nlayer)
171
172      ! allocate arrays in "dust_param_mod"
173      call end_dust_param_mod
174      call ini_dust_param_mod(ngrid)
175     
176      ! allocate arrays in "dust_rad_adjust_mod"
177      call end_dust_rad_adjust_mod
178      call ini_dust_rad_adjust_mod(ngrid)
179
180      ! allocate arrays in "comslope_mod"
181      call end_comslope_h
182      call ini_comslope_h(ngrid,nslope)
183
184      ! allocate arrays in "paleoclimate_mod"
185      call end_paleoclimate_h
186      call ini_paleoclimate_h(ngrid,nslope)
187
188      END SUBROUTINE phys_state_var_init
189
190END MODULE phys_state_var_init_mod
Note: See TracBrowser for help on using the repository browser.