/[lmdze]/trunk/libf/dyn3d/getparam.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/getparam.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 44 - (show annotations)
Wed Apr 13 12:29:18 2011 UTC (13 years, 1 month ago) by guez
File size: 2615 byte(s)
Removed argument "pdteta" of "calfis", because it was not used.

Created module "conf_guide_m", containing procedure
"conf_guide". Moved module variables from "guide_m" to "conf_guide_m".

In module "getparam", removed "ini_getparam" and "fin_getparam" from
generic interface "getpar".

Created module variables in "tau2alpha_m" to replace common "comdxdy".

1 MODULE getparam
2
3 ! From dyn3d/getparam.F90, version 1.1.1.1 2004/05/19 12:53:07
4
5 USE getincom
6
7 INTERFACE getpar
8 MODULE PROCEDURE getparamr, getparami, getparaml
9 END INTERFACE
10
11 private getparamr, getparami, getparaml
12 INTEGER, PARAMETER :: out_eff=99
13
14 CONTAINS
15
16 SUBROUTINE ini_getparam(fichier)
17 !
18 IMPLICIT NONE
19 !
20 CHARACTER*(*) :: fichier
21 open(out_eff, file=fichier, status='unknown', form='formatted')
22 END SUBROUTINE ini_getparam
23
24 !**********************************************************
25
26 SUBROUTINE fin_getparam
27 !
28 IMPLICIT NONE
29 !
30 close(out_eff)
31
32 END SUBROUTINE fin_getparam
33
34 !**********************************************************
35
36 SUBROUTINE getparamr(TARGET, def_val, ret_val, comment)
37 !
38 IMPLICIT NONE
39 !
40 ! Get a real scalar. We first check if we find it
41 ! in the database and if not we get it from the run.def
42 !
43 ! getinr1d and getinr2d are written on the same pattern
44 !
45 CHARACTER*(*) :: TARGET
46 REAL :: def_val
47 REAL :: ret_val
48 CHARACTER*(*) :: comment
49
50 ret_val=def_val
51 call getin(TARGET, ret_val)
52
53 write(out_eff, *) '******'
54 write(out_eff, *) comment
55 write(out_eff, *) TARGET, '=', ret_val
56
57 END SUBROUTINE getparamr
58
59 !**********************************************************
60
61 SUBROUTINE getparami(TARGET, def_val, ret_val, comment)
62 !
63 IMPLICIT NONE
64 !
65 ! Get a real scalar. We first check if we find it
66 ! in the database and if not we get it from the run.def
67 !
68 ! getinr1d and getinr2d are written on the same pattern
69 !
70 CHARACTER*(*) :: TARGET
71 INTEGER :: def_val
72 INTEGER :: ret_val
73 CHARACTER*(*) :: comment
74
75 ret_val=def_val
76 call getin(TARGET, ret_val)
77
78 write(out_eff, *) '***'
79 write(out_eff, *) '*** ', comment, ' ***'
80 write(out_eff, *) comment
81 write(out_eff, *) TARGET, '=', ret_val
82
83 END SUBROUTINE getparami
84
85 !**********************************************************
86
87 SUBROUTINE getparaml(TARGET, def_val, ret_val, comment)
88 !
89 IMPLICIT NONE
90 !
91 ! Get a real scalar. We first check if we find it
92 ! in the database and if not we get it from the run.def
93 !
94 ! getinr1d and getinr2d are written on the same pattern
95 !
96 CHARACTER*(*) :: TARGET
97 LOGICAL :: def_val
98 LOGICAL :: ret_val
99 CHARACTER*(*) :: comment
100
101 ret_val=def_val
102 call getin(TARGET, ret_val)
103
104 write(out_eff, *) '***'
105 write(out_eff, *) '*** ', comment, ' ***'
106 write(out_eff, *) TARGET, '=', ret_val
107
108 END SUBROUTINE getparaml
109
110 END MODULE getparam

  ViewVC Help
Powered by ViewVC 1.1.21