Silverfrost Forums

Welcome to our forums

Odd error messages from FTN95 compiler and SLINK

21 Feb 2018 4:17 (Edited: 21 Feb 2018 5:48) #21490

While compiling a package, I made a couple of mistakes, and saw rather strange behavior from the compiler and the linker. I know now to avoid the mistakes, but perhaps the confusing messages and behavior can be rectified.

I placed an interface block into a small source file, intending to INCLUDE the file wherever an interface was needed. Mistake-1: I named the file 'fvec-int.f90' instead of 'fvec-int.inc'.

INTERFACE
  SUBROUTINE fvec(x, f, m, n)
    IMPLICIT NONE
    REAL, INTENT(IN)  :: x(:)
    REAL, INTENT(OUT) :: f(:)
    INTEGER, INTENT(IN)    :: m, n
  END SUBROUTINE fvec
END INTERFACE

Mistake-2: Lazily, I compiled all the files (ftn95 *.f90). Even though the above file does not have a compilable unit, FTN95 takes it and produces a zero-length OBJ file. Other compilers refuse to compile this source file. The linker (SLINK) said

s:\NLEQ\bug>slink *.obj
*** No object files loaded

I tried typing in the file names in full:

s:\NLEQ\bug>slink hahn1.obj tenslv.obj fvec_int.obj
*** Could not open:  fvec_int.obj
^C

That is when I listed the directory and saw that the file was a zero-length file.

All this was in 32-bit mode. With /64, a 15-byte OBJ file was produced, but SLINK64 produced an EXE.

The source files with the executable code are (i) hahn1.f90:

MODULE fdata
IMPLICIT NONE
INTEGER, PARAMETER :: NDAT = 236, NCOEF = 7
REAL :: t(NDAT),y(NDAT)
END MODULE FDATA

PROGRAM xhahn1
USE tensolve
USE fdata
IMPLICIT NONE

INTEGER            :: m, n, msg, termcd, i
REAL               :: x0(NCOEF)

INTERFACE
  SUBROUTINE fhahn1 ( x, f, m, n )
    IMPLICIT NONE
    REAL , INTENT(IN)             :: x(:)
    REAL , INTENT(OUT)            :: f(:)
    INTEGER, INTENT(IN)               :: m
    INTEGER, INTENT(IN)               :: n
  END SUBROUTINE fhahn1
END INTERFACE

!     Set dimensions of the problem.

m      = NDAT
n      = NCOEF

x0 = (/ 1.08d0, -1.23d-3, 4.09d-3, -1.43d-6, -5.76d-3, 2.40d-4, -1.23d-7 /)
msg    = 24

CALL tsnesi(x0, m, n, fhahn1, msg, termcd )

WRITE(*, '(a, i5)')     ' Termination code = ', termcd

!     end of example1 main program.
STOP
END PROGRAM xhahn1

SUBROUTINE fhahn1 ( x, f, m, n )
USE fdata
IMPLICIT NONE
REAL , INTENT(IN)   :: x(:)
REAL , INTENT(OUT)  :: f(:)
INTEGER, INTENT(IN)     :: m
INTEGER, INTENT(IN)     :: n

INTEGER :: i

DO i = 1,m
   f(i) = (((x(4)*t(i)+x(3))*t(i)+x(2))*t(i)+x(1))/ &
          (((x(7)*t(i)+x(6))*t(i)+x(5))*t(i)+1d0 ) &
          - y(i)
END DO

RETURN
END SUBROUTINE fhahn1

[TO BE CONTINUED]

21 Feb 2018 4:18 #21491

[CONTINUED] and (ii) tenslv.f90:

MODULE tensolve

IMPLICIT NONE

REAL, PARAMETER  :: zero = 0.0, one = 1.0

REAL, ALLOCATABLE, SAVE  :: fc(:), anls(:,:), aja(:,:), s(:,:)
INTEGER, SAVE                 :: qrank, meqns, nvars

CONTAINS

SUBROUTINE tsnesi(x0, m, n, fvec, msg, termcd)

REAL, INTENT(IN OUT)  :: x0(:)
INTEGER, INTENT(IN)        :: m
INTEGER, INTENT(IN)        :: n
INTEGER, INTENT(IN OUT)    :: msg
INTEGER, INTENT(OUT)       :: termcd

include 'fvec_int.f90'   ! for interface to fvec()

REAL :: dfn(m)

IF(msg > 0) print *,'MSG = ',msg
call fvec(x0,dfn,m,n)
termcd = 5
RETURN
END SUBROUTINE tsnesi

END MODULE tensolve
23 Feb 2018 7:56 #21503

Many thanks for the feedback. I have made a note of this.

10 Mar 2018 4:26 #21601

This has been fixed for the next release of FTN95.

Please login to reply.