mo_truncation.f90

      MODULE mo_truncation
      
        USE mo_parameters, ONLY: jphgl, jpmp1, jpnlev
        USE mo_doctor,     ONLY: nout
   5: 
        IMPLICIT NONE
      
        PRIVATE
        PUBLIC :: nmp, nnp, mcrit, am, ntrn, ntrm, ntrk
  10:   PUBLIC :: scpar               ! initialization routine
      
        ! ---------------------------------------------------------------
        !
        ! module *mo_truncation* - quantities related to the spectral truncation.
  15:   !
        ! ---------------------------------------------------------------
      
        INTEGER, ALLOCATABLE :: ntrm(:)  !  max zonal wave number.
        INTEGER, ALLOCATABLE :: ntrk(:)  !  max meridional wave number.
  20:   INTEGER :: ntrn(jpnlev)  !  max meridional wave number for m=0.
        INTEGER :: nmp(jpmp1)    !  displacement of the first point of columns
                                 !  for computations in spectral space.
        INTEGER :: nnp(jpmp1)    !  number of points on each column.
        INTEGER :: mcrit(jphgl)  !  critical zonal wave number depending on
  25:                            !  the latitude line,beyond which *fourier
                                 !  components are ignored.
        REAL    :: am(jpmp1)     !  float(m).i.e jm-1 in the jm loops.
      
      CONTAINS
  30: 
        SUBROUTINE scpar (nm, nn, nk)
      
          USE mo_mpi, ONLY: p_pe, p_io
      
  35:     INTEGER ,intent(in) :: nm ! max zonal wave number
          INTEGER ,intent(in) :: nn ! max meridional wave number for m=0
          INTEGER ,intent(in) :: nk ! max meridional wave number
      
          ! Description:
  40:     !
          ! Computes parameters used for computations in spectral space.
          !
          ! Method:
          !
  45:     ! This subroutine computes some parameters related to the
          ! truncation and used for the computations in spectral space and
          ! for the *Legendre transforms.
          !
          ! *scpar* is called from *initialise*
  50:     !
          ! Results:
          ! The results are stored in arrays in module *mo_truncation*
          !
          ! Authors:
  55:     !
          ! M. Jarraud, ECMWF, March 1982, original source
          ! L. Kornblueh, MPI, May 1998, f90 rewrite
          ! U. Schulzweida, MPI, May 1998, f90 rewrite
          ! 
  60:     ! for more details see file AUTHORS
          !
      
      !   USE mo_control,    only: nkp1, nmp1, nn
      !   USE mo_truncation, only: am, nmp, nnp
  65: 
          !  Local scalars: 
          INTEGER :: jm
      
          !  Intrinsic functions 
  70:     INTRINSIC MIN
      
          !  Executable statements 
      
      !-- 0. These parameters may be overwritten later in 'setdyn'
  75: 
          ntrm (:) = nm
          ntrn (:) = nn
          ntrk (:) = nk
          mcrit(:) = nm+1
  80: 
      !-- 1. Preliminary computations
      
      !-- 2. Compute parameters
      
  85:     DO jm = 1, nm+1
            nnp(jm) = MIN(nk+1-jm,nn) + 1
          END DO
      
          nmp(1) = 0
  90:     DO jm = 2, nm+1
            nmp(jm) = nmp(jm-1) + nnp(jm-1)
          END DO
      
      !-- 3. Fill arrays *am* and *annp1*
  95: 
          DO jm = 1, nm+1
            am(jm) = jm - 1.
          END DO
      
 100:     IF (p_Pe == p_io) THEN
             WRITE (nout, '(a)') &
                  ' Number of points on each column (NNP): '  
             WRITE (nout, '(11i7)') nnp(1:nm+1)
             WRITE (nout, '(a)') &
 105:             ' Displacement of the first point of columns (NMP): '  
             WRITE (nout, '(11i7)') nmp(1:nm+1)
          END IF
      
        END SUBROUTINE scpar
 110: 
      END MODULE mo_truncation


Info Section
uses: mo_doctor, mo_mpi, mo_parameters
back to top
ECHAM 4 vf90 (C) 1998 Max-Planck-Institut für Meteorologie, Hamburg
Wed Nov 24 01:25:21 CST 1999

HTML derived from FORTRAN source by f2html.pl v0.3 (C) 1997,98 Beroud Jean-Marc.