source: trunk/WRF.COMMON/INTERFACES/dynphy_wrf_titan_lmd/iniphysiq_mod.F @ 3404

Last change on this file since 3404 was 2367, checked in by mlefevre, 4 years ago

MESOSCALE. Corrected spelling mistake and deleted useless call

File size: 5.1 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
37
38implicit none
39
40INCLUDE 'mpif.h'
41
42REAL,intent(in) :: prad
43REAL,intent(in) :: pg
44REAL,intent(in) :: pr
45REAL,intent(in) :: pcpp
46REAL,intent(in) :: punjours
47!DOUBLE PRECISION,intent(in) :: ptimestep
48
49!real,intent(in) :: prad ! radius of the planet (m)
50!real,intent(in) :: pg ! gravitational acceleration (m/s2)
51!real,intent(in) :: pr ! ! reduced gas constant R/mu
52!real,intent(in) :: pcpp ! specific heat Cp
53!real,intent(in) :: punjours ! length (in s) of a standard day [daysec]
54integer,intent(in) :: pdayref ! reference day of for the simulation [day_ini]
55integer,intent(in) :: iflag_phys ! type of physics to be called
56
57integer :: nday=0 ! this is dummy for mesoscale (in dyn3d/control_mod)
58
59integer,intent(in) :: ngrid ! number of physics columns for this MPI process
60integer,intent(in) :: nlayer ! number of atmospheric layers
61integer,intent(in) :: nq ! number of tracers
62!real,intent(in) :: phour_ini   ! start time (fraction of day) of the run
63!0=<phour_ini<1
64real,intent(in) :: piphysiq   ! call physics every piphysiq dynamical timesteps
65!real :: latitude(ngrid),longitude(ngrid),cell_area(ngrid)
66!  real,intent(in) :: prefff ! reference surface pressure (Pa)
67!  real,intent(in) :: apf(nlayer+1) ! hybrid coordinate at interfaces
68!  real,intent(in) :: bpf(nlayer+1)
69logical :: ok_slab_ocean
70real*8 :: lat(ngrid),long(ngrid),cellarea(ngrid)
71REAL*8 :: pprad,ppg,ppr,ppcpp,ppunjours
72REAL*8 :: dummy
73  ! the common part for all planetary physics
74  !------------------------------------------
75  ! --> initialize physics distribution, global fields and geometry
76  ! (i.e. things in phy_common or dynphy_lonlat)
77
78  ! the distinct part for all planetary physics (ie. things in phystd)
79  !------------------------------------------
80
81CALL Init_phys_lmdz_para(1,1,1,MPI_COMM_WORLD)
82
83!call phys_state_var_init
84print*,'ngrid',ngrid,'nlayer',nlayer
85call init_dimphy(ngrid,nlayer)
86call phys_state_var_init(nqtot_p)
87! copy over preff , ap() and bp()
88!call ini_planete_mod(nlayer,prefff,apf,bpf)
89
90! for slab ocean, copy over some arrays
91ok_slab_ocean=.false. ! default value
92!call getin_p("ok_slab_ocean",ok_slab_ocean)
93!if (ok_slab_ocean) then
94!  call ini_surf_heat_transp(ip1jm,ip1jmp1,unsairez,fext,unsaire, &
95!                            cu,cuvsurcv,cv,cvusurcu,aire,apoln,apols, &
96!                            aireu,airev)
97!endif
98
99dummy=1.
100lat(:)=0.
101long(:)=0.
102cellarea(:)=1.
103print*,'pg',pg
104!ppunjours=punjours
105ppunjours=1.
106pprad=prad
107ppg=pg
108ppr=pr
109ppcpp=pcpp
110call inifis(ngrid,nlayer,nq,pdayref,ppunjours,nday,dummy, &
111            lat,long,cellarea,pprad,ppg,ppr,ppcpp)
112
113     open(17,file='controle.txt',form='formatted',status='old')
114     rewind(17)
115     read(17,*)
116     read(17,*)
117     read(17,*) day_ini !(tab0+3)
118     read(17,*)
119     read(17,*) !tab0+5)
120     read(17,*) omeg !(tab0+6)
121     read(17,*) !(tab0+7)
122     read(17,*) mugaz
123     read(17,*)  !(tab0+9)
124     read(17,*) daysec
125     read(17,*) dtphys !tab0+11)
126     read(17,*)
127     read(17,*)
128     read(17,*) year_day !(tab0+14)
129     read(17,*) periastr !tab0+15)
130     read(17,*) apoastr !tab0+16)
131     read(17,*) peri_day !tab0+17)
132     read(17,*) obliquit !tab0+18)
133     read(17,*) z0
134     read(17,*)
135     read(17,*)
136     read(17,*)
137     read(17,*)
138     read(17,*) emisice(1)
139     read(17,*) emisice(2)
140     read(17,*) emissiv
141     read(17,*)
142     read(17,*)
143     read(17,*)
144     read(17,*)
145     read(17,*) iceradius(1)
146     read(17,*) iceradius(2)
147     read(17,*) dtemisice(1)
148     read(17,*) dtemisice(2)
149     close(17)
150     !print*,'g',g
151
152     !emissiv(:)=EMIS
153     !qsurf(:,:) = 0.
154     print*,'check'
155     print*,'iceradius',iceradius,'dtemisice',dtemisice
156     print*,'apoastr,periastr,year_day,peri_day,obliq',apoastr,periastr,year_day,peri_day,obliquit
157     print*,'emissiv',emissiv
158     print*,'mugaz',mugaz
159     
160end subroutine iniphysiq
161
162
163END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.