source: flexpart.git/src/coordtrafo.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 3.6 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine coordtrafo
5
6  !**********************************************************************
7  !                                                                     *
8  !             FLEXPART MODEL SUBROUTINE COORDTRAFO                    *
9  !                                                                     *
10  !**********************************************************************
11  !                                                                     *
12  !             AUTHOR:      G. WOTAWA                                  *
13  !             DATE:        1994-02-07                                 *
14  !             LAST UPDATE: 1996-05-18   A. STOHL                      *
15  !                                                                     *
16  !**********************************************************************
17  !                                                                     *
18  ! DESCRIPTION: This subroutine transforms x and y coordinates of      *
19  ! particle release points to grid coordinates.                        *
20  !                                                                     *
21  !**********************************************************************
22
23  use point_mod
24  use par_mod
25  use com_mod
26
27  implicit none
28
29  integer :: i,j,k
30  real :: yrspc ! small real number relative to x
31
32  if (numpoint.eq.0) goto 30
33
34  ! TRANSFORM X- AND Y- COORDINATES OF STARTING POINTS TO GRID COORDINATES
35  !***********************************************************************
36
37  do i=1,numpoint
38    xpoint1(i)=(xpoint1(i)-xlon0)/dx
39    xpoint2(i)=(xpoint2(i)-xlon0)/dx
40    ypoint1(i)=(ypoint1(i)-ylat0)/dy
41    ypoint2(i)=(ypoint2(i)-ylat0)/dy
42  end do
43
4415   continue
45
46
47  ! CHECK IF RELEASE POINTS ARE WITHIN DOMAIN
48  !******************************************
49 
50  yrspc = spacing(real(nymin1,kind=sp))
51 
52  do i=1,numpoint
53    if (sglobal.and.(ypoint1(i).lt.1.e-6)) ypoint1(i)=1.e-6
54    if (nglobal.and.(ypoint2(i).gt.real(nymin1,kind=dp)-1.e-5)) &
55         ypoint2(i)=real(nymin1,kind=dp)-10*yrspc
56    if ((ypoint1(i).lt.1.e-6).or.(ypoint1(i).ge.real(nymin1,kind=dp)-1.e-6) &
57       .or.(ypoint2(i).lt.1.e-6).or.(ypoint2(i).ge.real(nymin1,kind=dp)-yrspc) &
58       .or.((.not.xglobal).and.((xpoint1(i).lt.1.e-6).or. &
59       (xpoint1(i).ge.real(nxmin1,kind=dp)-1.e-6).or.(xpoint2(i).lt.1.e-6).or. &
60       (xpoint2(i).ge.real(nxmin1,kind=dp)-1.e-6)))) then
61      write(*,*) ' NOTICE: RELEASE POINT OUT OF DOMAIN DETECTED.'
62      write(*,*) ' IT IS REMOVED NOW ... '
63      if (i.le.1000) then
64         write(*,*) ' COMMENT: ',compoint(i)
65      else
66         write(*,*) ' COMMENT: ',compoint(1001)
67      endif
68      if (i.lt.numpoint) then
69        do j=i+1,numpoint
70          xpoint1(j-1)=xpoint1(j)
71          ypoint1(j-1)=ypoint1(j)
72          xpoint2(j-1)=xpoint2(j)
73          ypoint2(j-1)=ypoint2(j)
74          zpoint1(j-1)=zpoint1(j)
75          zpoint2(j-1)=zpoint2(j)
76          npart(j-1)=npart(j)
77          kindz(j-1)=kindz(j)
78          ireleasestart(j-1)=ireleasestart(j)
79          ireleaseend(j-1)=ireleaseend(j)
80          if (j.le.1000) compoint(j-1)=compoint(j)
81          do k=1,nspec
82            xmass(j-1,k)=xmass(j,k)
83          end do
84        end do
85      endif
86
87      numpoint=numpoint-1
88      if (numpoint.gt.0) goto 15
89    endif
90  end do
91
9230   if(numpoint.eq.0) then
93    write(*,*) ' FLEXPART MODEL SUBROUTINE COORDTRAFO: ERROR ! '
94    write(*,*) ' NO PARTICLE RELEASES ARE DEFINED!'
95    write(*,*) ' CHECK FILE RELEASES...'
96    stop
97  endif
98
99end subroutine coordtrafo
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG