source: trunk/WRF.COMMON/INTERFACES_V4/dynphy_wrf_titan_lmd/iniphysiq_mod.F @ 3661

Last change on this file since 3661 was 3661, checked in by emoisan, 4 months ago

Titan CRM:
Add Titan interface in INTERFACES_V4
Adapt module_model_constants.F to Titan
Add new tracer_mode for Titan (CH4 scalar)
Add new communication of variables between LMDZ.TITAN and WRF
Allow microphysics for Mesoscale in physiq_mod.F90
EMo

File size: 5.4 KB
Line 
1MODULE iniphysiq_mod
2
3CONTAINS
4
5subroutine iniphysiq(ngrid,nlayer,nq,piphysiq,&
6                     punjours, pdayref, &
7                     prad,pg,pr,pcpp,iflag_phys)
8
9!use control_mod, only: nday
10!use surf_heat_transp_mod, only: ini_surf_heat_transp
11!use infotrac, only : nqtot ! number of advected tracers
12!USE comvert_mod, ONLY: ap,bp,preff
13use inifis_mod, only: inifis
14use ioipsl_getin_p_mod, only: getin_p
15
16!use inigeomphy_mod, only: inigeomphy
17!use geometry_mod, only: cell_area, & ! physics grid area (m2)
18!                        longitude, & ! longitudes (rad)
19!                        latitude ! latitudes (rad)
20! necessary to get klon_omp
21!USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
22USE mod_phys_lmdz_para, ONLY: Init_phys_lmdz_para
23USE dimphy, ONLY: init_dimphy
24USE phys_state_var_mod
25!use planete_mod, only: year_day, periastr, apoastr, peri_day,&
26!                       obliquit, z0, lmixmin, emin_turb
27!                       init_planete_mod
28use planete_mod
29use time_phylmdz_mod, only: dtphys, daysec,day_ini
30use planete_mod, only: year_day, periastr, apoastr, peri_day,&
31                   obliquit, z0, lmixmin, emin_turb
32use surfdat_h,  only: emissiv,iceradius, &
33                    emisice,dtemisice
34use comcstfi_mod, only: omeg,mugaz
35use tracer_h, only: nqtot_p
36!use comm_wrf, only : allocate_comm_wrf
37USE variables_mod, only: zdt_split
38use mod_grid_phy_lmdz, only: nbp_lev, klon_glo
39
40implicit none
41
42INCLUDE 'mpif.h'
43
44REAL,intent(in) :: prad
45REAL,intent(in) :: pg
46REAL,intent(in) :: pr
47REAL,intent(in) :: pcpp
48REAL,intent(in) :: punjours
49!DOUBLE PRECISION,intent(in) :: ptimestep
50
51!real,intent(in) :: prad ! radius of the planet (m)
52!real,intent(in) :: pg ! gravitational acceleration (m/s2)
53!real,intent(in) :: pr ! ! reduced gas constant R/mu
54!real,intent(in) :: pcpp ! specific heat Cp
55!real,intent(in) :: punjours ! length (in s) of a standard day [daysec]
56integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini]
57integer,intent(in) :: iflag_phys ! type of physics to be called
58
59integer :: nday=0 ! this is dummy for mesoscale (in dyn3d/control_mod)
60
61integer,intent(in) :: ngrid ! number of physics columns for this MPI process
62integer,intent(in) :: nlayer ! number of atmospheric layers
63integer,intent(in) :: nq ! number of tracers
64!real,intent(in) :: phour_ini   ! start time (fraction of day) of the run
65!0=<phour_ini<1
66real,intent(in) :: piphysiq   ! call physics every piphysiq dynamical timesteps
67!real :: latitude(ngrid),longitude(ngrid),cell_area(ngrid)
68!  real,intent(in) :: prefff ! reference surface pressure (Pa)
69!  real,intent(in) :: apf(nlayer+1) ! hybrid coordinate at interfaces
70!  real,intent(in) :: bpf(nlayer+1)
71logical :: ok_slab_ocean
72real*8 :: lat(ngrid),long(ngrid),cellarea(ngrid)
73REAL*8 :: pprad,ppg,ppr,ppcpp,ppunjours
74!REAL*8 :: dummy
75  ! the common part for all planetary physics
76  !------------------------------------------
77  ! --> initialize physics distribution, global fields and geometry
78  ! (i.e. things in phy_common or dynphy_lonlat)
79
80  ! the distinct part for all planetary physics (ie. things in phystd)
81  !------------------------------------------
82
83nbp_lev = nlayer ! emoisan
84klon_glo = 1 !emoisan !we run the physics as if we were in 1D
85CALL Init_phys_lmdz_para(1,1,1,MPI_COMM_WORLD)
86
87!call phys_state_var_init
88print*,'ngrid',ngrid,'nlayer',nlayer
89call init_dimphy(ngrid,nlayer)
90call phys_state_var_init(nqtot_p)
91! copy over preff , ap() and bp()
92!call ini_planete_mod(nlayer,prefff,apf,bpf)
93
94! for slab ocean, copy over some arrays
95ok_slab_ocean=.false. ! default value
96!call getin_p("ok_slab_ocean",ok_slab_ocean)
97!if (ok_slab_ocean) then
98!  call ini_surf_heat_transp(ip1jm,ip1jmp1,unsairez,fext,unsaire, &
99!                            cu,cuvsurcv,cv,cvusurcu,aire,apoln,apols, &
100!                            aireu,airev)
101!endif
102
103!dummy=1. !used before instead of zdt_split (EMoi)
104lat(:)=0.
105long(:)=0.
106cellarea(:)=1.
107print*,'pg',pg
108!ppunjours=punjours
109ppunjours=1.
110pprad=prad
111ppg=pg
112ppr=pr
113ppcpp=pcpp
114call inifis(ngrid,nlayer,nq,pdayref,ppunjours,nday,zdt_split, &
115            lat,long,cellarea,pprad,ppg,ppr,ppcpp)
116
117     open(17,file='controle.txt',form='formatted',status='old')
118     rewind(17)
119     read(17,*)
120     read(17,*)
121     read(17,*) day_ini !(tab0+3)
122     read(17,*)
123     read(17,*) !tab0+5)
124     read(17,*) !omeg !(tab0+6)
125     read(17,*) !(tab0+7)
126     read(17,*) !mugaz
127     read(17,*)  !(tab0+9)
128     read(17,*) daysec
129     read(17,*) dtphys !tab0+11)
130     read(17,*)
131     read(17,*)
132     read(17,*) year_day !(tab0+14)
133     read(17,*) periastr !tab0+15)
134     read(17,*) apoastr !tab0+16)
135     read(17,*) peri_day !tab0+17)
136     read(17,*) obliquit !tab0+18)
137     read(17,*) z0
138     read(17,*)
139     read(17,*)
140     read(17,*)
141     read(17,*)
142     read(17,*) emisice(1)
143     read(17,*) emisice(2)
144     read(17,*) emissiv
145     read(17,*)
146     read(17,*)
147     read(17,*)
148     read(17,*)
149     read(17,*) iceradius(1)
150     read(17,*) iceradius(2)
151     read(17,*) dtemisice(1)
152     read(17,*) dtemisice(2)
153     close(17)
154     !print*,'g',g
155
156     !emissiv(:)=EMIS
157!    cloudfrac(:,:)=0.5
158!    totcloudfrac(:)=0.5
159!    hice(:)=0.
160!    rnat(:)=0.
161!    pctsrf_sic(:)=0.
162!    tsea_ice(:)=0.
163     !qsurf(:,:) = 0.
164     print*,'check'
165     print*,'iceradius',iceradius,'dtemisice',dtemisice
166     print*,'apoastr,periastr,year_day,peri_day,obliq',apoastr,periastr,year_day,peri_day,obliquit
167     print*,'emissiv',emissiv
168     print*,'mugaz',mugaz
169     
170end subroutine iniphysiq
171
172
173END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.