source: branches/publications/ORCHIDEE-LEAK-r5919/src_driver/getprec.f90 @ 5925

Last change on this file since 5925 was 1042, checked in by josefine.ghattas, 12 years ago

First commit for Re-organization of sources code (see ticket 19) :

  • Driver sources were moved from ORCHIDEE_OL/ to new directory ORCHIDEE/src_driver/
  • Target checkprec and config were not adapted for new structure.
  • Removed specifications for old machines in src_driver/AA_make : sxnec, intel,..
  • Compiling is now done in ORCHIDEE directory. To compile all executables, use : "gmake driver"
  • Property svn:keywords set to HeadURL Date Author Revision
File size: 1.6 KB
Line 
1!< $HeadURL$
2!< $Date$
3!< $Author$
4!< $Revision$
5!-
6PROGRAM getprec
7!---------------------------------------------------------------------
8!- This program verifies that that the number representation
9!- between the different components of the model are compatible
10!---------------------------------------------------------------------
11  USE defprec
12!-
13  IMPLICIT NONE
14!-
15  INTEGER :: i
16  REAL    :: r
17!-
18  INTEGER :: range_int,range_real,precision_real
19!---------------------------------------------------------------------
20  range_int  = RANGE(i)
21  range_real = RANGE(r)
22  precision_real = PRECISION(r)
23!-
24  WRITE(*,*) 'The following ranges and precisions are standard'
25  WRITE(*,*) 'on this computer with your compiler options :'
26  WRITE(*,*) ' INTEGER range     :',range_int
27  WRITE(*,*) ' REAL    range     :',range_real
28  WRITE(*,*) ' REAL    precision :',precision_real
29!-
30  WRITE(*,*) 'The corresponding kinds are :'
31  WRITE(*,*) ' KIND for integer  :', &
32 & SELECTED_INT_KIND(range_int)
33  WRITE(*,*) ' KIND for real     :', &
34 & SELECTED_REAL_KIND(precision_real,range_real)
35!-
36  WRITE(*,*) 'We test if this corresponds to what is used'
37  WRITE(*,*) 'in various parts of the code :'
38!-
39! Real :
40!-
41  IF (SELECTED_REAL_KIND(precision_real,range_real) /= r_std) THEN
42    WRITE(*,*) ' REAL : ERROR, the wrong kind is specified.'
43    WRITE(*,*) ' Use the value above.'
44  ELSE
45    WRITE(*,*) ' REAL    : OK'
46  ENDIF
47!-
48! Integer :
49!-
50  IF (SELECTED_INT_KIND(range_int) /= i_std) THEN
51    WRITE(*,*) ' INTEGER : ERROR, the wrong kind is specified.'
52    WRITE(*,*) ' Use the value above.'
53  ELSE
54    WRITE(*,*) ' INTEGER : OK'
55  ENDIF
56!------------------
57END PROGRAM getprec
Note: See TracBrowser for help on using the repository browser.