source: LMDZ6/trunk/libf/dyn3d_common/coordij.f90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 861 bytes
Line 
1!
2! $Header$
3!
4SUBROUTINE coordij(lon,lat,ilon,jlat)
5
6  !=======================================================================
7  !
8  !   calcul des coordonnees i et j de la maille scalaire dans
9  !   laquelle se trouve le point (lon,lat) en radian
10  !
11  !=======================================================================
12
13  USE comgeom_mod_h
14  USE comconst_mod, ONLY: pi
15
16  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
17USE paramet_mod_h
18IMPLICIT NONE
19  REAL :: lon,lat
20  INTEGER :: ilon,jlat
21  INTEGER :: i,j
22
23
24
25
26  real :: zlon,zlat
27
28  zlon=lon*pi/180.
29  zlat=lat*pi/180.
30
31  DO i=1,iim+1
32     IF (rlonu(i).GT.zlon) THEN
33        ilon=i
34        GOTO 10
35     ENDIF
36  ENDDO
3710   CONTINUE
38
39  j=0
40  DO j=1,jjm
41     IF(rlatv(j).LT.zlat) THEN
42        jlat=j
43        GOTO 20
44     ENDIF
45  ENDDO
4620   CONTINUE
47  IF(j.EQ.0) j=jjm+1
48
49  RETURN
50END SUBROUTINE coordij
Note: See TracBrowser for help on using the repository browser.