Changeset 463 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Dec 9, 2011, 8:52:27 AM (13 years ago)
Author:
emillour
Message:

Mars GCM: more updates for photochemistry from FL: improved aeronomars/surfacearea.F, along with a change in arguments.
EM

Location:
trunk/LMDZ.MARS/libf
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/aeronomars/surfacearea.F

    r459 r463  
    1       subroutine surfacearea(ngrid, nlay, pplay, pzlay, pt, pq, nq,
    2      $                       rdust, rice, tau, tauscaling,
     1      subroutine surfacearea(ngrid, nlay, ptimestep,
     2     $                       pplay, pzlay,
     3     $                       pt, pq, pdq, nq, rdust, rice, tau,
     4     $                       tauscaling,
    35     $                       surfdust, surfice)
    46
     
    1012!
    1113!     Franck Lefevre
    12 !     version 1.0 november 2011
     14!     version 1.1 november 2011
    1315!==========================================================================
    1416
     
    2426! input
    2527
    26       integer ngrid, nlay
    27       integer nq                   ! number of tracers
    28       real pplay(ngrid,nlay)       ! pressure at mid-layers (Pa)
    29       real pzlay(ngrid,nlay)       ! altitude at mid-layers (m)
    30       real pt(ngrid,nlay)          ! temperature at mid-layers (K)
    31       real pq(ngrid,nlay,nq)       ! tracers (kg/kg)
    32       real rdust(ngrid,nlay)       ! dust geometric mean radius (m)
    33       real rice(ngrid,nlay)        ! ice mass mean radius (m)
    34       real tau(ngrid,naerkind)     ! column dust optical depth at each point
    35       real tauscaling(ngrid)       ! conversion factor for dust amount
     28      integer,intent(in) :: ngrid, nlay
     29      integer,intent(in) :: nq               ! number of tracers
     30      real,intent(in) :: ptimestep           ! physics time step (s)
     31      real,intent(in) :: pplay(ngrid,nlay)   ! pressure at mid-layers (Pa)
     32      real,intent(in) :: pzlay(ngrid,nlay)   ! altitude at mid-layers (m)
     33      real,intent(in) :: pt(ngrid,nlay)      ! temperature at mid-layers (K)
     34      real,intent(in) :: pq(ngrid,nlay,nq)   ! tracers (kg/kg)
     35      real,intent(in) :: pdq(ngrid,nlay,nq)  ! physical tendency (kg/kg.s-1)
     36      real,intent(in) :: rdust(ngrid,nlay)   ! dust geometric mean radius (m)
     37      real,intent(in) :: rice(ngrid,nlay)    ! ice mass mean radius (m)
     38      real,intent(in) :: tau(ngrid,naerkind) ! column dust optical depth at each point
     39      real,intent(in) :: tauscaling(ngrid)   ! conversion factor for dust amount
    3640
    3741! output
    3842
    39       real surfdust(ngrid,nlay)    ! dust surface area (m2/m3)
    40       real surfice(ngrid,nlay)     ! water-ice surface area (m2/m3)
     43      real,intent(out) :: surfdust(ngrid,nlay) ! dust surface area (m2/m3)
     44      real,intent(out) :: surfice(ngrid,nlay)  ! water-ice surface area (m2/m3)
    4145
    4246! local
     
    4448      integer l, ig
    4549      real rho                     ! density (kg/m3)
     50      real dustnd                  ! uodated dust number density (kg/kg)
     51      real icend                   ! uodated ice number density (kg/kg)
    4652      real ccntyp                  ! typical dust number density (#/kg)
    4753                                   ! (microphys = false)
     
    5460         do l = 1,nlay
    5561            do ig = 1,ngrid
     62!              atmospheric density
    5663               rho = pplay(ig,l)/(rnew(ig,l)*pt(ig,l))
    57                surfdust(ig,l) = pq(ig,l,igcm_dust_number)*rho
    58      $                          *tauscaling(ig)
     64!              updated dust number density
     65               dustnd = pq(ig,l,igcm_dust_number)
     66     $                + pdq(ig,l,igcm_dust_number)*ptimestep
     67!              updated ice number density
     68               icend  = pq(ig,l,igcm_ccn_number)
     69     $                + pdq(ig,l,igcm_ccn_number)*ptimestep
     70!              dust surface area
     71               surfdust(ig,l) = dustnd*rho*tauscaling(ig)
    5972     $                          *4.*pi*rdust(ig,l)**2
    60                surfice(ig,l)  = pq(ig,l,igcm_ccn_number)*rho
    61      $                          *tauscaling(ig)
     73!              ice surface area
     74               surfice(ig,l)  = icend*rho*tauscaling(ig)
    6275     $                          *4.*pi*rice(ig,l)**2
    6376            end do
    6477         end do
    65       else            ! simpleclouds
     78      else               ! simpleclouds
    6679         do l = 1,nlay
    6780            do ig = 1,ngrid
     81!              atmospheric density
    6882               rho = pplay(ig,l)/(rnew(ig,l)*pt(ig,l))
     83!              typical dust radius
    6984               rdusttyp = max(.8e-6*exp(-pzlay(ig,l)/18000.),1.e-9)
     85!              typical dust number density
    7086               ccntyp = 1.3e+8*max(tau(ig,1),0.001)/0.1
    7187     $                  *exp(-pzlay(ig,l)/10000.)
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r459 r463  
    308308      real rho(ngridmx,nlayermx)  ! density
    309309      real vmr(ngridmx,nlayermx)  ! volume mixing ratio
    310       !real colden(ngridmx,nqmx)   ! vertical column                      !FL
     310      REAL colden(ngridmx,nqmx)   ! vertical column of tracers
    311311      REAL mtot(ngridmx)          ! Total mass of water vapor (kg/m2)
    312312      REAL icetot(ngridmx)        ! Total mass of water ice (kg/m2)
     
    10881088
    10891089!           dust and ice surface area
    1090             call surfacearea(ngrid, nlayer, pplay, zzlay, pt, pq, nq,
     1090            call surfacearea(ngrid, nlayer, ptimestep, pplay, zzlay,
     1091     $                       pt, pq, pdq, nq,
    10911092     $                       rdust, rice, tau, tauscaling,
    10921093     $                       surfdust, surfice)
     
    14871488             if (thermochem.or.photochem) then
    14881489                do iq=1,nq
    1489                    if ((noms(iq).eq."o").or.(noms(iq).eq."co2").or.
    1490      .                (noms(iq).eq."co").or.(noms(iq).eq."n2").or.
    1491      .                (noms(iq).eq."h2").or.
    1492      .                (noms(iq).eq."o3")) then
    1493                         do l=1,nlayer
    1494                           do ig=1,ngrid
    1495                             vmr(ig,l)=zq(ig,l,iq)*mmean(ig,l)/mmol(iq)
    1496                           end do
    1497                         end do
    1498                         call wstats(ngrid,"vmr_"//trim(noms(iq)),
    1499      .                     "Volume mixing ratio","mol/mol",3,vmr)
    1500                    endif
    1501 !                   do ig = 1,ngrid
    1502 !                      colden(ig,iq) = 0.                             !FL
    1503 !                   end do
    1504 !                   do l=1,nlayer                                     !FL
    1505 !                      do ig=1,ngrid                                  !FL
    1506 !                         colden(ig,iq) = colden(ig,iq) + zq(ig,l,iq) !FL
    1507 !     $                                  *(pplev(ig,l)-pplev(ig,l+1)) !FL
    1508 !     $                                  *6.022e22/(mmol(iq)*g)       !FL
    1509 !                      end do                                         !FL
    1510 !                   end do                                            !FL
    1511 !                   call wstats(ngrid,"c_"//trim(noms(iq)),           !FL
    1512 !     $                         "column","mol cm-2",2,colden(1,iq))   !FL
     1490                   if (noms(iq) .ne. "dust_mass" .and.
     1491     $                 noms(iq) .ne. "dust_number" .and.
     1492     $                 noms(iq) .ne. "ccn_mass" .and.
     1493     $                 noms(iq) .ne. "ccn_number") then
     1494                   do l=1,nlayer
     1495                      do ig=1,ngrid
     1496                         vmr(ig,l)=zq(ig,l,iq)*mmean(ig,l)/mmol(iq)
     1497                      end do
     1498                   end do
     1499                   call wstats(ngrid,"vmr_"//trim(noms(iq)),
     1500     $                         "Volume mixing ratio","mol/mol",3,vmr)
     1501                   if ((noms(iq).eq."o") .or. (noms(iq).eq."co2").or.
     1502     $                 (noms(iq).eq."o3")) then                     
     1503                      call writediagfi(ngrid,"vmr_"//trim(noms(iq)),
     1504     $                         "Volume mixing ratio","mol/mol",3,vmr)
     1505                   end if
     1506                   do ig = 1,ngrid
     1507                      colden(ig,iq) = 0.                           
     1508                   end do
     1509                   do l=1,nlayer                                   
     1510                      do ig=1,ngrid                                 
     1511                         colden(ig,iq) = colden(ig,iq) + zq(ig,l,iq)
     1512     $                                  *(pplev(ig,l)-pplev(ig,l+1))
     1513     $                                  *6.022e22/(mmol(iq)*g)       
     1514                      end do                                       
     1515                   end do                                         
     1516                   call wstats(ngrid,"c_"//trim(noms(iq)),           
     1517     $                         "column","mol cm-2",2,colden(1,iq)) 
     1518                   call writediagfi(ngrid,"c_"//trim(noms(iq)), 
     1519     $                             "column","mol cm-2",2,colden(1,iq))
     1520                   end if
    15131521                end do
    15141522             end if ! of if (thermochem.or.photochem)
     
    16351643         call WRITEDIAGFI(ngrid,"co2col","CO2 column","kg.m-2",2,
    16361644     &                  co2col)
    1637 !!!!! FL
    1638 !            do iq = 1,nq
    1639 !               if (noms(iq) .ne. "dust_mass" .and.
    1640 !     $             noms(iq) .ne. "dust_number") then
    1641 !               call writediagfi(ngrid,"c_"//trim(noms(iq)),         
    1642 !     $                         "column","mol cm-2",2,colden(1,iq))
    1643 !               end if
    1644 !            end do
    1645 !!!!! FL
    16461645         endif ! of if (tracer.and.(igcm_co2.ne.0))
    16471646
Note: See TracChangeset for help on using the changeset viewer.