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

Last change on this file since 3026 was 2994, checked in by llange, 18 months ago

MARS PCM
Introduce paleoclimate modul which will contains all the stuff used for
the paleoclimates studies. For now, just the lag layer thicknesses (for
preliminary tests with the 1D model).
LL

File size: 6.4 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: pi,rad,cpp,g,r,rcp
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      pi=2.*asin(1.)
112      rad=prad
113      cpp=pcpp
114      g=pg
115      r=pr
116      rcp=r/cpp
117
118      ! Initialize some "temporal and calendar" related variables
119      call init_time(day_ini,day_end,hour_ini,pdaysec,ptimestep)
120
121      ! allocate "slope_mod" arrays
122      call end_slope_mod
123      call ini_slope_mod(ngrid)
124
125      ! allocate "comsaison_h" arrays
126      call end_comsaison_h
127      call ini_comsaison_h(ngrid)
128
129      ! allocate "surfdat_h" arrays
130      call end_surfdat_h
131      call ini_surfdat_h(ngrid,nq,nslope)
132
133      ! allocate "comgeomfi_h" arrays
134      call end_comgeomfi_h
135      call ini_comgeomfi_h(ngrid)
136
137      ! allocate "comsoil_h" arrays
138      call end_comsoil_h
139      call ini_comsoil_h(ngrid,nslope)
140
141      ! set some variables in "dimradmars_mod"
142      call end_dimradmars_mod
143      call ini_dimradmars_mod(ngrid,nlayer,nslope)
144
145      ! allocate arrays in "yomlw_h"
146      call end_yomlw_h
147      call ini_yomlw_h(ngrid)
148
149      ! allocate arrays in "conc_mod" (aeronomars)
150      call end_conc_mod
151      call ini_conc_mod(ngrid,nlayer)
152
153      ! allocate arrays in "turb_mod"
154      call end_turb_mod
155      call ini_turb_mod(ngrid,nlayer)
156
157      ! allocate arrays in "compute_dtau_mod":
158      call end_compute_dtau_mod
159      call ini_compute_dtau_mod(ngrid)
160
161      ! allocate arrays in "rocketduststorm_mod":
162      call end_rocketduststorm_mod
163      call ini_rocketduststorm_mod(ngrid)
164
165      ! allocate arrays in "calchim_mod" (aeronomars)
166      call end_calchim_mod
167      call ini_calchim_mod(ngrid,nlayer,nq)
168
169      ! allocate arrays in "watercloud_mod"
170      call end_watercloud_mod
171      call ini_watercloud_mod(ngrid,nlayer,nq)
172
173      ! allocate arrays in "nonoro_gwd_ran_mod"
174      call end_nonoro_gwd_ran
175      call ini_nonoro_gwd_ran(ngrid,nlayer)
176
177      ! allocate arrays in "dust_param_mod"
178      call end_dust_param_mod
179      call ini_dust_param_mod(ngrid)
180     
181      ! allocate arrays in "dust_rad_adjust_mod"
182      call end_dust_rad_adjust_mod
183      call ini_dust_rad_adjust_mod(ngrid)
184
185      ! allocate arrays in "comslope_mod"
186      call end_comslope_h
187      call ini_comslope_h(ngrid,nslope)
188
189      ! allocate arrays in "paleoclimate_mod"
190      call end_paleoclimate_h
191      call ini_paleoclimate_h(ngrid,nslope)
192
193      END SUBROUTINE phys_state_var_init
194
195END MODULE phys_state_var_init_mod
Note: See TracBrowser for help on using the repository browser.