source: trunk/src/coordtrafo.f90 @ 28

Last change on this file since 28 was 4, checked in by mlanger, 11 years ago
File size: 4.7 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine coordtrafo
23
24  !**********************************************************************
25  !                                                                     *
26  !             FLEXPART MODEL SUBROUTINE COORDTRAFO                    *
27  !                                                                     *
28  !**********************************************************************
29  !                                                                     *
30  !             AUTHOR:      G. WOTAWA                                  *
31  !             DATE:        1994-02-07                                 *
32  !             LAST UPDATE: 1996-05-18   A. STOHL                      *
33  !                                                                     *
34  !**********************************************************************
35  !                                                                     *
36  ! DESCRIPTION: This subroutine transforms x and y coordinates of      *
37  ! particle release points to grid coordinates.                        *
38  !                                                                     *
39  !**********************************************************************
40
41  use point_mod
42  use par_mod
43  use com_mod
44
45  implicit none
46
47  integer :: i,j,k
48
49  if (numpoint.eq.0) goto 30
50
51  ! TRANSFORM X- AND Y- COORDINATES OF STARTING POINTS TO GRID COORDINATES
52  !***********************************************************************
53
54  do i=1,numpoint
55    xpoint1(i)=(xpoint1(i)-xlon0)/dx
56    xpoint2(i)=(xpoint2(i)-xlon0)/dx
57    ypoint1(i)=(ypoint1(i)-ylat0)/dy
58    ypoint2(i)=(ypoint2(i)-ylat0)/dy
59  end do
60
6115   continue
62
63
64  ! CHECK IF RELEASE POINTS ARE WITHIN DOMAIN
65  !******************************************
66
67  do i=1,numpoint
68    if (sglobal.and.(ypoint1(i).lt.1.e-6)) ypoint1(i)=1.e-6
69    if (nglobal.and.(ypoint2(i).gt.real(nymin1)-1.e-5)) &
70         ypoint2(i)=real(nymin1)-1.e-5
71  if ((ypoint1(i).lt.1.e-6).or.(ypoint1(i).ge.real(nymin1)-1.e-6) &
72       .or.(ypoint2(i).lt.1.e-6).or.(ypoint2(i).ge.real(nymin1)-1.e-6) &
73       .or.((.not.xglobal).and.((xpoint1(i).lt.1.e-6).or. &
74       (xpoint1(i).ge.real(nxmin1)-1.e-6).or.(xpoint2(i).lt.1.e-6).or. &
75       (xpoint2(i).ge.real(nxmin1)-1.e-6)))) then
76      write(*,*) ' NOTICE: RELEASE POINT OUT OF DOMAIN DETECTED.'
77      write(*,*) ' IT IS REMOVED NOW ... '
78      if (i.ge.1000) then
79         write(*,*) ' COMMENT: ',compoint(i)
80      else
81         write(*,*) ' COMMENT: ',compoint(1001)
82      endif
83      if (i.lt.numpoint) then
84        do j=i+1,numpoint
85          xpoint1(j-1)=xpoint1(j)
86          ypoint1(j-1)=ypoint1(j)
87          xpoint2(j-1)=xpoint2(j)
88          ypoint2(j-1)=ypoint2(j)
89          zpoint1(j-1)=zpoint1(j)
90          zpoint2(j-1)=zpoint2(j)
91          npart(j-1)=npart(j)
92          kindz(j-1)=kindz(j)
93          ireleasestart(j-1)=ireleasestart(j)
94          ireleaseend(j-1)=ireleaseend(j)
95          if (j.le.1000) compoint(j-1)=compoint(j)
96          do k=1,nspec
97            xmass(j-1,k)=xmass(j,k)
98          end do
99        end do
100      endif
101
102      numpoint=numpoint-1
103      if (numpoint.gt.0) goto 15
104    endif
105  end do
106
10730   if(numpoint.eq.0) then
108    write(*,*) ' FLEXPART MODEL SUBROUTINE COORDTRAFO: ERROR ! '
109    write(*,*) ' NO PARTICLE RELEASES ARE DEFINED!'
110    write(*,*) ' CHECK FILE RELEASES...'
111    stop
112  endif
113
114end subroutine coordtrafo
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG