source: LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/gr_dyn_fi.f90 @ 5119

Last change on this file since 5119 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_dyn_fi(nfield, im, jm, ngrid, pdyn, pfi)
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 :: j, ifield, ig
20
21  !-----------------------------------------------------------------------
22  !   calcul:
23  !   -------
24
25  IF (ngrid/=2 + (jm - 2) * (im - 1)) THEN
26    CALL abort_gcm("gr_dyn_fi", 'probleme de dim', 1)
27  end if
28  !   traitement des poles
29  CALL SCOPY(nfield, pdyn, im * jm, pfi, ngrid)
30  CALL SCOPY(nfield, pdyn(1, jm, 1), im * jm, pfi(ngrid, 1), ngrid)
31
32  !   traitement des point normaux
33  DO ifield = 1, nfield
34    DO j = 2, jm - 1
35      ig = 2 + (j - 2) * (im - 1)
36      CALL SCOPY(im - 1, pdyn(1, j, ifield), 1, pfi(ig, ifield), 1)
37    ENDDO
38  ENDDO
39
40  RETURN
41END SUBROUTINE gr_dyn_fi
Note: See TracBrowser for help on using the repository browser.