~ubuntu-branches/ubuntu/wily/eso-midas/wily-proposed

« back to all changes in this revision

Viewing changes to applic/fit/libsrc/ftcomp.for

  • Committer: Package Import Robot
  • Author(s): Ole Streicher
  • Date: 2014-04-22 14:44:58 UTC
  • Revision ID: package-import@ubuntu.com-20140422144458-okiwi1assxkkiz39
Tags: upstream-13.09pl1.2+dfsg
ImportĀ upstreamĀ versionĀ 13.09pl1.2+dfsg

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
C  @(#)ftcomp.for       19.1 (ESO-DMD) 02/25/03 13:17:31 
 
2
C===========================================================================
 
3
C Copyright (C) 1995 European Southern Observatory (ESO)
 
4
C
 
5
C This program is free software; you can redistribute it and/or 
 
6
C modify it under the terms of the GNU General Public License as 
 
7
C published by the Free Software Foundation; either version 2 of 
 
8
C the License, or (at your option) any later version.
 
9
C
 
10
C This program is distributed in the hope that it will be useful,
 
11
C but WITHOUT ANY WARRANTY; without even the implied warranty of
 
12
C MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 
13
C GNU General Public License for more details.
 
14
C
 
15
C You should have received a copy of the GNU General Public 
 
16
C License along with this program; if not, write to the Free 
 
17
C Software Foundation, Inc., 675 Massachusetts Ave, Cambridge, 
 
18
C MA 02139, USA.
 
19
C
 
20
C Correspondence concerning ESO-MIDAS should be addressed as follows:
 
21
C       Internet e-mail: midas@eso.org
 
22
C       Postal address: European Southern Observatory
 
23
C                       Data Management Division 
 
24
C                       Karl-Schwarzschild-Strasse 2
 
25
C                       D 85748 Garching bei Muenchen 
 
26
C                       GERMANY
 
27
C===========================================================================
 
28
C
 
29
      SUBROUTINE FTCOMP(ISTAT)                                                  
 
30
C++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++                   
 
31
C.COPYRIGHT: Copyright (c) 1987 European Southern Observatory,                  
 
32
C                                         all rights reserved                   
 
33
C                                                                               
 
34
C.VERSION: 1.0  ESO-FORTRAN Conversion, AA  17:25 - 13 JAN 1988                 
 
35
C                                                                               
 
36
C.LANGUAGE: F77+ESOext                                                          
 
37
C                                                                               
 
38
C.AUTHOR: J.D.PONZ                                                              
 
39
C                                                                               
 
40
C.IDENTIFICATION                                                                
 
41
C                                                                               
 
42
C  FTCOMP.FOR
 
43
C                                                                               
 
44
C.PURPOSE                                                                       
 
45
C                                                                               
 
46
C  INTERFACE ROUTINES FOR THE FITTING STRUCTURES                                
 
47
C
 
48
C COMPUTE FITTED VALUES FOR THE DEFINED INDEPENDENT                             
 
49
C VARIABLES, RESULT ON THE DEFINED DEPENDENT VARIABLE                           
 
50
C                                                                               
 
51
C                                                                               
 
52
C.KEYWORDS                                                                      
 
53
C                                                                               
 
54
C  NON LINEAR FITTING                                                           
 
55
C                                                                               
 
56
C.VERSION
 
57
C 021122        last modif
 
58
C                                                                               
 
59
C----------------------------------------------------------------               
 
60
C                                                                               
 
61
C                                                                               
 
62
C      IMPLICIT NONE                                                            
 
63
C                                                                               
 
64
 
 
65
      INTEGER ICOL(2),ISTAT,NCOL,NROW,NSC,I,IUNIT 
 
66
      INTEGER NP1, NP2, NP3, NAC, NAR
 
67
      INTEGER MADRID(1)
 
68
       
 
69
      REAL CUT(4),VALUE(8)                                
 
70
 
 
71
      DOUBLE PRECISION RES(2),RES1(2)                                                   
 
72
      LOGICAL NULL(8),VALID,ISEL                                                
 
73
C
 
74
      INCLUDE 'MID_INCLUDE:FITI.INC/NOLIST'                                    
 
75
      INCLUDE 'MID_INCLUDE:FITC.INC/NOLIST'                                    
 
76
      COMMON/VMR/MADRID
 
77
C                                                                               
 
78
 
79
      DO 100, I=1,8
 
80
         NULL(I) = .FALSE.
 
81
100   CONTINUE
 
82
 
 
83
      IF (FZMAPPED.EQ.0) THEN                                                 
 
84
         ISTAT  = FERDAT                                                   
 
85
         RETURN                                                                
 
86
      END IF                                                                    
 
87
C                                                                               
 
88
C TABLE DATA                                                                    
 
89
C                                                                               
 
90
      IF (FZTYPE.EQ.'TBL ') THEN                                              
 
91
C                                                                               
 
92
C   READ GENERAL INFO AND SET UP OUTPUT COLUMNS                                 
 
93
C                                                                               
 
94
          CALL TBIGET(FZIDEN,NCOL,NROW,NSC,NAC,NAR,ISTAT)                             
 
95
          ICOL(1) = FZDVAR                                                    
 
96
          IF (FZWEIGHT.GT.0) THEN                                             
 
97
              NCOL   = 2                                                        
 
98
              ICOL(2) = FZWEIGHT                                              
 
99
          ELSE                                                                  
 
100
              NCOL   = 1                                                        
 
101
          END IF                                                                
 
102
C                                                                               
 
103
C   COMPUTE LOOP                                                                
 
104
C                                                                               
 
105
          DO 10 I = 1,NROW                                                      
 
106
              CALL TBSGET(FZIDEN,I,ISEL,ISTAT)                                
 
107
              CALL TBRRDR(FZIDEN,I,FZNIND,FZIVAR,VALUE,NULL,        
 
108
     +                    ISTAT)                                                
 
109
              VALID  = ISEL .AND. ( .NOT. NULL(1)) .AND.                        
 
110
     +                 ( .NOT. NULL(2)) .AND. ( .NOT. NULL(3))                  
 
111
              IF (VALID) THEN                                                   
 
112
                  CALL FTCVAL(FZIVAR,VALUE,RES)                               
 
113
                  RES1(1) = RES(1)                                              
 
114
                  RES1(2) = RES(2)                                              
 
115
                  CALL TBRWRD(FZIDEN,I,NCOL,ICOL,RES1,ISTAT)            
 
116
              END IF                                                            
 
117
                                                                                
 
118
   10     CONTINUE                                                              
 
119
C                                                                               
 
120
C RELEASE TABLE DATA                                                            
 
121
C                                                                               
 
122
          CALL TBSINI(FZIDEN,ISTAT)                                           
 
123
          CALL TBTCLO(FZIDEN,ISTAT)                                           
 
124
          FZMAPPED = 0                                                        
 
125
                                                                                
 
126
      ELSE                                                                      
 
127
C                                                                               
 
128
C IMAGE DATA                                                                    
 
129
C                                                                               
 
130
          IF (FZNAXIS.GT.3) THEN                                              
 
131
              CALL STTPUT('Max.no. of dim.exceded',ISTAT)                       
 
132
              RETURN                                                            
 
133
                                                                                
 
134
          END IF                                                                
 
135
                                                                                
 
136
          NP1 = FZNPIX(1)
 
137
          NP2 = FZNPIX(2)
 
138
          NP3 = FZNPIX(3)
 
139
          CALL FTCVA1(MADRID(FZPTRI),MADRID(FZPTRM),FZNAXIS,              
 
140
     +                NP1,NP2,NP3,FZSTART,FZSTEP,CUT)                          
 
141
          CALL STDWRR(FZIDEN,'LHCUTS',CUT,1,4,IUNIT,ISTAT)                      
 
142
          CALL STFCLO(FZIDEN,ISTAT)                                           
 
143
          FZMAPPED = 0                                                        
 
144
      END IF                                                                    
 
145
                                                                                
 
146
      RETURN                                                                    
 
147
                                                                                
 
148
      END