mo_memory_gl.f90

      MODULE mo_memory_gl
      
        USE mo_kind,        ONLY: dp
        USE mo_linked_list, ONLY: list
   5:   USE mo_memory_base, ONLY: create_list, delete_list, new_entry, get_entry,&
                                  print_memory_table, print_memory_use, print_sinfo,&
                                  get_info, memory_info 
        USE mo_netCDF,      ONLY: max_dim_name
      
  10:   IMPLICIT NONE
      
        PRIVATE
      
        PUBLIC :: construct_gl ! construct the gl table
  15:   PUBLIC :: destruct_gl  ! destruct  the gl table
      
        PUBLIC :: new_entry
        PUBLIC :: get_entry
        PUBLIC :: get_info
  20: 
        PUBLIC :: print_memory_table     ! print information on sp table
        PUBLIC :: print_memory_use
        PUBLIC :: print_sinfo
      
  25:   PUBLIC :: memory_info            ! meta data
      
        ! declaration of predefined fields within this module 
      
        REAL(dp), POINTER, PUBLIC :: q(:,:,:)
  30:   REAL(dp), POINTER, PUBLIC :: x(:,:,:)
        REAL(dp), POINTER, PUBLIC :: xt(:,:,:,:)
        REAL(dp), POINTER, PUBLIC :: lammp(:,:,:)
        REAL(dp), POINTER, PUBLIC :: phimp(:,:,:)
        REAL(dp), POINTER, PUBLIC :: sigmp(:,:,:)
  35: 
        ! declaration of table with 3d-field entries
      
        TYPE (list), PUBLIC :: gl
      
  40: CONTAINS
      
        SUBROUTINE construct_gl (lnlon, nglpx, lnlev, lntrac, lngl, &
                                 nlon,         nlev,  ntrac,  ngl)
      
  45:     INTEGER, INTENT (in) :: lnlon, nglpx, lnlev, lntrac, lngl
          INTEGER, INTENT (in) ::  nlon,         nlev,  ntrac,  ngl
      
          INTEGER :: nlp2
          INTEGER :: dim1(3), dim1p(3)
  50:     INTEGER :: dim2(4), dim2p(4)
          INTEGER :: dim3(3), dim3p(3)
          CHARACTER (max_dim_name) :: dim1n(3), dim2n(4), dim3n(3)
      
          ! construct the gl table
  55:     !
          ! all information specific to this table is set in this subroutine
      
          nlp2  = nlon  + 2
      
  60:     ! overwrite default entries for the predefined fields
          ! allocate the predefined fields
      
          CALL create_list (gl)
      
  65:     ! assign pointers
      
          dim1p = (/  nglpx, lnlev, lngl  /)
          dim1  = (/  nlp2,   nlev,  ngl  /)
          dim1n = (/ "nlp2", "nlev","ngl "/)
  70: 
          dim2p = (/ lnlon,   lnlev,   lntrac,  lngl    /)
          dim2  = (/  nlon,    nlev,    ntrac,   ngl    /)
          dim2n = (/ "nlon  ","nlev  ","nhtrac","ngl   "/)
      
  75:     dim3p = (/ lnlon, lnlev, lngl  /)
          dim3  = (/  nlon,  nlev,  ngl  /)
          dim3n = (/ "nlon","nlev","ngl "/)
      
          CALL new_entry (gl, 'Q',  q, dim1p, dim1, dimnames=dim1n, restart=.true.)
  80:     CALL new_entry (gl, 'X',  x, dim1p, dim1, dimnames=dim1n, restart=.true.)
          IF (ntrac > 0) THEN
             CALL new_entry (gl, 'XT', xt, dim2p, dim2, dimnames=dim2n, restart=.true.)
          ELSE
             CALL new_entry (gl, 'XT', xt, dim2p, dim2)
  85:     END IF
          CALL new_entry (gl, 'LAMMP',  lammp, dim3p, dim3, dimnames=dim3n, restart=.true.)
          CALL new_entry (gl, 'PHIMP',  phimp, dim3p, dim3, dimnames=dim3n, restart=.true.)
          CALL new_entry (gl, 'SIGMP',  sigmp, dim3p, dim3, dimnames=dim3n, restart=.true.)
      
  90:   END SUBROUTINE construct_gl
      
        SUBROUTINE destruct_gl
      
          CALL delete_list (gl)
  95: 
        END SUBROUTINE destruct_gl
      
      END MODULE mo_memory_gl


Info Section
uses: mo_kind, mo_linked_list, mo_memory_base, mo_netcdf calls: create_list, delete_list, new_entry
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.