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

Last change on this file since 2903 was 2900, checked in by romain.vande, 3 years ago

Mars PCM:
Following r2896, further implementation of subslope parametrisation.
Carefull ! This is a devolpment revision and it still need improvements and tests.
However, this commit should not change anything for nslope=1.
Only nslope=1 is possible for now!
Utilitaries are not adapted yet.
Dimension of some variables (30 listed below) is changed to add the nslope dimension.
Outputs (diagfi and restartfi) are not changed yet.
nslope is now read and written in the startfi.nc

Changed variables:
_ In surfdat_h:

  • qsurf
  • tsurf
  • watercap
  • emis
  • capcal
  • fluxgrd

_ In comsoil_h

  • tsoil
  • mthermdiff
  • thermdiff
  • coefd
  • alph
  • beta

_ In dimradmars_mod

  • albedo
  • fluxrad_sky
  • fluxrad

_ In physiq_mod

  • inertiesoil
  • fluxsurf_lw
  • fluxsurf_dn_sw
  • dqsurf
  • zdtsurf
  • zdtsdif
  • zdtsurfc
  • zdqsdif
  • zdqsc
  • dwatercap
  • dwatercap_dif
  • zflubid
  • fluxsurf_dn_sw_tot
  • inertiedat_tmp

New variables called VAR_meshavg correspond to the mesh average over all the subslope distribution of the variable

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