source: flexpart.git/src/coordtrafo.f90 @ 3481cc1

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

move license from headers to a different file

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