~ubuntu-branches/debian/jessie/eso-midas/jessie

« back to all changes in this revision

Viewing changes to applic/fit/libsrc/funct2t.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 @(#)funct2t.for       19.1 (ES0-DMD) 02/25/03 13:17:38
 
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 Massachusetss Ave, Cambridge, 
 
18
C MA 02139, USA.
 
19
C
 
20
C Corresponding 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 FUNC2T(NRPRM,PRM,FCT,GRD)                                    
 
30
C+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++        
 
31
C                                                                               
 
32
C.MODULE                                                                        
 
33
C       FIT                                                                     
 
34
C                                                                               
 
35
C.NAME                                                                          
 
36
C       FUNCT2_T                                                                
 
37
C                                                                               
 
38
C.PURPOSE                                                                       
 
39
C       Function to compute the sum of residuals and the gradient.              
 
40
C       for FIT/TABLE                                                           
 
41
C                                                                               
 
42
C.KEYWORDS                                                                      
 
43
C       Approximating Function.                                                 
 
44
C                                                                               
 
45
C.DESCRIPTION                                                                   
 
46
C       Trivial                                                                 
 
47
C                                                                               
 
48
C.LANGUAGE                                                                      
 
49
C       FORTRAN                                                                 
 
50
C                                                                               
 
51
C.CALLING SEQUENCE                                                              
 
52
C      CALL LSFUN2(NRPRM,PRM,FCT,GRD)                                           
 
53
C                                                                               
 
54
C.INPUT PARAMETERS                                                              
 
55
C       NRPRM               INTEGER  Number of parameters                       
 
56
C       PRM (NRPRM)         DOUBLE   Parameters                                 
 
57
C                                                                               
 
58
C.MODIFIED PARAMETERS                                                           
 
59
C       none                                                                    
 
60
C                                                                               
 
61
C.OUTPUT PARAMETERS                                                             
 
62
C       FCT                 DOUBLE   Sum of residuals                           
 
63
C       GRD (NRPRM)         DOUBLE   Gradient                                   
 
64
C                                                                               
 
65
C.FILES                                                                         
 
66
C       FIT_NAG.INC/NOLIST                                                      
 
67
C                                                                               
 
68
C.MODULES CALLED                                                                
 
69
C       FTFUNC                                                                  
 
70
C                                                                               
 
71
C.AUTHOR                                                                        
 
72
C       Ph. DEFERT,      Feb 1986                                               
 
73
C                                                                               
 
74
C.MODIFICATIONS                                                                 
 
75
C                                                                               
 
76
C                                                                               
 
77
C-----------------------------------------------------------------------        
 
78
C      IMPLICIT NONE                                                            
 
79
C     ..                                                                        
 
80
C     .. Scalar Arguments ..                                                    
 
81
      INTEGER NRPRM,NAC,NAR                                                     
 
82
      DOUBLE PRECISION FCT                                                      
 
83
C     ..                                                                        
 
84
C     .. Array Arguments ..                                                     
 
85
      DOUBLE PRECISION PRM(NRPRM),GRD(NRPRM)                                    
 
86
C     ..                                                                        
 
87
C     .. Scalars in Common ..                                                   
 
88
      INTEGER NRCOL,ISTAR                                                       
 
89
      CHARACTER WGTTYP*1                                                        
 
90
C     ..                                                                        
 
91
C     .. Arrays in Common ..                                                    
 
92
      INTEGER ICOL(10)                                                          
 
93
C     ..                                                                        
 
94
C     .. Local Scalars ..                                                       
 
95
      DOUBLE PRECISION W,Y,Y1,YOUT,YY                                           
 
96
      INTEGER IDAT,IFUN,ISTAT,K,NC,NROW,NS,BEGFCT,IP                 
 
97
      LOGICAL ISEL,VALID                                                        
 
98
C     ..                                                                        
 
99
C     .. Local Arrays ..                                                        
 
100
      REAL XVAL(10),X(10)                                                       
 
101
      LOGICAL NULL(10)                                                          
 
102
C     ..                                                                        
 
103
C     .. External Files ..                                                      
 
104
       INCLUDE 'MID_INCLUDE:FITNAGI.INC/NOLIST'                                 
 
105
      DOUBLE PRECISION PARDER(MAXPAR)                                           
 
106
       INCLUDE 'MID_INCLUDE:FITNAGC.INC/NOLIST'                                 
 
107
C     ..                                                                        
 
108
C     .. Common blocks ..                                                       
 
109
      COMMON /LSQFUN/ICOL,NRCOL,ISTAR,WGTTYP                                    
 
110
C     ..                                                                        
 
111
C     .. Executable Statements ..                                               
 
112
C                                                                               
 
113
C  Deal with simple linear constrains                                           
 
114
C                                                                               
 
115
      DO 10 K = 1,NRPRM                                                         
 
116
          IP     = FIXPAR(K)                                                    
 
117
          IF (IP.GT.0) THEN                                                     
 
118
              PRM(K) = PRM(IP)*PRPFAC(K)                                        
 
119
              PARAM(K) = PRM(K)                                                 
 
120
          END IF                                                                
 
121
                                                                                
 
122
          GRD(K) = 0.                                                           
 
123
   10 CONTINUE                                                                  
 
124
C                                                                               
 
125
C  Go through the table                                                         
 
126
C                                                                               
 
127
      CALL TBIGET(FZIDEN,NC,NROW,NS,NAC,NAR,ISTAT)                                      
 
128
      FCT    = 0.                                                               
 
129
      DO 70 IDAT = 1,NROW                                                       
 
130
          CALL TBSGET(FZIDEN,IDAT,ISEL,ISTAT)                                   
 
131
          IF ( .NOT. ISEL) GO TO 70                                             
 
132
          CALL TBRRDR(FZIDEN,IDAT,NRCOL,ICOL(ISTAR),XVAL(ISTAR),          
 
133
     +                NULL,ISTAT)                                               
 
134
          VALID  = ISEL                                                         
 
135
          DO 20 K = 1,NRCOL                                                     
 
136
              VALID  = VALID .AND. ( .NOT. NULL(K))                             
 
137
   20     CONTINUE                                                              
 
138
          IF ( .NOT. VALID) GO TO 70                                            
 
139
          Y      = XVAL(2)                                                      
 
140
          W      = XVAL(1)                                                      
 
141
          DO 30 K = 1,NRCOL                                                     
 
142
              X(K)   = XVAL(K+2)                                                
 
143
   30     CONTINUE                                                              
 
144
C                                                                               
 
145
C  Compute the weighting factors                                                
 
146
C                                                                               
 
147
          IF (WGTTYP(1:1).NE.'W') THEN                                          
 
148
              IF (WGTTYP(1:1).EQ.'C') THEN                                      
 
149
                  W      = 1.                                                   
 
150
                                                                                
 
151
              ELSE IF (WGTTYP(1:1).EQ.'S') THEN                                 
 
152
                  YY     = ABS(Y)                                               
 
153
                  IF (YY.LT.1.E-12) THEN                                        
 
154
                      W      = 1.                                               
 
155
                                                                                
 
156
                  ELSE                                                          
 
157
                      W      = 1./YY                                            
 
158
                  END IF                                                        
 
159
                                                                                
 
160
              ELSE IF (WGTTYP(1:1).EQ.'I') THEN                                 
 
161
                  W      = 1./W**2                                              
 
162
                                                                                
 
163
              END IF                                                            
 
164
                                                                                
 
165
          END IF                                                                
 
166
C                                                                               
 
167
C  Compute the fitting values                                                   
 
168
C                                                                               
 
169
          Y1     = 0.D0                                                         
 
170
          BEGFCT = 1                                                            
 
171
          DO 50 IFUN = 1,NRFUN                                                  
 
172
              CALL FTFUNC(FCTCOD(IFUN),NRIND,X,ACTPAR(IFUN),PRM(BEGFCT),        
 
173
     +                    YOUT,PARDER(BEGFCT))                                  
 
174
              Y1     = Y1 + YOUT                                                
 
175
                 BEGFCT = BEGFCT + ACTPAR(IFUN)        
 
176
   50     CONTINUE                                                              
 
177
                                                                                
 
178
          FCT    = FCT + W* (Y1-Y)**2                                           
 
179
                                                                                
 
180
          DO 60 K = 1,NRPRM                                                     
 
181
              IP     = FIXPAR(K)                                                
 
182
              IF (IP.LE.0) THEN                                                 
 
183
                  GRD(K) = GRD(K) + 2.D0*W*PARDER(K)* (Y1-Y)                    
 
184
                                                                                
 
185
              ELSE                                                              
 
186
                  GRD(IP) = GRD(IP) + 2.D0*W*PARDER(K)* (Y1-Y)/PRPFAC(K)        
 
187
              END IF                                                            
 
188
                                                                                
 
189
   60     CONTINUE                                                              
 
190
                                                                                
 
191
   70 CONTINUE                                                                  
 
192
                                                                                
 
193
      RETURN                                                                    
 
194
                                                                                
 
195
      END