source: trunk/LMDZ.GENERIC/libf/phystd/kcm1d.F90 @ 724

Last change on this file since 724 was 716, checked in by rwordsworth, 13 years ago

Mainly updates to radiative transfer and gas management scheme.
Most CIA data now read from standard HITRAN datafiles. For the H2O
continuum, two options have been added: the standard CKD continuum,
and the empirical formula in PPC (Pierrehumbert 2010). Use the toggle
'H2Ocont_simple' in callphys.def to choose.

Note to Martians: I've changed the default values of 'sedimentation' and
'co2cond' in inifis to false. Both these are defined in the standard deftank
callphys.def file, so there shouldn't be any compatibility problems.

  • Property svn:executable set to *
File size: 10.1 KB
Line 
1program kcm1d
2
3  use radinc_h,      only: NAERKIND
4  use radcommon_h,   only: L_NSPECTI, L_NSPECTV, sigma
5  use watercommon_h, only: mH2O
6  use ioipsl_getincom
7
8  implicit none
9
10  !==================================================================
11  !     
12  !     Purpose
13  !     -------
14  !     Run the universal model radiative transfer once in a 1D column.
15  !     Useful for climate evolution studies etc.
16  !     
17  !     It can be compiled with a command like (e.g. for 25 layers):
18  !                                  "makegcm -p std -d 25 kcm1d"
19  !     It requires the files "callphys.def", "gases.def"
20  !     "traceur.def", and "run.def" with a line "INCLUDEDEF=callphys.def"
21  !
22  !     Authors
23  !     -------
24  !     R. Wordsworth
25  !
26  !==================================================================
27
28#include "dimensions.h"
29#include "dimphys.h"
30#include "callkeys.h"
31#include "comcstfi.h"
32#include "planete.h"
33#include "comsaison.h"
34#include "control.h"
35#include "advtrac.h"
36
37  ! --------------------------------------------------------------
38  !  Declarations
39  ! --------------------------------------------------------------
40
41  integer nlayer,nlevel,nq
42  integer ilay,ilev,iq,iw,iter
43  real play(nlayermx)     ! Pressure at the middle of the layers [Pa]
44  real zlay(nlayermx)     ! Altitude at middle of the layers [km]
45  real plev(nlayermx+1)   ! Intermediate pressure levels [Pa]
46  real temp(nlayermx)     ! temperature at the middle of the layers [K]
47  real q(nlayermx,nqmx)   ! tracer mixing ratio [kg/kg]
48  real vmr(nlayermx,nqmx) ! tracer mixing ratio [mol/mol]
49  real qsurf(nqmx)        ! tracer surface budget [kg/kg] ????
50  real psurf,psurf_n,tsurf     
51
52  real emis, albedo
53
54  real muvar(nlayermx+1)
55
56  real dtsw(nlayermx) ! heating rate (K/s) due to SW
57  real dtlw(nlayermx) ! heating rate (K/s) due to LW
58  real fluxsurf_lw   ! incident LW flux to surf (W/m2)
59  real fluxtop_lw    ! outgoing LW flux to space (W/m2)
60  real fluxsurf_sw   ! incident SW flux to surf (W/m2)
61  real fluxabs_sw    ! SW flux absorbed by planet (W/m2)
62  real fluxtop_dn    ! incident top of atmosphere SW flux (W/m2)
63
64  ! not used
65  real reffrad(nlayermx,naerkind)
66  real nueffrad(nlayermx,naerkind)
67  real cloudfrac(nlayermx)
68  real totcloudfrac
69  real tau_col
70
71  real dTstrat
72  real aerosol(nlayermx,naerkind) ! aerosol tau (kg/kg)
73  real OLR_nu(ngridmx,L_NSPECTI)
74  real OSR_nu(ngridmx,L_NSPECTV)
75  real Eatmtot
76
77  integer ierr
78  logical firstcall,lastcall,global1d
79
80  ! --------------
81  ! Initialisation
82  ! --------------
83
84  pi=2.E+0*asin(1.E+0)
85
86  reffrad(:,:)  = 0.0
87  nueffrad(:,:) = 0.0
88  cloudfrac(:)  = 0.0
89  totcloudfrac  = 0.0
90
91
92  nlayer=nlayermx
93  nlevel=nlayer+1
94
95
96  !  Load parameters from "run.def"
97  ! -------------------------------
98
99  ! check if 'kcm1d.def' file is around (otherwise reading parameters
100  ! from callphys.def via getin() routine won't work.)
101  open(90,file='kcm1d.def',status='old',form='formatted',&
102       iostat=ierr)
103  if (ierr.ne.0) then
104     write(*,*) 'Cannot find required file "kcm1d.def"'
105     write(*,*) '  (which should contain some input parameters'
106     write(*,*) '   along with the following line:'
107     write(*,*) '   INCLUDEDEF=callphys.def'
108     write(*,*) '   )'
109     write(*,*) ' ... might as well stop here ...'
110     stop
111  else
112     close(90)
113  endif
114
115! now, run.def is needed anyway. so we create a dummy temporary one
116! for ioipsl to work. if a run.def is already here, stop the
117! program and ask the user to do a bit of cleaning
118  open(90,file='run.def',status='old',form='formatted',&
119       iostat=ierr)
120  if (ierr.eq.0) then
121     close(90)
122     write(*,*) 'There is already a run.def file.'
123     write(*,*) 'This is not compatible with 1D runs.'
124     write(*,*) 'Please remove the file and restart the run.'
125     write(*,*) 'Runtime parameters are supposed to be in kcm1d.def'
126     stop
127  else
128     call system('touch run.def')
129     call system("echo 'INCLUDEDEF=callphys.def' >> run.def")
130     call system("echo 'INCLUDEDEF=kcm1d.def' >> run.def")
131  endif
132
133  global1d = .false. ! default value
134  call getin("global1d",global1d)
135  if(.not.global1d)then
136     print*,'Error, kcm1d must have global1d=.true. in kcm1d.def!'
137     stop
138  end if
139
140  psurf_n=100000. ! default value for psurf
141  print*,'Dry surface pressure (Pa)?'
142  call getin("psurf",psurf_n)
143  write(*,*) " psurf = ",psurf_n
144
145! OK. now that run.def has been read once -- any variable is in memory.
146! so we can dump the dummy run.def
147  call system("rm -rf run.def")
148
149  tsurf=300.0 ! default value for tsurf
150  print*,'Surface temperature (K)?'
151  call getin("tref",tsurf)
152  write(*,*) " tsurf = ",tsurf
153
154  g=10.0 ! default value for g
155  print*,'Gravity ?'
156  call getin("g",g)
157  write(*,*) " g = ",g
158
159  periastr = 1.0
160  apoastr  = 1.0
161  print*,'Periastron (AU)?'
162  call getin("periastr",periastr)
163  write(*,*) "periastron = ",periastr
164  dist_star = periastr
165  fract     = 0.5
166  print*,'Apoastron (AU)?'
167  call getin("apoastr",apoastr)
168  write(*,*) "apoastron = ",apoastr
169
170  albedo=0.2 ! default value for albedo
171  print*,'Albedo of bare ground?'
172  call getin("albedo",albedo)
173  write(*,*) " albedo = ",albedo
174
175  emis=1.0 ! default value for emissivity
176  PRINT *,'Emissivity of bare ground ?'
177  call getin("emis",emis)
178  write(*,*) " emis = ",emis
179
180  pceil=100.0 ! Pascals
181  PRINT *,'Ceiling pressure (Pa) ?'
182  call getin("pceil",pceil)
183  write(*,*) " pceil = ", pceil
184
185  mugaz=0.
186  cpp=0.
187
188  check_cpp_match = .false.
189  call getin("check_cpp_match",check_cpp_match)
190  if (check_cpp_match) then
191     print*,"In 1D modeling, check_cpp_match is supposed to be F"
192     print*,"Please correct callphys.def"
193     stop
194  endif
195
196  call su_gases
197  call calc_cpp_mugaz
198
199  call inifis(1,llm,0,86400.0,1.0,0.0,0.0,1.0,rad,g,r,cpp)
200
201  ! Tracer initialisation
202  ! ---------------------
203  if (tracer) then
204     ! load tracer names from file 'traceur.def'
205     open(90,file='traceur.def',status='old',form='formatted',&
206          iostat=ierr)
207     if (ierr.eq.0) then
208        write(*,*) "kcm1d: Reading file traceur.def"
209        ! read number of tracers:
210        read(90,*,iostat=ierr) nq
211        if (ierr.ne.0) then
212           write(*,*) "kcm1d: error reading number of tracers"
213           write(*,*) "   (first line of traceur.def) "
214           stop
215        else
216           ! check that the number of tracers is indeed nqmx
217           if (nq.ne.nqmx) then
218              write(*,*) "kcm1d: error, wrong number of tracers:"
219              write(*,*) "nq=",nq," whereas nqmx=",nqmx
220              stop
221           endif
222        endif
223
224        do iq=1,nq
225           ! minimal version, just read in the tracer names, 1 per line
226           read(90,*,iostat=ierr) tnom(iq)
227           if (ierr.ne.0) then
228              write(*,*) 'kcm1d: error reading tracer names...'
229              stop
230           endif
231        enddo !of do iq=1,nq
232     endif
233
234     call initracer()
235
236  endif
237
238
239  do iq=1,nqmx
240     do ilay=1,nlayer
241        q(ilay,iq) = 0.
242     enddo
243  enddo
244
245  do iq=1,nqmx
246     qsurf(iq) = 0.
247  enddo
248
249  firstcall = .true.
250  lastcall  = .false.
251
252  iter    = 1
253  Tstrat  = 150.0
254  dTstrat = 1000.0
255
256  ! ---------
257  ! Run model
258  ! ---------
259  !do
260     psurf = psurf_n
261
262     !    Create vertical profiles
263     call kcmprof_fn(psurf,qsurf(1),tsurf,    &
264          tstrat,play,plev,zlay,temp,q(:,1),muvar(1))
265
266     !    Run radiative transfer
267     call callcorrk(ngridmx,nlayer,q,nqmx,qsurf,      &
268          albedo,emis,mu0,plev,play,temp,                    &
269          tsurf,fract,dist_star,aerosol,muvar,         &
270          dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,    &
271          fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,reffrad,tau_col,  &
272          cloudfrac,totcloudfrac,.false.,firstcall,lastcall)
273
274     !    Iterate stratospheric temperature
275     print*,'Tstrat = ',Tstrat
276     dTstrat = Tstrat
277     !Tstrat  = Tsurf*(0.2786*(psurf/100000.)**(-1.123))**0.25
278     ! skin temperature (gray approx.) using analytic pure H2 expression
279     !Tstrat  = (fluxabs_sw/(2*sigma))**0.25 ! skin temperature (gray approx.)
280     Tstrat  = (fluxtop_lw/(2*sigma))**0.25 ! skin temperature (gray approx.)
281     dTstrat = dTstrat-Tstrat
282
283     !if(abs(dTstrat).lt.1.0)then
284     !   print*,'dTstrat = ',dTstrat
285     !   exit
286     !endif
287
288     !iter=iter+1
289     !if(iter.eq.100)then
290     !   print*,'Stratosphere failed to converge after'
291     !   print*,'100 iteration, aborting run.'
292     !   call abort
293     !endif
294
295  !end do
296
297  ! Run radiative transfer one last time to get OLR,OSR
298  firstcall=.false.
299  lastcall=.true.
300  call callcorrk(ngridmx,nlayer,q,nqmx,qsurf,      &
301       albedo,emis,mu0,plev,play,temp,                    &
302       tsurf,fract,dist_star,aerosol,muvar,         &
303       dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,    &
304       fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,             &
305       reffrad,tau_col,  &
306       cloudfrac,totcloudfrac,.false.,firstcall,lastcall)
307
308
309  ! Calculate total atmospheric energy
310  Eatmtot=0.0
311  !  call calcenergy_kcm(tsurf,temp,play,plev,qsurf,&
312  !     q(:,1),muvar,Eatmtot)
313
314  ! ------------------------
315  ! Save data to ascii files
316  ! ------------------------
317
318  print*,'Saving profiles...'
319  open(115,file='profpres.out',form='formatted')
320  open(116,file='proftemp.out',form='formatted')
321  open(117,file='profztab.out',form='formatted')
322  open(118,file='profqvar.out',form='formatted')
323  open(119,file='profvvar.out',form='formatted')
324
325  write(115,*) psurf
326  write(116,*) tsurf
327  write(117,*) 0.0
328  write(118,*) qsurf(1)
329  write(119,*) qsurf(1)*(muvar(1)/mH2O)
330  do ilay=1,nlayer
331     vmr(ilay,1) = q(ilay,1)*(muvar(ilay+1)/mH2O)
332     write(115,*) play(ilay)
333     write(116,*) temp(ilay)
334     write(117,*) zlay(ilay)
335     write(118,*) q(ilay,1)
336     write(119,*) vmr(ilay,1)
337  enddo
338  close(115)
339  close(116)
340  close(117)
341  close(118)
342  close(119)
343
344  print*, tsurf,psurf,fluxtop_dn,fluxabs_sw,fluxtop_lw
345
346  print*,'Saving scalars...'
347  open(116,file='surf_vals.out')
348  write(116,*) tsurf,psurf,fluxtop_dn,         &
349       fluxabs_sw,fluxtop_lw
350  close(116)
351  open(111,file='ene_vals.out')
352  write(111,*) tsurf,psurf,Eatmtot,Tstrat
353  close(111)
354
355  print*,'Saving spectra...'
356  open(117,file='OLRnu.out')
357  do iw=1,L_NSPECTI
358     write(117,*) OLR_nu(1,iw)
359  enddo
360  close(117)
361
362  open(127,file='OSRnu.out')
363  do iw=1,L_NSPECTV
364     write(127,*) OSR_nu(1,iw)
365  enddo
366  close(127) 
367
368end program kcm1d
Note: See TracBrowser for help on using the repository browser.