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

Last change on this file since 3523 was 3335, checked in by emillour, 6 months ago

Generic PCM:
Add reading/writing of surface albedo in (re)startfi.nc to
improve model restartability. For now only the simpler case
of non-spectral dependent surface albedo is handled.
Turned "surfini" in a module in the process.
Unrelated: added missing delarations in kcm1d so it compiles one again.
EM

  • Property svn:executable set to *
File size: 17.1 KB
Line 
1program kcm1d
2
3  use infotrac, only: nqtot
4  use radinc_h,      only: NAERKIND
5  use radcommon_h,   only: L_NSPECTI, L_NSPECTV, sigma, glat
6  use watercommon_h, only: mH2O
7  use ioipsl_getincom, only: getin
8  use comsaison_h, only: mu0, fract, dist_star
9  use planete_mod
10  use callkeys_mod, only: pceil, tstrat, tracer, global1d, &
11                          varspec, varspec_data, nvarlayer
12  use inifis_mod, only: inifis
13  use aerosol_mod, only: iniaerosol
14  use callcorrk_mod, only: callcorrk
15  use comcstfi_mod
16  use mod_grid_phy_lmdz, only : regular_lonlat
17  use regular_lonlat_mod, only: init_regular_lonlat
18  use physics_distribution_mod, only: init_physics_distribution
19  use regular_lonlat_mod, only: init_regular_lonlat
20  use mod_interface_dyn_phys, only: init_interface_dyn_phys
21  use geometry_mod, only: init_geometry
22  use dimphy, only : init_dimphy
23  use gases_h, only: ngasmx
24
25  implicit none
26
27  !==================================================================
28  !     
29  !     Purpose
30  !     -------
31  !     Run the universal model radiative transfer once in a 1D column.
32  !     Useful for climate evolution studies etc.
33  !     
34  !     It can be compiled with a command like (e.g. for 25 layers):
35  !                                  "makegcm -p std -d 25 kcm1d"
36  !     It requires the files "callphys.def", "gases.def"
37  !     "traceur.def", and "run.def" with a line "INCLUDEDEF=callphys.def"
38  !
39  !     Authors
40  !     -------
41  !     - R. Wordsworth
42  !     - updated by M. Turbet (June 2017)
43  !
44  !==================================================================
45
46#include "dimensions.h"
47!#include "dimphys.h"
48
49  ! --------------------------------------------------------------
50  !  Declarations
51  ! --------------------------------------------------------------
52
53  integer nlayer,nlevel,nq
54  integer ilay,ilev,iq,iw,iter
55  real play(llm)     ! Pressure at the middle of the layers [Pa]
56  real zlay(llm)     ! Altitude at middle of the layers [km]
57  real plev(llm+1)   ! Intermediate pressure levels [Pa]
58  real temp(llm)     ! temperature at the middle of the layers [K]
59  real,allocatable :: q(:,:)   ! tracer mixing ratio [kg/kg]
60  real,allocatable :: vmr(:,:) ! tracer mixing ratio [mol/mol]
61  real,allocatable :: qsurf(:)        ! tracer surface budget [kg/kg] ????
62  real psurf,psurf_n,tsurf(1)     
63
64  real emis(1), albedo(1), albedo_equivalent(1)
65  real albedo_wv(1,L_NSPECTV)
66
67  real muvar(llm+1)
68
69  real dtsw(llm) ! heating rate (K/s) due to SW
70  real dtlw(llm) ! heating rate (K/s) due to LW
71  real fluxsurf_lw(1)   ! incident LW flux to surf (W/m2)
72  real fluxtop_lw(1)    ! outgoing LW flux to space (W/m2)
73  real fluxsurf_sw(1)   ! incident SW flux to surf (W/m2)
74  real fluxsurfabs_sw(1) ! absorbed SW flux by the surf (W/m2)
75  real fluxabs_sw(1)    ! SW flux absorbed by planet (W/m2)
76  real fluxtop_dn(1)    ! incident top of atmosphere SW flux (W/m2)
77
78  ! not used
79  real cloudfrac(1,llm)
80  real totcloudfrac(1)
81  real tau_col(1)
82
83  real dTstrat
84  real,allocatable :: aerosol(:,:) ! aerosol tau (kg/kg)
85  real OLR_nu(1,L_NSPECTI)
86  real OSR_nu(1,L_NSPECTV)
87  real GSR_nu(1,L_NSPECTV)
88  real int_dtaui(1,llm,L_NSPECTI)
89  real int_dtauv(1,llm,L_NSPECTV)
90  real Eatmtot
91 
92  ! For fixed variable molar mass
93  real, dimension(:),allocatable,save :: p_var
94  real, dimension(:),allocatable,save :: mu_var
95  real, dimension(:,:),allocatable,save :: frac_var
96
97  integer ierr
98  logical firstcall,lastcall
99
100  character*20,allocatable :: nametrac(:)   ! name of the tracer (no need for adv trac common)
101 
102  real :: latitude(1), longitude(1), cell_area(1), phisfi(1)
103 
104  !     added by JVO and YJ to read modern traceur.def
105  character(len=500) :: line ! to store a line of text
106  LOGICAL :: moderntracdef=.false. ! JVO, YJ : modern traceur.def
107
108  character(len=100) :: dt_file
109  integer :: ios
110  integer :: k
111 
112  ! --------------
113  ! Initialisation
114  ! --------------
115
116  pi=2.E+0*asin(1.E+0)
117
118  cloudfrac(1,:)  = 0.0
119  totcloudfrac(1)  = 0.0
120
121
122  nlayer=llm
123  nlevel=nlayer+1
124
125  !! this is defined in comsaison_h
126  ALLOCATE(mu0(1))
127  ALLOCATE(fract(1))
128  ALLOCATE(glat(1))
129
130! Initialize fixed variable mu
131!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~   
132
133  if(varspec) then
134    IF (.NOT.ALLOCATED(p_var))  ALLOCATE(p_var(nvarlayer))
135    IF (.NOT.ALLOCATED(mu_var))  ALLOCATE(mu_var(nvarlayer))
136    IF (.NOT.ALLOCATED(frac_var))  ALLOCATE(frac_var(nvarlayer,ngasmx))
137    p_var = 0.0
138    mu_var = 0.0
139    frac_var = 0.0
140    dt_file=TRIM(varspec_data)
141    open(34,file=dt_file,form='formatted',status='old',iostat=ios)
142    if (ios.ne.0) then        ! file not found
143      write(*,*) 'Error from varspec'
144      write(*,*) 'Data file ',trim(varspec_data),' not found.'
145      write(*,*) 'Check that the data is in your run repository.'
146      call abort_physic !a verifier
147    else
148      do k=1,nvarlayer
149        read(34,*) p_var(k), mu_var(k),frac_var(k,1:ngasmx)
150        !The order of columns in frac_var must correspond to order of molecules gases.def
151        !The format of your file must be:
152        ! pressure(k) molar_mass(k), molar_fraction_of_gas_1(k), molar_fraction_of_gas_2(k),..., molar_fraction_of_gas_ngasmx(k)
153      enddo
154    endif
155    close(34)
156  endif
157
158  !  Load parameters from "run.def"
159  ! -------------------------------
160
161  ! check if 'kcm1d.def' file is around (otherwise reading parameters
162  ! from callphys.def via getin() routine won't work.)
163  open(90,file='kcm1d.def',status='old',form='formatted',&
164       iostat=ierr)
165  if (ierr.ne.0) then
166     write(*,*) 'Cannot find required file "kcm1d.def"'
167     write(*,*) '  (which should contain some input parameters'
168     write(*,*) '   along with the following line:'
169     write(*,*) '   INCLUDEDEF=callphys.def'
170     write(*,*) '   )'
171     write(*,*) ' ... might as well stop here ...'
172     stop
173  else
174     close(90)
175  endif
176 
177! now, run.def is needed anyway. so we create a dummy temporary one
178! for ioipsl to work. if a run.def is already here, stop the
179! program and ask the user to do a bit of cleaning
180  open(90,file='run.def',status='old',form='formatted',&
181       iostat=ierr)
182  if (ierr.eq.0) then
183     close(90)
184     write(*,*) 'There is already a run.def file.'
185     write(*,*) 'This is not compatible with 1D runs.'
186     write(*,*) 'Please remove the file and restart the run.'
187     write(*,*) 'Runtime parameters are supposed to be in kcm1d.def'
188     stop
189  else
190     call system('touch run.def')
191     call system("echo 'INCLUDEDEF=callphys.def' >> run.def")
192     call system("echo 'INCLUDEDEF=kcm1d.def' >> run.def")
193  endif
194   
195! check if we are going to run with or without tracers
196  write(*,*) "Run with or without tracer transport ?"
197  tracer=.false. ! default value
198  call getin("tracer",tracer)
199  write(*,*) " tracer = ",tracer
200
201
202
203  ! Tracer initialisation
204  ! ---------------------
205  if (tracer) then
206     ! load tracer names from file 'traceur.def'
207     open(90,file='traceur.def',status='old',form='formatted',&
208          iostat=ierr)
209     if (ierr.eq.0) then
210        write(*,*) "kcm1d: Reading file traceur.def"
211        ! read number of tracers:
212        !! - Modif. by JVO and YJ for modern planetary traceur.def ---------------
213        READ(90,'(A)') line
214        IF (trim(line).ne.'#ModernTrac-v1') THEN ! Test modern traceur.def
215           READ(line,*,iostat=ierr) nq ! Try standard traceur.def
216        ELSE
217           moderntracdef = .true.
218           DO
219             READ(90,'(A)',iostat=ierr) line
220             IF (ierr.eq.0) THEN
221               IF (index(line,'#').ne.1) THEN ! Allows arbitary number of comments lines in the header
222                 READ(line,*,iostat=ierr) nq
223                 EXIT
224               ENDIF
225             ELSE ! If pb, or if reached EOF without having found nbtr
226                write(*,*) "rcm1d: error reading number of tracers"
227                write(*,*) "   (first line of traceur.def) "
228                stop
229             ENDIF
230           ENDDO
231        ENDIF ! if modern or standard traceur.def
232        if (ierr.ne.0) then
233           write(*,*) "kcm1d: error reading number of tracers"
234           write(*,*) "   (first line of traceur.def) "
235           stop
236        endif
237        nqtot=nq
238        ! allocate arrays which depend on number of tracers
239        allocate(nametrac(nq))
240        allocate(q(nlayer,nq))
241        allocate(vmr(nlayer,nq))
242        allocate(qsurf(nq))
243
244        do iq=1,nq
245           ! minimal version, just read in the tracer names, 1 per line
246           read(90,*,iostat=ierr) nametrac(iq)
247           write(*,*) 'tracer here is', nametrac(iq)
248           if (ierr.ne.0) then
249              write(*,*) 'kcm1d: error reading tracer names...'
250              stop
251           endif
252        enddo !of do iq=1,nq
253        close(90)
254     endif
255
256     call initracer(1,nq)
257
258  endif
259 
260
261
262
263
264  psurf_n=100000. ! default value for psurf
265  print*,'Dry surface pressure (Pa)?'
266  call getin("psurf",psurf_n)
267  write(*,*) " psurf = ",psurf_n
268
269! OK. now that run.def has been read once -- any variable is in memory.
270! so we can dump the dummy run.def
271  call system("rm -rf run.def")
272
273  tsurf=300.0 ! default value for tsurf
274  print*,'Surface temperature (K)?'
275  call getin("tref",tsurf)
276  write(*,*) " tsurf = ",tsurf
277
278  g=10.0 ! default value for g
279  print*,'Gravity ?'
280  call getin("g",g)
281  write(*,*) " g = ",g
282  glat(1)=g
283
284  periastr = 1.0
285  apoastr  = 1.0
286  print*,'Periastron (AU)?'
287  call getin("periastr",periastr)
288  write(*,*) "periastron = ",periastr
289  dist_star = periastr
290  fract     = 0.5
291  print*,'Apoastron (AU)?'
292  call getin("apoastr",apoastr)
293  write(*,*) "apoastron = ",apoastr
294
295  albedo=0.2 ! default value for albedo
296  print*,'Albedo of bare ground?'
297  call getin("albedo",albedo)
298  write(*,*) " albedo = ",albedo
299  do iw=1,L_NSPECTV
300     albedo_wv(1,iw)=albedo(1)
301  enddo
302
303  emis=1.0 ! default value for emissivity
304  PRINT *,'Emissivity of bare ground ?'
305  call getin("emis",emis)
306  write(*,*) " emis = ",emis
307
308  pceil=100.0 ! Pascals
309  PRINT *,'Ceiling pressure (Pa) ?'
310  call getin("pceil",pceil)
311  write(*,*) " pceil = ", pceil
312
313!!! GEOGRAPHICAL INITIALIZATIONS
314     !!! AREA. useless in 1D
315  cell_area(1)=1.E+0 !JL+EM to have access to the area in the diagfi.nc files.
316     !!! GEOPOTENTIAL. useless in 1D because control by surface pressure
317  phisfi(1)=0.E+0
318     !!! LATITUDE. can be set.
319  latitude=0 ! default value for latitude
320  PRINT *,'latitude (in degrees) ?'
321  call getin("latitude",latitude)
322  write(*,*) " latitude = ",latitude
323  latitude=latitude*pi/180.E+0
324     !!! LONGITUDE. useless in 1D.
325  longitude=0.E+0
326  longitude=longitude*pi/180.E+0
327
328  rad=6400000.
329  !rad = -99999.
330  !PRINT *,'PLANETARY RADIUS in m ?'
331  !call getin("rad",rad)
332  ! Planetary  radius is needed to compute shadow of the rings
333  !IF (rad.eq.-99999. .and. rings_shadow .eqv. .true.) THEN
334  !   PRINT *,"STOP. I NEED rad IN RCM1D.DEF."
335  !   STOP
336  !ELSE
337  !   PRINT *,"--> rad = ",rad
338  !ENDIF
339
340
341
342  call init_physics_distribution(regular_lonlat,4,1,1,1,nlayer,1)
343  call init_interface_dyn_phys
344  CALL init_regular_lonlat(1,1,longitude,latitude,(/0.,0./),(/0.,0./))
345  call init_geometry(1,longitude,latitude,(/0.,0.,0.,0./),(/0.,0.,0.,0./),cell_area)
346  call init_dimphy(1,nlayer) ! Initialize dimphy module
347
348!!! CALL INIFIS
349!!! - read callphys.def
350!!! - calculate sine and cosine of longitude and latitude
351!!! - calculate mugaz and cp
352!!! NB: some operations are being done dummily in inifis in 1D
353!!! - physical constants: nevermind, things are done allright below
354!!! - physical frequency: nevermind, in inifis this is a simple print
355
356  cpp=1.d-7 !JL because we divide by cpp in inifis, there may be a more elegant solution
357  CALL inifis(1,llm,nq,0,86400.0,1,1.0,latitude,longitude,cell_area,rad,g,r,cpp)
358
359  if(.not.global1d)then
360     print*,'Error, kcm1d must have global1d=.true. in kcm1d.def!'
361     stop
362  end if
363
364  !write(*,*) 'BASE 1'
365  !write(*,*) 1,llm,nq,0,86400.0,1,1.0,latitude,longitude,cell_area,rad,g,r,cpp
366
367  ! initialise naerkind (from callphys.def) and allocate aerosol(:,:)
368  naerkind=0 !default
369  call getin("naerkind",naerkind)
370  allocate(aerosol(llm,naerkind))
371  aerosol(:,:)=0
372
373  do iq=1,nq
374     do ilay=1,nlayer
375        q(ilay,iq) = 0.
376     enddo
377  enddo
378 
379  do iq=1,nq
380     qsurf(iq) = 0.
381  enddo
382
383  firstcall = .true.
384  lastcall  = .false.
385
386  iter    = 1
387  Tstrat  = 150.0
388  dTstrat = 1000.0
389
390  ! ---------
391  ! Run model
392  ! ---------
393  !do
394  psurf = psurf_n
395
396     !    Create vertical profiles
397  call kcmprof_fn(nlayer,psurf,qsurf(1),tsurf,    &
398       tstrat,play,plev,zlay,temp,q(:,1),muvar(1))
399         
400
401  !write(*,*) 'BASE 2'
402  !write(*,*) nlayer,psurf,qsurf(1),tsurf,    &
403  !           tstrat
404  !write(*,*) play
405  !write(*,*) plev
406  !write(*,*) zlay
407  !write(*,*) temp
408  !write(*,*) q(:,1),muvar(1)
409
410         
411               
412     call iniaerosol
413     
414
415     
416
417     !    Run radiative transfer
418     call callcorrk(1,nlayer,q,nq,qsurf,                  &
419          albedo_wv,albedo_equivalent,                    &
420          emis,mu0,plev,play,temp,                        &
421          tsurf,fract,dist_star,aerosol,muvar,            &
422          dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,              &
423          fluxsurfabs_sw,fluxtop_lw,                      &
424          fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,GSR_nu,     &
425          int_dtaui,int_dtauv,                            &
426          tau_col,cloudfrac,totcloudfrac,                 &
427          .false.,p_var,frac_var,firstcall,lastcall)
428
429     !write(*,*) 'BASE 3'
430     !write(*,*) 1,nlayer,'A',q,'B',nq,'C',qsurf,                      &
431     !     albedo_wv,'D',albedo_equivalent,'E',                    &
432     !     emis,'F',mu0,'G',plev,'H',play,'I',temp,'J',                        &
433     !     tsurf,'K',fract,'L',dist_star,'M',aerosol,'N',muvar,'O',            &
434     !     dtlw,'P',dtsw,'Q',fluxsurf_lw,'R',fluxsurf_sw,'S',              &
435     !     fluxsurfabs_sw,'T',fluxtop_lw,'U',                      &
436     !     fluxabs_sw,'V',fluxtop_dn,'W',OLR_nu,'X',OSR_nu,'Y',tau_col,'Z',    &
437     !     cloudfrac,'A1',totcloudfrac,'A2',.false.,'A3',firstcall,'A4',lastcall
438
439
440
441
442
443
444
445     !    Iterate stratospheric temperature
446     print*,'Tstrat = ',Tstrat
447     dTstrat = Tstrat
448     !Tstrat  = Tsurf*(0.2786*(psurf/100000.)**(-1.123))**0.25
449     ! skin temperature (gray approx.) using analytic pure H2 expression
450     !Tstrat  = (fluxabs_sw/(2*sigma))**0.25 ! skin temperature (gray approx.)
451     Tstrat  = (fluxtop_lw(1)/(2*sigma))**0.25 ! skin temperature (gray approx.)
452     dTstrat = dTstrat-Tstrat
453
454     !if(abs(dTstrat).lt.1.0)then
455     !   print*,'dTstrat = ',dTstrat
456     !   exit
457     !endif
458
459     !iter=iter+1
460     !if(iter.eq.100)then
461     !   print*,'Stratosphere failed to converge after'
462     !   print*,'100 iteration, aborting run.'
463     !   call abort
464     !endif
465
466  !end do
467
468
469  ! Run radiative transfer one last time to get OLR,OSR
470  firstcall=.false.
471  lastcall=.true.
472  call callcorrk(1,nlayer,q,nq,qsurf,                          &
473       albedo_wv,albedo_equivalent,emis,mu0,plev,play,temp,    &
474       tsurf,fract,dist_star,aerosol,muvar,                    &
475       dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxsurfabs_sw,       &
476       fluxtop_lw, fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,GSR_nu, &
477       int_dtaui,int_dtauv,                                    &
478       tau_col,cloudfrac,totcloudfrac,                         &
479       .false.,p_var,frac_var,firstcall,lastcall)
480
481
482     !write(*,*) 'BASE 4'
483     !write(*,*) 1,nlayer,'A',q,'B',nq,'C',qsurf,                      &
484     !     albedo_wv,'D',albedo_equivalent,'E',                    &
485     !     emis,'F',mu0,'G',plev,'H',play,'I',temp,'J',                        &
486     !     tsurf,'K',fract,'L',dist_star,'M',aerosol,'N',muvar,'O',            &
487     !     dtlw,'P',dtsw,'Q',fluxsurf_lw,'R',fluxsurf_sw,'S',              &
488     !     fluxsurfabs_sw,'T',fluxtop_lw,'U',                      &
489     !     fluxabs_sw,'V',fluxtop_dn,'W',OLR_nu,'X',OSR_nu,'Y',tau_col,'Z',    &
490     !     cloudfrac,'A1',totcloudfrac,'A2',.false.,'A3',firstcall,'A4',lastcall
491
492
493
494
495
496
497
498  ! Calculate total atmospheric energy
499  Eatmtot=0.0
500  !  call calcenergy_kcm(nlayer,tsurf,temp,play,plev,qsurf,&
501  !     q(:,1),muvar,Eatmtot)
502
503  ! ------------------------
504  ! Save data to ascii files
505  ! ------------------------
506
507  print*,'Saving profiles...'
508  open(115,file='profpres.out',form='formatted')
509  open(116,file='proftemp.out',form='formatted')
510  open(117,file='profztab.out',form='formatted')
511  open(118,file='profqvar.out',form='formatted')
512  open(119,file='profvvar.out',form='formatted')
513
514  write(115,*) psurf
515  write(116,*) tsurf
516  write(117,*) 0.0
517  write(118,*) qsurf(1)
518  write(119,*) qsurf(1)*(muvar(1)/mH2O)
519  do ilay=1,nlayer
520     vmr(ilay,1) = q(ilay,1)*(muvar(ilay+1)/mH2O)
521     write(115,*) play(ilay)
522     write(116,*) temp(ilay)
523     write(117,*) zlay(ilay)
524     write(118,*) q(ilay,1)
525     write(119,*) vmr(ilay,1)
526  enddo
527  close(115)
528  close(116)
529  close(117)
530  close(118)
531  close(119)
532
533  print*, tsurf,psurf,fluxtop_dn,fluxabs_sw,fluxtop_lw
534
535  print*,'Saving scalars...'
536  open(116,file='surf_vals.out')
537  write(116,*) tsurf,psurf,fluxtop_dn,         &
538       fluxabs_sw,fluxtop_lw
539  close(116)
540  open(111,file='ene_vals.out')
541  write(111,*) tsurf,psurf,Eatmtot,Tstrat
542  close(111)
543
544  print*,'Saving spectra...'
545  open(117,file='OLRnu.out')
546  do iw=1,L_NSPECTI
547     write(117,*) OLR_nu(1,iw)
548  enddo
549  close(117)
550
551  open(127,file='OSRnu.out')
552  do iw=1,L_NSPECTV
553     write(127,*) OSR_nu(1,iw)
554  enddo
555  close(127) 
556
557end program kcm1d
Note: See TracBrowser for help on using the repository browser.