Changeset 8a65cb0 in flexpart.git for src/outgrid_init_nest.f90


Ignore:
Timestamp:
Mar 2, 2015, 3:11:55 PM (9 years ago)
Author:
Espen Sollum ATMOS <espen@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
1d207bb
Parents:
60403cd
Message:

Added code, makefile for dev branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/outgrid_init_nest.f90

    re200b7a r8a65cb0  
    2222subroutine outgrid_init_nest
    2323
    24   !*****************************************************************************
    25   !                                                                            *
    26   !  This routine calculates, for each grid cell of the output nest, the       *
    27   !  volume and the surface area.                                              *
    28   !                                                                            *
    29   !     Author: A. Stohl                                                       *
    30   !                                                                            *
    31   !    30 August 2004                                                          *
    32   !                                                                            *
    33   !*****************************************************************************
    34   !                                                                            *
    35   ! Variables:                                                                 *
    36   !                                                                            *
    37   ! arean              surface area of all output nest cells                   *
    38   ! volumen            volumes of all output nest cells                        *
    39   !                                                                            *
    40   !*****************************************************************************
     24!*****************************************************************************
     25!                                                                            *
     26!  This routine calculates, for each grid cell of the output nest, the       *
     27!  volume and the surface area.                                              *
     28!                                                                            *
     29!     Author: A. Stohl                                                       *
     30!                                                                            *
     31!    30 August 2004                                                          *
     32!                                                                            *
     33!*****************************************************************************
     34!                                                                            *
     35! Variables:                                                                 *
     36!                                                                            *
     37! arean              surface area of all output nest cells                   *
     38! volumen            volumes of all output nest cells                        *
     39!                                                                            *
     40!*****************************************************************************
    4141
    4242  use unc_mod
     
    5555
    5656
    57   ! gridunc,griduncn        uncertainty of outputted concentrations
     57! gridunc,griduncn        uncertainty of outputted concentrations
    5858  allocate(griduncn(0:numxgridn-1,0:numygridn-1,numzgrid,maxspec, &
    5959       maxpointspec_act,nclassunc,maxageclass),stat=stat)
     
    6161
    6262  if (ldirect.gt.0) then
    63   allocate(wetgriduncn(0:numxgridn-1,0:numygridn-1,maxspec, &
    64        maxpointspec_act,nclassunc,maxageclass),stat=stat)
    65   if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
    66   allocate(drygriduncn(0:numxgridn-1,0:numygridn-1,maxspec, &
    67        maxpointspec_act,nclassunc,maxageclass),stat=stat)
    68   if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
     63    allocate(wetgriduncn(0:numxgridn-1,0:numygridn-1,maxspec, &
     64         maxpointspec_act,nclassunc,maxageclass),stat=stat)
     65    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
     66    allocate(drygriduncn(0:numxgridn-1,0:numygridn-1,maxspec, &
     67         maxpointspec_act,nclassunc,maxageclass),stat=stat)
     68    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
    6969  endif
    7070
    71   ! Compute surface area and volume of each grid cell: area, volume;
    72   ! and the areas of the northward and eastward facing walls: areaeast, areanorth
    73   !***********************************************************************
     71! Extra field for totals at MPI root process
     72  if (lroot.and.mpi_mode.gt.0) then
     73    ! allocate(griduncn0(0:numxgridn-1,0:numygridn-1,numzgrid,maxspec, &
     74    !      maxpointspec_act,nclassunc,maxageclass),stat=stat)
     75    ! if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
     76
     77    if (ldirect.gt.0) then
     78      allocate(wetgriduncn0(0:numxgridn-1,0:numygridn-1,maxspec, &
     79           maxpointspec_act,nclassunc,maxageclass),stat=stat)
     80      if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
     81      allocate(drygriduncn0(0:numxgridn-1,0:numygridn-1,maxspec, &
     82           maxpointspec_act,nclassunc,maxageclass),stat=stat)
     83      if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
     84    endif
     85! allocate a dummy to avoid compilator complaints
     86  else if (.not.lroot.and.mpi_mode.gt.0) then
     87    allocate(wetgriduncn0(1,1,1,1,1,1),stat=stat)
     88    allocate(drygriduncn0(1,1,1,1,1,1),stat=stat)
     89  end if
     90
     91! Compute surface area and volume of each grid cell: area, volume;
     92! and the areas of the northward and eastward facing walls: areaeast, areanorth
     93!***********************************************************************
    7494
    7595  do jy=0,numygridn-1
     
    81101    else
    82102
    83   ! Calculate area of grid cell with formula M=2*pi*R*h*dx/360,
    84   ! see Netz, Formeln der Mathematik, 5. Auflage (1983), p.90
    85   !************************************************************
     103! Calculate area of grid cell with formula M=2*pi*R*h*dx/360,
     104! see Netz, Formeln der Mathematik, 5. Auflage (1983), p.90
     105!************************************************************
    86106
    87107      cosfactp=cos(ylatp*pi180)
     
    100120
    101121
    102   ! Surface are of a grid cell at a latitude ylat
    103   !**********************************************
     122! Surface are of a grid cell at a latitude ylat
     123!**********************************************
    104124
    105125    gridarea=2.*pi*r_earth*hzone*dxoutn/360.
     
    108128      arean(ix,jy)=gridarea
    109129
    110   ! Volume = area x box height
    111   !***************************
     130! Volume = area x box height
     131!***************************
    112132
    113133      volumen(ix,jy,1)=arean(ix,jy)*outheight(1)
     
    119139
    120140
    121   !**************************************************************************
    122   ! Determine average height of model topography in nesteed output grid cells
    123   !**************************************************************************
    124 
    125   ! Loop over all output grid cells
    126   !********************************
     141!**************************************************************************
     142! Determine average height of model topography in nesteed output grid cells
     143!**************************************************************************
     144
     145! Loop over all output grid cells
     146!********************************
    127147
    128148  do jjy=0,numygridn-1
     
    130150      oroh=0.
    131151
    132   ! Take 100 samples of the topography in every grid cell
    133   !******************************************************
     152! Take 100 samples of the topography in every grid cell
     153!******************************************************
    134154
    135155      do j1=1,10
     
    140160          xl=(xlon-xlon0)/dx
    141161
    142   ! Determine the nest we are in
    143   !*****************************
     162! Determine the nest we are in
     163!*****************************
    144164
    145165          ngrid=0
     
    15317343        continue
    154174
    155   ! Determine (nested) grid coordinates and auxiliary parameters used for interpolation
    156   !*****************************************************************************
     175! Determine (nested) grid coordinates and auxiliary parameters used for interpolation
     176!*****************************************************************************
    157177
    158178          if (ngrid.gt.0) then
     
    192212      end do
    193213
    194   ! Divide by the number of samples taken
    195   !**************************************
     214! Divide by the number of samples taken
     215!**************************************
    196216
    197217      orooutn(iix,jjy)=oroh/100.
     
    201221
    202222
    203   !*******************************
    204   ! Initialization of output grids
    205   !*******************************
     223!*******************************
     224! Initialization of output grids
     225!*******************************
    206226
    207227  do kp=1,maxpointspec_act
    208   do ks=1,nspec
    209     do nage=1,nageclass
    210       do jy=0,numygridn-1
    211         do ix=0,numxgridn-1
    212           do l=1,nclassunc
    213   ! Deposition fields
    214             if (ldirect.gt.0) then
    215               wetgriduncn(ix,jy,ks,kp,l,nage)=0.
    216               drygriduncn(ix,jy,ks,kp,l,nage)=0.
    217             endif
    218   ! Concentration fields
    219             do kz=1,numzgrid
    220               griduncn(ix,jy,kz,ks,kp,l,nage)=0.
     228    do ks=1,nspec
     229      do nage=1,nageclass
     230        do jy=0,numygridn-1
     231          do ix=0,numxgridn-1
     232            do l=1,nclassunc
     233! Deposition fields
     234              if (ldirect.gt.0) then
     235                wetgriduncn(ix,jy,ks,kp,l,nage)=0.
     236                drygriduncn(ix,jy,ks,kp,l,nage)=0.
     237              endif
     238! Concentration fields
     239              do kz=1,numzgrid
     240                griduncn(ix,jy,kz,ks,kp,l,nage)=0.
     241              end do
    221242            end do
    222243          end do
     
    225246    end do
    226247  end do
    227   end do
    228248
    229249
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG