source: trunk/LMDZ.MARS/libf/phymars/callradite_mod.F @ 1711

Last change on this file since 1711 was 1711, checked in by mvals, 8 years ago

Mars GCM

  • implementation of a sub-grid water cloud fraction scheme (by A. Pottier): If CLFvarying is set to true in callphys.def, then the sub-grid cloud fraction routine is applied in watercloud.F and aeropacity.F.
  • accordingly modified files are: watercloud.F, aeropacity.F, callradite.F, conf_phys.F, phyetat0.F, phyredem.F90, physiq_mod.F, testphys1d.F, callkeys.h, newtsart.F, start2archive.F, lect_start_archive.F
  • added file: tcondwater.F90, used by watercloud.F to calculate the condensation temperature of water
  • watercloud.F, aeropacity.F, callradite.F are converted to module files as watercloud_mod.F, aeropacity_mod.F, callradite_mod.F

MV

File size: 20.1 KB
Line 
1      MODULE callradite_mod
2
3      IMPLICIT NONE
4
5      CONTAINS
6
7      SUBROUTINE callradite(icount,ngrid,nlayer,nq,zday,ls,pq,albedo,
8     $     emis,mu0,pplev,pplay,pt,tsurf,fract,dist_sol,igout,
9     $     dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,fluxtop_sw,
10     &     tauref,tau,aerosol,dsodust,tauscaling,taucloudtes,rdust,rice,
11     &     nuice,co2ice,clearsky,totcloudfrac)
12
13      use aeropacity_mod
14      use dimradmars_mod, only: ndomainsz, nflev, nsun, nir
15      use dimradmars_mod, only: naerkind, name_iaer,
16     &            iaer_dust_conrath,iaer_dust_doubleq,
17     &            iaer_dust_submicron,iaer_h2o_ice
18      use yomlw_h, only: gcp, nlaylte
19      use comcstfi_h, only: g,cpp
20      use time_phylmdz_mod, only: daysec
21      IMPLICIT NONE
22c=======================================================================
23c   subject:
24c   --------
25c   Subroutine designed to call the main canonic
26c   radiative transfer subroutine "lwmain" et "swmain"
27c   to compute radiative heating and cooling rate and
28c   radiative fluxes to the surface.
29c
30c   These calculations are only valid on the part of the atmosphere
31c   where Local Thermal Equilibrium (NLTE) is verified. In practice
32c   The calculations are only performed for the first "nlaylte"
33c   parameters (nlaylte is calculated by subroutine "nlthermeq"
34c   and stored in module "yomlw_h").
35c
36c   The purpose of this subroutine is to:
37c      1) Make some initial calculation at first call
38c      2) Split the calculation in several sub-grid
39c        ("sub-domain") to save memory and
40c        be able run on a workstation at high resolution
41c        The sub-grid size is defined in dimradmars_mod
42c      3) Compute the 3D scattering parameters depending on the
43c        size distribution of the different tracers (added by JBM)
44c      4) call "lwmain" and "swmain"
45c
46c
47c   authors:   
48c   ------
49c   Francois Forget / Christophe Hourdin / J.-B. Madeleine (2009)
50c
51c
52c   3D scattering scheme user's guide (J.-B. Madeleine)
53c   ---------------------------------
54c
55c   This routine has been modified to take into account 3D, time
56c   dependent scattering properties of the aerosols.
57c---- The look-up tables that contain the scattering parameters
58c   of a given tracer, for different sizes, are read by SUAER.F90.
59c   The names of the corresponding ASCII files have to be set in
60c   this subroutine (file_id variable), and files must be in the
61c   directory specified in datafile.h. Please make sure that the
62c   ASCII files are correctly written, and that the range
63c   of particle sizes is consistent with what you would expect.
64c---- SUAER.F90 is in charge of reading the ASCII files and averaging
65c   the scattering parameters in each GCM channel, using the three last
66c   equations of Forget et al. 1998 (GRL 25, No.7, p.1105-1108).
67c---- These look-up tables, loaded during the firstcall, are then
68c   constantly used by the subroutine "aeroptproperties.F" to compute,
69c   online, the 3D scattering parameters, based on the size distribution
70c   (reffrad and nueffrad) of the different tracers, in each grid box.
71c   These 3D size distributions are loaded by the "updatereffrad.F"
72c   subroutine. A log-normal distribution is then assumed in
73c   "aeroptproperties.F", along with a Gauss-Legendre integration.
74c---- The optical depth at the visible reference wavelength (set in
75c   SUAER.F90, after the file_id variable) is then computed by
76c   the subroutine "aeropacity.F", by using the size and spatial
77c   distribution of the corresponding tracer. This connection has to
78c   be implemented in "aeropacity.F" when adding a new tracer. To do so,
79c   one can use equation 2 of Forget et al. 1998 (Icarus 131, p.302-316).
80c---- The resulting variables "aerosol", "QVISsQREF3d", "omegaVIS3d" and
81c   "gVIS3d" (same in the infrared) are finally used by lwmain.F and
82c   swmain.F to solve the radiative transfer equation.
83c
84c   changes:
85c   -------
86c
87c   > SRL 7/2000
88c   
89c   This version has been modified to only calculate radiative tendencies
90c   over layers 1..NFLEV (set in dimradmars_mod).  Returns zero for higher
91c   layers, if any.
92c   In other routines, nlayer -> nflev.
93c   Routines affected: lwflux, lwi, lwmain, lwxb, lwxd, lwxn.
94c
95c   > J.-B. Madeleine 10W12
96c   This version uses the variable's splitting, which can be usefull
97c     when performing very high resolution simulation like LES.
98c
99c   ----------
100c   Here, solar band#1 is spectral interval between "long1vis" and "long2vis"
101c   set in dimradmars_mod
102c   Here, solar band#2 is spectral interval between "long2vis" and "long3vis"
103c   set in dimradmars_mod
104c
105c   input:
106c   -----
107c   icount                counter of call to subroutine physic by gcm
108c   ngrid                 number of gridpoint of horizontal grid
109c   nlayer                Number of layer
110c   nq                    Number of tracer
111c   ls                    Solar longitude (Ls) , radian
112c   zday                  Date (time since Ls=0, in martian days)
113c   pq(ngrid,nlayer,nq)   Advected fields
114c
115c   albedo (ngrid,2)      hemispheric surface albedo
116c                         albedo (i,1) : mean albedo for solar band#1
117c                                        (see below)
118c                         albedo (i,2) : mean albedo for solar band#2
119c                                        (see below)
120c   emis                  Thermal IR surface emissivity (no unit)
121c   mu0(ngrid)           cos of solar zenith angle
122c                           (=1 when sun at zenith)
123c   pplay(ngrid,nlayer)    pressure (Pa) in the middle of each layer
124c   pplev(ngrid,nlayer+1)  pressure (Pa) at boundaries of each layer
125c   pt(ngrid,nlayer)       atmospheric temperature in each layer (K)
126c   tsurf(ngrid)           surface temperature (K)
127c   fract(ngrid)         day fraction of the time interval
128c                          =1 during the full day ; =0 during the night
129c   declin                 latitude of subsolar point
130c   dist_sol               sun-Mars distance (AU)
131c   igout                  coordinate of analysed point for debugging
132c   reffrad(ngrid,nlayer,naerkind)  Aerosol effective radius
133c   nueffrad(ngrid,nlayer,naerkind) Aerosol effective variance
134
135c
136c  output:
137c  -------
138c dtlw (ngrid,nlayer)       longwave (IR) heating rate (K/s)
139c dtsw(ngrid,nlayer)        shortwave (Solar) heating rate (K/s)
140c fluxsurf_lw(ngrid)        surface downward flux tota LW (thermal IR) (W.m-2)
141c fluxsurf_sw(ngrid,1)      surface downward flux SW for solar band#1 (W.m-2)
142c fluxsurf_sw(ngrid,2)      surface downward flux SW for solar band#2 (W.m-2)
143c
144c fluxtop_lw(ngrid)         outgoing upward flux tota LW (thermal IR) (W.m-2)
145c fluxtop_sw(ngrid,1)       outgoing upward flux SW for solar band#1 (W.m-2)
146c fluxtop_sw(ngrid,2)       outgoing upward flux SW for solar band#2 (W.m-2)
147
148c   tauref       Prescribed mean column optical depth at 610 Pa
149c   tau          Column total visible dust optical depth at each point
150c   aerosol(ngrid,nlayer,naerkind)    aerosol extinction optical depth
151c                         at reference wavelength "longrefvis" set
152c                         in dimradmars_h , in each layer, for one of
153c                         the "naerkind" kind of aerosol optical
154c                         properties.
155
156c=======================================================================
157c
158c    Declarations :
159c    -------------
160c
161#include "callkeys.h"
162
163c-----------------------------------------------------------------------
164c    Input/Output
165c    ------------
166      INTEGER,INTENT(IN) :: icount       
167      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
168      INTEGER,INTENT(IN) :: igout
169
170      REAL,INTENT(IN) :: pq(ngrid,nlayer,nq)
171      REAL,INTENT(IN) :: tauscaling(ngrid) ! Conversion factor for
172                               ! qdust and Ndust
173      REAL,INTENT(IN) :: albedo(ngrid,2),emis(ngrid)
174      REAL,INTENT(IN) :: ls,zday
175
176      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1),pplay(ngrid,nlayer)
177      REAL,INTENT(IN) :: pt(ngrid,nlayer)
178      REAL,INTENT(IN) :: tsurf(ngrid)
179      REAL,INTENT(IN) :: dist_sol,mu0(ngrid),fract(ngrid)
180      REAL,INTENT(OUT) :: dtlw(ngrid,nlayer),dtsw(ngrid,nlayer)
181      REAL,INTENT(OUT) :: fluxsurf_lw(ngrid), fluxtop_lw(ngrid)
182      REAL,INTENT(OUT) :: fluxsurf_sw(ngrid,2), fluxtop_sw(ngrid,2)
183
184      REAL,INTENT(OUT) :: tauref(ngrid), tau(ngrid,naerkind)
185      REAL,INTENT(OUT) :: taucloudtes(ngrid)! Cloud opacity at infrared
186                               !   reference wavelength using
187                               !   Qabs instead of Qext
188                               !   (direct comparison with TES)
189      REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind)
190      REAL,INTENT(OUT) :: dsodust(ngrid,nlayer)
191      REAL,INTENT(OUT) :: rdust(ngrid,nlayer)  ! Dust geometric mean radius (m)
192      REAL,INTENT(OUT) :: rice(ngrid,nlayer)   ! Ice geometric mean radius (m)
193      REAL,INTENT(OUT) :: nuice(ngrid,nlayer)  ! Estimated effective variance
194      REAL,INTENT(IN) :: co2ice(ngrid)           ! co2 ice surface layer (kg.m-2)
195c     sub-grid scale water ice clouds
196      real,intent(out) :: totcloudfrac(ngrid)
197      logical,intent(in) :: clearsky
198
199c
200c    Local variables :
201c    -----------------
202
203      INTEGER j,l,ig,n,ich
204      INTEGER aer_count,iaer
205      INTEGER jd,ig0,nd
206
207      real  cste_mars ! solar constant on Mars (Wm-2)
208      REAL ptlev(ngrid,nlayer+1)
209
210      INTEGER,SAVE :: ndomain
211
212c     Thermal IR net radiative budget (W m-2)
213
214      real znetrad(ndomainsz,nflev)
215
216      real zfluxd_sw(ndomainsz,nflev+1,2)
217      real zfluxu_sw(ndomainsz,nflev+1,2)
218
219      REAL zplev(ndomainsz,nflev+1)
220      REAL zztlev(ndomainsz,nflev+1)
221      REAL zplay(ndomainsz,nflev)
222      REAL zt(ndomainsz,nflev)
223      REAL zaerosol(ndomainsz,nflev,naerkind)
224      REAL zalbedo(ndomainsz,2)
225      REAL zdp(ndomainsz,nflev)
226      REAL zdt0(ndomainsz)
227
228      REAL zzdtlw(ndomainsz,nflev)
229      REAL zzdtsw(ndomainsz,nflev)
230      REAL zzflux(ndomainsz,6)
231      real zrmuz
232
233      REAL :: zQVISsQREF3d(ndomainsz,nflev,nsun,naerkind)
234      REAL :: zomegaVIS3d(ndomainsz,nflev,nsun,naerkind)
235      REAL :: zgVIS3d(ndomainsz,nflev,nsun,naerkind)
236
237      REAL :: zQIRsQREF3d(ndomainsz,nflev,nir,naerkind)
238      REAL :: zomegaIR3d(ndomainsz,nflev,nir,naerkind)
239      REAL :: zgIR3d(ndomainsz,nflev,nir,naerkind)
240
241c     Aerosol size distribution
242      REAL :: reffrad(ngrid,nlayer,naerkind)
243      REAL :: nueffrad(ngrid,nlayer,naerkind)
244c     Aerosol optical properties
245      REAL :: QVISsQREF3d(ngrid,nlayer,nsun,naerkind)
246      REAL :: omegaVIS3d(ngrid,nlayer,nsun,naerkind)
247      REAL :: gVIS3d(ngrid,nlayer,nsun,naerkind)
248
249      REAL :: QIRsQREF3d(ngrid,nlayer,nir,naerkind)
250      REAL :: omegaIR3d(ngrid,nlayer,nir,naerkind)
251      REAL :: gIR3d(ngrid,nlayer,nir,naerkind)
252
253      REAL :: QREFvis3d(ngrid,nlayer,naerkind)
254      REAL :: QREFir3d(ngrid,nlayer,naerkind)
255
256      REAL :: omegaREFvis3d(ngrid,nlayer,naerkind)
257      REAL :: omegaREFir3d(ngrid,nlayer,naerkind)
258
259c   local saved variables
260c   ---------------------
261
262      real,save,allocatable :: pview(:)
263     
264      real zco2   ! volume fraction of CO2 in Mars atmosphere
265      DATA zco2/0.95/
266      SAVE zco2
267
268      LOGICAL firstcall
269      DATA firstcall/.true./
270      SAVE firstcall
271
272c----------------------------------------------------------------------
273
274c     Initialisation
275c     --------------
276
277      IF (firstcall) THEN
278        ! compute ndomain and allocate local saved arrays
279        ndomain= (ngrid-1) / ndomainsz + 1
280        allocate(pview(ngrid))
281
282c        Assign a number to the different scatterers
283c        -------------------------------------------
284
285         iaer_dust_conrath=0
286         iaer_dust_doubleq=0
287         iaer_dust_submicron=0
288         iaer_h2o_ice=0
289
290         aer_count=0
291         if (.NOT.active) then
292           do iaer=1,naerkind
293             if (name_iaer(iaer).eq."dust_conrath") then
294               iaer_dust_conrath = iaer
295               aer_count = aer_count + 1
296             endif
297           enddo
298         endif
299         if (doubleq.AND.active) then
300           do iaer=1,naerkind
301             if (name_iaer(iaer).eq."dust_doubleq") then
302               iaer_dust_doubleq = iaer
303               aer_count = aer_count + 1
304             endif
305           enddo
306         endif
307         if (submicron.AND.active) then
308           do iaer=1,naerkind
309             if (name_iaer(iaer).eq."dust_submicron") then
310               iaer_dust_submicron = iaer
311               aer_count = aer_count + 1
312             endif
313           enddo
314         endif
315         if (water.AND.activice) then
316           do iaer=1,naerkind
317             if (name_iaer(iaer).eq."h2o_ice") then
318               iaer_h2o_ice = iaer
319               aer_count = aer_count + 1
320             endif
321           enddo
322         endif
323
324c        Check that we identified all tracers:
325         if (aer_count.ne.naerkind) then
326           write(*,*) "callradite: found only ",aer_count," scatterers"
327           write(*,*) "               expected ",naerkind
328           write(*,*) "please make sure that the number of"
329           write(*,*) "scatterers in scatterers.h, the names"
330           write(*,*) "in callradite.F, and the flags in"
331           write(*,*) "callphys.def are all consistent!"
332           do iaer=1,naerkind
333             write(*,*)'      ',iaer,' ',trim(name_iaer(iaer))
334           enddo
335           stop
336         else
337           write(*,*) "callradite: found all scatterers, namely:"
338           do iaer=1,naerkind
339             write(*,*)'      ',iaer,' ',trim(name_iaer(iaer))
340           enddo
341         endif
342c        -------------------------------------------
343
344         DO ig=1,ngrid
345            pview(ig)=1.66     ! cosecant of viewing angle
346         ENDDO
347         gcp = g/cpp
348
349c        Loading the optical properties in external look-up tables:
350         CALL SUAER
351!         CALL SULW ! this step is now done in ini_yomlw_h
352
353         write(*,*) 'Splitting radiative calculations: ',
354     $              ' ngrid,ndomainsz,ndomain',
355     $                ngrid,ndomainsz,ndomain
356         if (ngrid .EQ. 1) then
357           if (ndomainsz .NE. 1) then
358             print*
359             print*,'ATTENTION !!!'
360             print*,'pour tourner en 1D, '
361             print*,'fixer ndomainsz=1 dans phymars/dimradmars_h'
362             print*
363             call exit(1)
364           endif
365         endif
366         firstcall=.false.
367      END IF
368
369c     Computing aerosol optical properties and opacity
370c     ------------------------------------------------
371
372c     Updating aerosol size distributions:
373      CALL updatereffrad(ngrid,nlayer,
374     &                rdust,rice,nuice,
375     &                reffrad,nueffrad,
376     &                pq,tauscaling,tau,pplay)
377
378c     Computing 3D scattering parameters:
379      CALL aeroptproperties(ngrid,nlayer,reffrad,nueffrad,
380     &                      QVISsQREF3d,omegaVIS3d,gVIS3d,
381     &                      QIRsQREF3d,omegaIR3d,gIR3d,
382     &                      QREFvis3d,QREFir3d,
383     &                      omegaREFvis3d,omegaREFir3d)
384
385c     Computing aerosol optical depth in each layer:
386      CALL aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
387     &     pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
388     &     nueffrad,QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d,
389     &     clearsky,totcloudfrac)
390
391c     Starting loop on sub-domain
392c     ----------------------------
393
394      DO jd=1,ndomain
395        ig0=(jd-1)*ndomainsz
396        if (jd.eq.ndomain) then
397         nd=ngrid-ig0
398        else
399         nd=ndomainsz
400        endif
401
402c       Spliting input variable in sub-domain input variables
403c       ---------------------------------------------------
404
405        do l=1,nlaylte
406         do ig = 1,nd
407           do iaer = 1, naerkind
408             do ich = 1, nsun
409               zQVISsQREF3d(ig,l,ich,iaer) =
410     &                           QVISsQREF3d(ig0+ig,l,ich,iaer)
411               zomegaVIS3d(ig,l,ich,iaer) =
412     &                           omegaVIS3d(ig0+ig,l,ich,iaer)
413               zgVIS3d(ig,l,ich,iaer) =
414     &                           gVIS3d(ig0+ig,l,ich,iaer)
415             enddo
416             do ich = 1, nir
417               zQIRsQREF3d(ig,l,ich,iaer) =
418     &                           QIRsQREF3d(ig0+ig,l,ich,iaer)
419               zomegaIR3d(ig,l,ich,iaer) =
420     &                           omegaIR3d(ig0+ig,l,ich,iaer)
421               zgIR3d(ig,l,ich,iaer) =
422     &                           gIR3d(ig0+ig,l,ich,iaer)
423             enddo
424           enddo
425         enddo
426        enddo
427
428        do l=1,nlaylte+1
429         do ig = 1,nd
430          zplev(ig,l) = pplev(ig0+ig,l)
431         enddo
432        enddo
433
434        do l=1,nlaylte
435         do ig = 1,nd
436          zplay(ig,l) = pplay(ig0+ig,l)
437          zt(ig,l) = pt(ig0+ig,l)
438c         Thickness of each layer (Pa) :
439          zdp(ig,l)= pplev(ig0+ig,l) - pplev(ig0+ig,l+1)
440         enddo
441        enddo
442
443        do n=1,naerkind
444          do l=1,nlaylte
445            do ig=1,nd
446              zaerosol(ig,l,n) = aerosol(ig0+ig,l,n)
447            enddo
448          enddo
449        enddo
450
451        do j=1,2
452          do ig = 1,nd
453           zalbedo(ig,j) = albedo(ig0+ig,j)
454          enddo
455        enddo
456
457c       Intermediate  levels: (computing tlev)
458c       ---------------------------------------
459c       Extrapolation for the air temperature above the surface
460        DO ig=1,nd
461              zztlev(ig,1)=zt(ig,1)+
462     s        (zplev(ig,1)-zplay(ig,1))*
463     s        (zt(ig,1)-zt(ig,2))/(zplay(ig,1)-zplay(ig,2))
464
465              zdt0(ig) = tsurf(ig0+ig) - zztlev(ig,1)
466        ENDDO
467
468        DO l=2,nlaylte
469         DO ig=1, nd
470               zztlev(ig,l)=0.5*(zt(ig,l-1)+zt(ig,l))
471         ENDDO
472        ENDDO
473
474        DO ig=1, nd
475           zztlev(ig,nlaylte+1)=zt(ig,nlaylte)
476        ENDDO
477
478
479c       Longwave ("lw") radiative transfer (= thermal infrared)
480c       -------------------------------------------------------
481        call lwmain (ig0,icount,nd,nflev
482     .        ,zdp,zdt0,emis(ig0+1),zplev,zztlev,zt
483     .        ,zaerosol,zzdtlw
484     .        ,fluxsurf_lw(ig0+1),fluxtop_lw(ig0+1)
485     .        ,znetrad
486     &        ,zQIRsQREF3d,zomegaIR3d,zgIR3d
487     &        ,co2ice(ig0+1))
488
489c       Shortwave ("sw") radiative transfer (= solar radiation)
490c       -------------------------------------------------------
491c          Mars solar constant (W m-2)
492c          1370 W.m-2 is the solar constant at 1 AU.
493           cste_mars=1370./(dist_sol*dist_sol)
494
495           call swmain ( nd, nflev,
496     S     cste_mars, zalbedo,
497     S     mu0(ig0+1), zdp, zplev, zaerosol, fract(ig0+1),
498     S     zzdtsw, zfluxd_sw, zfluxu_sw,
499     &     zQVISsQREF3d,zomegaVIS3d,zgVIS3d)
500
501c       ------------------------------------------------------------
502c       Un-spliting output variable from sub-domain input variables
503c       ------------------------------------------------------------
504
505        do l=1,nlaylte
506         do ig = 1,nd
507          dtlw(ig0+ig,l) = zzdtlw(ig,l)
508          dtsw(ig0+ig,l) = zzdtsw(ig,l)
509         enddo
510        enddo
511
512        do l=1,nlaylte+1
513         do ig = 1,nd
514          ptlev(ig0+ig,l) = zztlev(ig,l)
515         enddo
516        enddo
517
518        do ig = 1,nd
519          fluxsurf_sw(ig0+ig,1) = zfluxd_sw(ig,1,1)
520          fluxsurf_sw(ig0+ig,2) = zfluxd_sw(ig,1,2)
521          fluxtop_sw(ig0+ig,1) = zfluxu_sw(ig,nlaylte+1,1)
522          fluxtop_sw(ig0+ig,2) = zfluxu_sw(ig,nlaylte+1,2)
523        enddo
524
525      ENDDO         !   (boucle jd=1, ndomain)
526
527c     Zero tendencies for any remaining layers between nlaylte and nlayer
528      if (nlayer.gt.nlaylte) then
529         do l = nlaylte+1, nlayer
530            do ig = 1, ngrid
531               dtlw(ig, l) = 0.
532               dtsw(ig, l) = 0.
533            enddo
534         enddo
535      endif
536
537c     Output for debugging if lwrite=T
538c     --------------------------------
539c     Write all nlayer layers, even though only nlaylte layers may have
540c     non-zero tendencies.
541
542         IF(lwrite) THEN
543            PRINT*,'Diagnotique for the radiation'
544            PRINT*,'albedo, emissiv, mu0,fract,fluxsurf_lw,fluxsurf_sw'
545            PRINT*,albedo(igout,1),emis(igout),mu0(igout),
546     s           fract(igout), fluxsurf_lw(igout),
547     $     fluxsurf_sw(igout,1)+fluxsurf_sw(igout,2)
548            PRINT*,'Tlay Tlev Play Plev dT/dt SW dT/dt LW (K/s)'
549            PRINT*,'daysec',daysec
550            DO l=1,nlayer
551               PRINT*,pt(igout,l),ptlev(igout,l),
552     s         pplay(igout,l),pplev(igout,l),
553     s         dtsw(igout,l),dtlw(igout,l)
554            ENDDO
555         ENDIF
556
557
558      END SUBROUTINE callradite
559
560      END MODULE callradite_mod
Note: See TracBrowser for help on using the repository browser.