source: IOIPSL/trunk/example/testconfig.f90 @ 3279

Last change on this file since 3279 was 386, checked in by bellier, 16 years ago

Added CeCILL License information

  • Property svn:keywords set to Id
File size: 2.7 KB
Line 
1PROGRAM testconfig
2!-
3!$Id$
4!-
5! This software is governed by the CeCILL license
6! See IOIPSL/IOIPSL_License_CeCILL.txt
7  !
8  USE getincom
9  !
10  !
11  !      This program will do some basic tests on the getin module
12  !
13  !
14  IMPLICIT NONE
15  !
16  LOGICAL           :: debug
17  CHARACTER(LEN=80) :: filename
18  CHARACTER(LEN=10), DIMENSION(3) :: strvec
19  INTEGER           :: split
20  REAL              :: g
21  REAL, DIMENSION(3) :: realvec
22  !
23  !-
24  !- set debug to have more information
25  !-
26  !Config  Key  = DEBUG_INFO
27  !Config  Desc = Flag for debug information
28  !Config  Def  = n
29  !Config  Help = This option allows to switch on the output of debug
30  !Config         information without recompiling the code.
31  !-
32  debug = .FALSE.
33  CALL getin('DEBUG_INFO',debug) 
34  !
35  !Config  Key  = FORCING_FILE
36  !Config  Desc = Name of file containing the forcing data
37  !Config  Def  = islscp_for.nc
38  !Config  Help = This is the name of the file which should be opened
39  !Config         for reading the forcing data of the dim0 model.
40  !Config         The format of the file has to be netCDF and COADS
41  !Config         compliant.
42  !-
43  filename='islscp_for.nc'
44  CALL getin('FORCING_FILE',filename)
45  !
46  !
47  !Config  Key  = SPLIT_DT
48  !Config  Desc = splits the timestep imposed by the forcing
49  !Config  Def  = 12
50  !Config  Help = With this value the time step of the forcing
51  !Config         will be devided. In principle this can be run
52  !Config         in explicit mode but it is strongly suggested
53  !Config         to use the implicit method so that the
54  !Config         atmospheric forcing has a smooth evolution.
55  !-
56  split = 12
57  CALL getin('SPLIT_DT', split)
58  !
59  !
60  !Config  Key  = GRAVIT
61  !Config  Desc = Gravitation constant
62  !Config  Def  = 9.98
63  !Config  Help = In theory these parameters could also be defined through
64  !Config         this mechanisme to ensure that the same value is used by
65  !Config         all components of the model.
66  !-
67  g = 9.98
68  CALL getin('GRAVIT', g)
69  !
70  !Config  Key  = WORDS
71  !Config  Desc = A vector of words
72  !Config  Def  = here there anywhere
73  !Config  Help = An example for a vector of strings
74  !-
75  strvec(1) = "here"
76  strvec(2) = "there"
77  strvec(3) = "anywhere"
78  CALL getin('WORDS', strvec)
79  !
80  !Config  Key  = VECTOR
81  !Config  Desc = A vector of reals
82  !Config  Def  = 1, 2, 3
83  !Config  Help = An example for a vector of REALs
84  !-
85  realvec=(/1,2,3/)
86  CALL getin('VECTOR', realvec)
87  !
88  WRITE(*,*) 'From the run.def we have extracted the following information :'
89  WRITE(*,*) 'DEBUG : ', debug
90  WRITE(*,*) 'FILENAME : ', filename(1:len_trim(filename))
91  WRITE(*,*) 'SPLIT : ', split
92  WRITE(*,*) 'G : ', g
93  WRITE(*,*) 'WORDS : ', strvec
94  WRITE(*,*) 'VECTOR : ', realvec
95  !
96  CALL getin_dump()
97  !
98END PROGRAM testconfig
Note: See TracBrowser for help on using the repository browser.