/[PAMELA software]/gpamela/gpgar/gpgarin.F
ViewVC logotype

Annotation of /gpamela/gpgar/gpgarin.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.1 - (hide annotations) (download)
Thu Jul 11 16:02:15 2002 UTC (22 years, 4 months ago) by cafagna
Branch point for: v3r0, MAIN
Initial revision

1 cafagna 3.1 *
2     * $Id$
3     *
4     * $Log$
5     *
6     #if defined(GPAMELA_GARFIELD)
7     *CMZ : 3.00/00 11/05/2001 17.32.49 by Unknown
8     *-- Author : Marialuigia Ambriola 30/04/2001
9     SUBROUTINE GPGARIN
10     *-----------------------------------------------------------------------
11     * MAIN - This program reads headers from the input file and calls
12     * the appropriate routines to carry out the requested action.
13     * VARIABLE : GSTRING : serves for identifying the header.
14     * (Last changed on 13/ 2/00.)
15     *-----------------------------------------------------------------------
16     IMPLICIT NONE
17     C # GPAMELA Related commons
18     #include "gcunit.inc"
19     #include "gpunit.inc"
20     C # END. GPAMELA Related commons
21     #include "dimensions.inc"
22     C ML:
23     C # +SEQ,CELLDATA.
24     C # +SEQ,GASDATA.
25     #include "celldata.inc"
26     #include "gasdata.inc"
27     C END ML.
28     C # +SEQ,BFIELD.
29     #include "printplot.inc"
30     #include "input.inc"
31     LOGICAL STDSTR
32     INTEGER NC,IFAIL,GNWORD,INPCMP
33     CHARACTER*(MXCHAR) GSTRING
34     EXTERNAL STDSTR,INPCMP
35     WRITE(CHMAIL,10000)
36     CALL GMAIL(1,0)
37     *** Initialise variables, graphics, input and algebra.
38     CALL INIT
39     *** Set the LUN number garfield has to read from and open it
40     LUN=LUGAR
41     CALL DSNOPN(CHGAR,LEN(CHGAR),LUN,'READ-FILE',IFAIL)
42     IF (IFAIL.NE.0) THEN
43     WRITE(CHMAIL,10100) IFAIL, CHGAR, LUN
44     CALL GMAIL(1,0)
45     GOTO 20
46     ENDIF
47     *** Start an input loop that stops at the EOF or at the STOP command.
48     IFAIL=0
49     *** Otherwise the line should start with an & symbol.
50     10 CONTINUE
51     CALL INPNUM(GNWORD)
52     * Skip blank lines.
53     IF(GNWORD.EQ.0)THEN
54     CALL INPWRD(GNWORD)
55     GOTO 10
56     ENDIF
57     * Stay in main if requested.
58     IF(INPCMP(1,'&MAIN')+INPCMP(2,'MAIN').NE.0)THEN
59     CALL INPWRD(GNWORD)
60     GOTO 10
61     ENDIF
62     * Make sure it starts with an ampersand.
63     CALL INPSTR(1,1,GSTRING,NC)
64     IF(GSTRING(1:1).NE.'&')THEN
65     WRITE(CHMAIL,10200)
66     CALL GMAIL(1,0)
67     CALL INPWRD(GNWORD)
68     GOTO 10
69     ELSEIF(NC.EQ.1.AND.GNWORD.EQ.1)THEN
70     WRITE(CHMAIL,10300)
71     CALL GMAIL(1,0)
72     CALL INPWRD(GNWORD)
73     GOTO 10
74     ENDIF
75     IF((GNWORD.GT.2.AND.NC.EQ.1).OR.(GNWORD.GT.1.AND.NC.GT.1)) THEN
76     WRITE(CHMAIL,10400)
77     CALL GMAIL(1,0)
78     ENDIF
79     *** Stop if STOP is the keyword.
80     C # Just exit in the GPAMELA case
81     IF(INPCMP(1,'&ST#OP')+INPCMP(2,'ST#OP')+ INPCMP(1,'&Q#UIT')+
82     +INPCMP(2,'Q#UIT')+ INPCMP(1,'&EX#IT')+INPCMP(2,'EX#IT').NE.0)
83     +THEN
84     GOTO 20
85     *** Call CELDEF if CELL is a keyword,
86     ELSEIF(INPCMP(1,'&C#ELL')+INPCMP(2,'C#ELL').NE.0) THEN
87     * Call cell reading routine.
88     CALL CELDEF(IFAIL)
89     IF(IFAIL.EQ.1) PRINT *,' !!!!!! MAIN WARNING : The cell'//
90     + ' section failed ; various sections can not be entered.'
91     *** Call MAGINP if MAGNETIC is a keyword.
92     ELSEIF(INPCMP(1,'&M#AGNETIC-#FIELD')+ INPCMP(2,'M#AGNETIC-#'//
93     + 'FIELD').NE.0) THEN
94     PRINT *,' !!!!!! MAIN WARNING : The &CELL and &MAGNETIC'//
95     + ' sections are absent in this compilation.'
96     CALL SKIP
97     *** Read gas data if GAS is the first keyword,
98     ELSEIF(INPCMP(1,'&G#AS')+INPCMP(2,'G#AS').NE.0)THEN
99     * Call the gas data reading routine.
100     CALL GASDEF(IFAIL)
101     IF(IFAIL.NE.0.AND.JFAIL.EQ.1)THEN
102     PRINT *,' !!!!!! MAIN WARNING : Gas section failed'//
103     + ' ; CO2 will be used for the time being.'
104     CALL XXXGAS(IFAIL)
105     IF(IFAIL.NE.0)PRINT *,' ###### MAIN ERROR : CO2'//
106     + ' data are not correct ; no gas data.'
107     ELSEIF(IFAIL.NE.0)THEN
108     PRINT *,' !!!!!! MAIN WARNING : The gas section'//
109     + ' failed ; various sections can not be entered.'
110     ENDIF
111     *** Call FLDINP if FIELD is a keyword.
112     ELSEIF(INPCMP(1,'&F#IELD')+INPCMP(2,'F#IELD').NE.0)THEN
113     PRINT *,' !!!!!! MAIN WARNING : The &FIELD section is '//
114     + 'absent in this compilation.'
115     CALL SKIP
116     *** Call OPTINP if OPTIMISE is a keyword.
117     ELSEIF(INPCMP(1,'&O#PTIMISE')+INPCMP(2,'O#PTIMISE').NE.0)THEN
118     PRINT *,' !!!!!! MAIN WARNING : The &OPTIMISE section '//
119     + 'is absent in this compilation.'
120     CALL SKIP
121     C ML:
122     C ML *** Warn if the drift section has not been compiled.
123     C ML
124     C ML ELSEIF(INPCMP(1,'&D#RIFT')+INPCMP(2,'D#RIFT').NE.0)THEN
125     C ML PRINT *,' !!!!!! MAIN WARNING : The &DRIFT section is '//
126     C ML + 'absent in this compilation.'
127     C ML C # CALL SKIP
128     C ML CALL INPWRD(GNWORD)
129     C ML GOTO 10
130     *** Call DRFINP if DRIFT is the keyword.
131     ELSEIF(INPCMP(1,'&D#RIFT')+INPCMP(2,'D#RIFT').NE.0)THEN
132     IF((.NOT.GASSET).AND.JFAIL.EQ.1)THEN
133     PRINT *,' !!!!!! MAIN WARNING : No gas data found'//
134     + ' so far ; CO2 will be used for the time being.'
135     CALL XXXGAS(IFAIL)
136     IF(IFAIL.NE.0)THEN
137     PRINT *,' ###### MAIN ERROR : The CO2 data'//
138     + ' are not correct ; no gas data.'
139     CALL SKIP
140     GOTO 10
141     ENDIF
142     ELSEIF(.NOT.GASSET)THEN
143     PRINT *,' !!!!!! MAIN WARNING : No valid gas data'//
144     + ' found so far ; drift section not executed.'
145     CALL SKIP
146     GOTO 10
147     ENDIF
148     IF(CELSET)THEN
149     CALL DRFINP
150     ELSE
151     PRINT *,' !!!!!! MAIN WARNING : No valid cell data'//
152     + ' found so far ; drift section not executed.'
153     CALL SKIP
154     ENDIF
155     C END ML.
156     *** Warn if the signal section has not been compiled.
157     ELSEIF(INPCMP(1,'&SI#GNAL')+INPCMP(2,'SI#GNAL').NE.0)THEN
158     PRINT *,' !!!!!! MAIN WARNING : The &SIGNAL section is '//
159     + 'absent in this compilation.'
160     CALL SKIP
161     *** Header is recognised.
162     ELSE
163     PRINT *,' !!!!!! MAIN WARNING : ',GSTRING(1:NC),' is'//
164     + ' not a valid header.'
165     CALL SKIP
166     ENDIF
167     *** Read a new header.
168     GOTO 10
169     10000 FORMAT(' GPGARIN: Welcome, this is Garfield - version 7.04,',
170     + ' updated until 6/1/2001.')
171     10100 FORMAT(' GPGARIN: ERROR ID:',I8,' OPENING FILE:',A,', ON LUN',
172     + ': ',I8)
173     10200 FORMAT(' GPGARIN: WARNING : Please enter a section',
174     + ' header, a control statement or a global command.')
175     10300 FORMAT(' GPGARIN: WARNING : A section name should',
176     + ' be appended to the &; try again.')
177     10400 FORMAT(' GPGARIN: WARNING : Keywords on the header',
178     + ' line are ignored in this version of the program.')
179     10500 FORMAT(' GPGARIN: Exiting garfield INIT')
180     20 CONTINUE
181     WRITE(CHMAIL,10500)
182     CALL GMAIL(1,0)
183     RETURN
184     END
185     #endif

  ViewVC Help
Powered by ViewVC 1.1.23