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

Last change on this file since 5134 was 5119, checked in by abarral, 2 months ago

enforce PRIVATE by default in several modules, expose PUBLIC as needed
move eigen.f90 to obsolete/
(lint) aslong the way

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