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

Last change on this file since 5254 was 5246, checked in by abarral, 32 hours ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • 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: 845 bytes
RevLine 
[524]1!
2! $Header$
3!
[5246]4SUBROUTINE coordij(lon,lat,ilon,jlat)
[524]5
[5246]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  !=======================================================================
[524]12
[5246]13  USE comconst_mod, ONLY: pi
[524]14
[5246]15  IMPLICIT NONE
16  REAL :: lon,lat
17  INTEGER :: ilon,jlat
18  INTEGER :: i,j
[524]19
[5246]20  include "dimensions.h"
21  include "paramet.h"
22  include "comgeom.h"
[524]23
[5246]24  real :: zlon,zlat
[524]25
[5246]26  zlon=lon*pi/180.
27  zlat=lat*pi/180.
[524]28
[5246]29  DO i=1,iim+1
30     IF (rlonu(i).GT.zlon) THEN
31        ilon=i
32        GOTO 10
33     ENDIF
34  ENDDO
3510   CONTINUE
[524]36
[5246]37  j=0
38  DO j=1,jjm
39     IF(rlatv(j).LT.zlat) THEN
40        jlat=j
41        GOTO 20
42     ENDIF
43  ENDDO
4420   CONTINUE
45  IF(j.EQ.0) j=jjm+1
46
47  RETURN
48END SUBROUTINE coordij
Note: See TracBrowser for help on using the repository browser.