source: CPL/oasis3-mct_5.0/lib/scrip/src/kinds_mod.f90 @ 6328

Last change on this file since 6328 was 6328, checked in by aclsce, 17 months ago

First import of oasis3-mct_5.0 (from oasis git server, branch OASIS3-MCT_5.0)

File size: 3.2 KB
Line 
1!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2!
3!     This module defines the F90 kind parameter for common data types.
4!
5!-----------------------------------------------------------------------
6!
7!     CVS:$Id: kinds_mod.f 818 2006-03-10 17:18:31Z valcke $
8!
9!     Copyright (c) 1997, 1998 the Regents of the University of
10!       California.
11!
12!     This software and ancillary information (herein called software)
13!     called SCRIP is made available under the terms described here. 
14!     The software has been approved for release with associated
15!     LA-CC Number 98-45.
16!
17!     Unless otherwise indicated, this software has been authored
18!     by an employee or employees of the University of California,
19!     operator of the Los Alamos National Laboratory under Contract
20!     No. W-7405-ENG-36 with the U.S. Department of Energy.  The U.S.
21!     Government has rights to use, reproduce, and distribute this
22!     software.  The public may copy and use this software without
23!     charge, provided that this Notice and any statement of authorship
24!     are reproduced on all copies.  Neither the Government nor the
25!     University makes any warranty, express or implied, or assumes
26!     any liability or responsibility for the use of this software.
27!
28!     If software is modified to produce derivative works, such modified
29!     software should be clearly marked, so as not to confuse it with
30!     the version available from Los Alamos National Laboratory.
31!
32!***********************************************************************
33
34      module kinds_mod
35
36!-----------------------------------------------------------------------
37
38      implicit none
39      save
40
41!-----------------------------------------------------------------------
42
43      integer, parameter :: char_len  = 80
44      integer, parameter :: int_kind  = SELECTED_INT_KIND(9)
45      integer, parameter :: log_kind  = kind(.true.)
46      integer, parameter :: real_kind = SELECTED_REAL_KIND(12,307)
47      integer, parameter :: dbl_kind  = SELECTED_REAL_KIND(12,307)
48!-----------------------------------------------------------------------
49! hardwire for now, tcraig
50
51      INTEGER           :: nlogprt = 0
52      INTEGER           :: nulou = 6
53      logical,parameter :: ll_single = .false.   ! single reals
54      logical,parameter :: lncdfgrd = .true.     ! grid files netcdf
55      integer,parameter :: jpeight = 8
56      character(len=*),parameter :: cgrdnam = 'grids'
57      character(len=*),parameter :: cglonsuf  = '.lon'
58      character(len=*),parameter :: cglatsuf  = '.lat'
59      character(len=*),parameter :: crnlonsuf = '.clo'
60      character(len=*),parameter :: crnlatsuf = '.cla'
61
62      INTEGER, DIMENSION (:), ALLOCATABLE :: snum_links, snum_wgts
63      LOGICAL, DIMENSION (:), ALLOCATABLE :: sweight_flag
64
65      TYPE wp
66         REAL(kind=dbl_kind), POINTER :: warray(:,:)
67      END TYPE wp
68      type(wp), allocatable :: sweigth(:)
69
70      TYPE sp
71        INTEGER, POINTER :: srcarray(:)
72      END TYPE sp
73      type(sp), allocatable :: ssrc_addr(:)
74
75      TYPE dp
76        INTEGER, POINTER :: dstarray(:)
77      END TYPE dp
78      type(dp), allocatable :: sdst_addr(:)
79
80      end module kinds_mod
81
82!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Note: See TracBrowser for help on using the repository browser.