source: LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/gr_fi_dyn.f90 @ 5110

Last change on this file since 5110 was 5105, checked in by abarral, 2 months ago

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

  • 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: 1.0 KB
Line 
1
2! $Header$
3
4SUBROUTINE gr_fi_dyn(nfield,ngrid,im,jm,pfi,pdyn)
5  IMPLICIT NONE
6  !=======================================================================
7  !   passage d'un champ de la grille scalaire a la grille physique
8  !=======================================================================
9
10  !-----------------------------------------------------------------------
11  !   declarations:
12  !   -------------
13
14  INTEGER :: im,jm,ngrid,nfield
15  REAL :: pdyn(im,jm,nfield)
16  REAL :: pfi(ngrid,nfield)
17
18  INTEGER :: i,j,ifield,ig
19
20  !-----------------------------------------------------------------------
21  !   calcul:
22  !   -------
23
24  DO ifield=1,nfield
25  !   traitement des poles
26     DO i=1,im
27        pdyn(i,1,ifield)=pfi(1,ifield)
28        pdyn(i,jm,ifield)=pfi(ngrid,ifield)
29     ENDDO
30
31  !   traitement des point normaux
32     DO j=2,jm-1
33        ig=2+(j-2)*(im-1)
34        CALL SCOPY(im-1,pfi(ig,ifield),1,pdyn(1,j,ifield),1)
35        pdyn(im,j,ifield)=pdyn(1,j,ifield)
36     ENDDO
37  ENDDO
38
39  RETURN
40END SUBROUTINE gr_fi_dyn
Note: See TracBrowser for help on using the repository browser.