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

Last change on this file since 30 was 16, checked in by bellier, 17 years ago

JB: add Id (ommited !)

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