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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 30 - (hide annotations)
Thu Apr 1 09:07:28 2010 UTC (14 years, 1 month ago) by guez
File size: 2301 byte(s)
Imported Source files of the external library "IOIPSL_Lionel" into
"libf/IOIPSL".

Split "cray.f90" into "scopy.f90" and "ssum.f90".

Rewrote "leapfrog" in order to have a clearer algorithmic structure.

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

  ViewVC Help
Powered by ViewVC 1.1.21