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

Last change on this file was 5128, checked in by abarral, 8 weeks ago

Correct bug in vlspltqs_loc.f90 from r2270 where we call SSUM with incorrect arguments.
Merge the three different versions of abort_gcm into one
Fix seq, para 3D compilation broken from r5107 onwards
(lint) usual + Remove uneeded fixed-form continuations

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