Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

error LNK2001 and 2005

gambato79
Beginner
2,028 Views

Hi all,

I'mbuildinga file.exewith a Fortran Consol Applicationof with visual fortran 6.6 . My codeis very big sice it has a lot of subroutine. When I try to build it I obtain 226 errors of two type:

error LNK2001 : unresolved external symbol _'name'@'number' (name and number are general, only to understand)

error LNK2005: _'NAME?__ already defined in file.OBJ

I try to solve my problem in every way...but I can't, can you help me, please?

thank you

G.

0 Kudos
14 Replies
Lorri_M_Intel
Employee
2,028 Views

Okay, let's see if I can describe this well enough so you can get started.

First, the calling standard used by CVF is very similar to stdcall. In particular, the external names are "decorated" with an @ followed by the number of bytes of arguments. For example,

subroutine mysub (i)

should generate the external name _MYSUB@4, because there is one argument, the address of variable I, and the size of an address is 4 bytes. This is the external name that would be generated in the file that has the SUBROUTINE statement.

If, in another subroutine, you had code that looked like this:

call mysub (10, 20)

then that would generate the external name _MYSUB@8, because now there are two arguments; the address of 10 and the address of 20.

If you had this kind of mismatch, you would get an error message like:

error LNK2001 : unresolved external symbol _MYSUB@8

So, I would recommend that the first thing you do is look for everyplace in the code that calls MYSUB, and compare it to the actual declaratino of MYSUB, and make sure it matches.

That's the first problem. Thesecond problem is most likely that you have initialized COMMON in multiple routines. This ismost likely in an INCLUDE file. Move the initialization to a separate BLOCK DATA file, and remove the initializations from the INCLUDE file. If thatis NOT the problem, we'll need more clues.

Good luck!

- Lorri

0 Kudos
gambato79
Beginner
2,028 Views

Thanks Lorri for your help....I understand what you wrote...but unfortunately there are some problems. I try to explain better.

First of allI didn't write this code...and so it is good because I don't know it.

Then....the errors LNK 2001 are of this type (I report you only same of them)

AVGST1.OBJ : error LNK2001: unresolved external symbol _D0EQ@4
C05NBF1.OBJ : error LNK2001: unresolved external symbol _C05NBF@32
C05NBF2.OBJ : error LNK2001: unresolved external symbol _C05NBF@32
COMLIN.OBJ : error LNK2001: unresolved external symbol _COMMAND_LINE@8
CONSTI.OBJ : error LNK2001: unresolved external symbol _PZ3MAJ@68

I analyzed them as you told me but I found theese problems:

1. D0EQ is defined as logiacal function: d0eq(a,b).

logical function d0eq(a,b)
implicit none
double precision a,b,err,dmach
logical d0eq0
save err
data err/-1.0d0/
if (err.le.0.0d0) err=100.0d0*dmach(1)
d0eq=abs(a-b).le.err*abs(a+b).or.(d0eq0(a).and.d0eq0(b))
return
end

It used ina subroutine in this way...... if ((d0eq(n)) .and. etc) then ......

I modified it but I obtained more errors.

2. C05NBF is a fortran routine. It is defined as C05NBF(fcn,n,x,fvec,xtol,wa,lwa,ifail)....I learnt it; it is called by two soubroutine but in the same way and with the same number of variables. And then....I don't think that i can modifie a fortran routine!

3. COMMAND_LINE is a fortran routine, too

4. PZ3MAJ is a subroutine with 17 variables and it is called in three soubroutines with the same numbers of variables. Then it is called in three file .inf with : load pz3maj. It seem all ok...but it will not.

Theese are only the first four error...and in them I have already 4 problems. I desperate...I don't know what I could do.

Concerning the error 2005...thy are of this type:

APLTEX01.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
APLTEX02.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
C05NBF1.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
C05NBF2.OBJ : error LNK2005: _FCN@16 already defined in C05NBF1.OBJ
C05NBF2.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
C05NBF2.OBJ : error LNK2005: _FCN already defined in C05NBF1.OBJ
CFORM.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
CHECK3A.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
DYNE1D.OBJ : error LNK20 05: _MAIN__ already defined in ANSI

so I can't modify the common and include file because they are referred to object file. Also, considering the first error, the word 'MAIN' isn't define in subroutine APLTEX01.FOR and in ANSI01A.FOR....and so I don't know what I could do, again.

Could you help me??? please

G.

0 Kudos
gambato79
Beginner
2,028 Views

Thanks Lorri for your help....I understand what you wrote...but unfortunately there are some problems. I try to explain better.

First of allI didn't write this code...and so it isn't good because I don't know it.

Then....the errors LNK 2001 are of this type (I report you only same of them)

AVGST1.OBJ : error LNK2001: unresolved external symbol _D0EQ@4
C05NBF1.OBJ : error LNK2001: unresolved external symbol _C05NBF@32
C05NBF2.OBJ : error LNK2001: unresolved external symbol _C05NBF@32
COMLIN.OBJ : error LNK2001: unresolved external symbol _COMMAND_LINE@8
CONSTI.OBJ : error LNK2001: unresolved external symbol _PZ3MAJ@68

I analyzed them as you told me but I found theese problems:

1. D0EQ is defined as logiacal function: d0eq(a,b).

logical function d0eq(a,b)
implicit none
double precision a,b,err,dmach
logical d0eq0
save err
data err/-1.0d0/
if (err.le.0.0d0) err=100.0d0*dmach(1)
d0eq=abs(a-b).le.err*abs(a+b).or.(d0eq0(a).and.d0eq0(b))
return
end

It used ina subroutine in this way...... if ((d0eq(n)) .and. etc) then ......

I modified it but I obtained more errors.

2. C05NBF is a fortran routine. It is defined as C05NBF(fcn,n,x,fvec,xtol,wa,lwa,ifail)....I learnt it; it is called by two soubroutine but in the same way and with the same number of variables. And then....I don't think that i can modifie a fortran routine!

3. COMMAND_LINE is a fortran routine, too

4. PZ3MAJ is a subroutine with 17 variables and it is called in three soubroutines with the same numbers of variables. Then it is called in three file .inf with : load pz3maj. It seem all ok...but it will not.

Theese are only the first four error...and in them I have already 4 problems. I desperate...I don't know what I could do.

Concerning the error 2005...thy are of this type:

APLTEX01.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
APLTEX02.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
C05NBF1.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
C05NBF2.OBJ : error LNK2005: _FCN@16 already defined in C05NBF1.OBJ
C05NBF2.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
C05NBF2.OBJ : error LNK2005: _FCN already defined in C05NBF1.OBJ
CFORM.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
CHECK3A.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ
DYNE1D.OBJ : error LN K2005: _MAIN__ already defined in ANSI

so I can't modify the common and include file because they are referred to object file. Also, considering the first error, the word 'MAIN' isn't define in subroutine APLTEX01.FOR and in ANSI01A.FOR....and so I don't know what I could do, again.

Could you help me??? please

G.

0 Kudos
Lorri_M_Intel
Employee
2,028 Views

Wow, there is so much to talk about! :-)

Okay, let me take them one at a time.

1. D0EQ is defined as logiacal function: d0eq(a,b).

logical function d0eq(a,b)

It used ina subroutine in this way...... if ((d0eq(n)) .and. etc) then ......

Please note that you declared it with two arguments, but called it with only one. That's EXACTLY the kind of problem that a name mismatch shows. Look in your subroutine, in file AVGST1, wherever you have the call to d0eq, and make sure there are always two arguments. OK? That one is probably easy.

Now, these ones:

2. C05NBF is a fortran routine. It is defined as C05NBF(fcn,n,x,fvec,xtol,wa,lwa,ifail)
3. COMMAND_LINE is a fortran routine, too

When I gave my first explanation, I sort of ignored one of the complications, explicitly CHARACTER arguments. By default, whenever you specify a CHARACTER argument, Fortran passes a "hidden" argument that contains the length of the CHARACTER argument. So, for example:

subroutine printme (string)
character*(*) string

will have the external name _PRINTME@8, because there are really two arguments being passed; one is the address of the string to be printed, and the other is the length of that argument.

I'm telling you this because MAYBE your problem is that some of the arguments are defined as CHARACTER, but not being passed as CHARACTER? I would suspect that with COMMAND_LINE, just because of its name.

4. PZ3MAJ is a subroutine with 17 variables

This one, too, may be affected by passing character variables. Also, I do know that when there are SO MANY arguments, that it's very easy for silly mistakes to happen.Please don't take that as any kind of insult, just an observation.

Now, the LNK2005problems

APLTEX01.OBJ : error LNK2005: _MAIN__ already defined in ANSI01A.OBJ

The "_MAIN__" symbol is generated by the compiler whenever it sees a Fortran main program. These messages indicate to me that you are trying to combine multiple, standalone programs into one combined program --- is that true? Just from this short list, it looks like APLTEX01 might be its own program, as is ANSI01A, etc.

I am going to assume that your project contains several files that are common to several programs, and you want to be able to create these several programs without having to copy the common files multiple times. DevStudio is good here, because you can have a single workspace set up to build multiple things; they are called projects, and a workspace can have multiple projects. You can use this feature of DevStudio to create a workspace with multiple projects, configured like this:

1) Figure out which Fortran files are common, and create a STATIC LIBRARY, or DYNAMIC LIBRARY project containing JUST those fi les.

2) Next, for each of the main programs, such as APLTEX01, or ANSI01A, create a FORTRAN CONSOLE APPLICATION project containing that file (and any others that are specific to that application, if any).

3) You will also need to set a dependency between this new application project and the library project from step one; go to Project-Dependencies, and indicate that your console application depends on the library project.

Now, when you build each executable, you shouldn't get a LINK2005 error about _MAIN__, because now there is only one Fortran main program per executable.

Finally ---

C05NBF2.OBJ : error LNK2005: _FCN@16 already defined in C05NBF1.OBJ
This message is telling you that there is a routine (either a subroutine or a function) in the file C05NBF called "FCN", and there is also a routine in the file C05NBF2 called "FCN". You can't have two routines with the same name in the same library or executable. Probably when you take care of the other problem, and put some files into a library, and create new projects for each executable, this will get resolved.

OK? Can you make more progress now?

- Lorri

0 Kudos
gambato79
Beginner
2,028 Views

First of all....thank you very much Lorri....your help is of vital importance for me!

Now...I controlled all my file and I realized that I had not only one program...but many others! So I started to compile one of theese....and as you prefigured I don't have LNK 2005 error messages; and it is magnific!!

But I have same LNK 2001 error message....I couldn't watch everyone because I had no time so I tell you two of theese....that I think are similar.

TERMIN.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
MPRINL.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
MSTORE.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
OPENFL.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
WARNED.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
ANSI01.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
CTITL1.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
MAIN1D.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8
MODNAM.OBJ : error LNK2001: unresolved external symbol _NEOLIN@8

I controlled every subroutine and in everyone NEOLIN is declared as INTEGER; but inside the subroutine NEOLIN is used as NEOLIN(TTEMP) o NEOLIN(MESS) o NEOLIN(STEMP) and TTEMP,MESS,STEMP are CHARACTER type. In some subroutine I have character*(*), in others character*80, character*200, character*70. I tried to define NEOLIN as an array...but the error remain.

Another error is

UNSAT3.OBJ : error LNK2001: unresolved external symbol _DMACH@4
D0EQ.OBJ : error LNK2001: unresolved external symbol _DMACH@4
ORTHO5.OBJ : error LNK2001: unresolved external symbol _DMACH@4
RYIELD1.OBJ : error LNK2001: unresolved external symbol _DMACH@4
STREDU.OBJ : error LNK2001: unresolved external symbol _DMACH@4
TOTDEV.OBJ : error LNK2001: unresolved external symbol _DMACH@4
OELASTI.OBJ : error LNK2001: unresolved external symbol _DMACH@4
ORTHO1.OBJ : error LNK2001: unresolved external symbol _DMACH@4
ORTHO2.OBJ : err or LNK2001: unresolved external symbol _DMACH@4
ORTHO3.OBJ : error LNK2001: unresolved external symbol _DMACH@4
D0EQ0.OBJ : error LNK2001: unresolved external symbol _DMACH@4
INVAR1.OBJ : error LNK2001: unresolved external symbol _DMACH@4
JOSA01.OBJ : error LNK2001: unresolved external symbol _DMACH@4
MAIN1D.OBJ : error LNK2001: unresolved external symbol _DMACH@4

where DMACH is defined asDOUBLE PRECISION but it is used in the subroutines as DMACH(1) or DMACH(2) orDMACH(3).

Can you help me again?

thank you very much!

G.

0 Kudos
Lorri_M_Intel
Employee
2,028 Views

Excellent news that we're making progress! smiley [:-)]

I don't know what you mean by saying that NEOLIN is declared as integer. Is it a function? Could you post the declaration please? Include the declarations of all arguments, too please.

And, would you do the same for DMACH?

Regards,

- Lorri

0 Kudos
gambato79
Beginner
2,028 Views

Hi Lorri...thanks again for your help! My progresses are going on!

I solved a lot of error smiley [:-)]....NEOLIN, DATCH ...and others are logical function or double precision function....so I could correct them simply.

Now ..... I have only4 errors :

Linking...
CONSTI.OBJ : error LNK2001: unresolved external symbol
_PZ3MAJ@68
SYSFUN.OBJ : error LNK2001: unresolved external symbol _SECONDS_SINCE_1980@4
SYSFUN.OBJ : error LNK2001: unresolved external symbol _EDATE@8
Debug/dyne1d.exe : fatal error LNK1120: 3 unresolved externals
Error executing link.exe.

dyne1d.exe - 4 error(s), 0 warning(s).

I analyzed each one in detail so you can understand better.

1. EDATE isavariable definedin my file SYSFUN.PCS (which is situated in Exteranl Dependencies in my Porject) as

CHARACTER edate*8
external edate

.....which is the meaning of .PCS? .

It is named in this file (SYSFUN.PCS ) in this way

C.... ALSO FOR THE DATE SUBROUTINE
c ENTRY DATE(TCHAR)
tchar=edate()//' '
GOTO 1999
C.... GET THE TIME NOW

what can I do??......but looking better inall my files I found that I have the same file but called SYSFUN.PC (initially I hadn't insert it in my workspace...and even if I insert it nothing changes)....what is the differnt with .PCS (if I put it in my workspace it go in Resource File ). Is there a correspondence between theese two things?

2. SECONDS_SINCE_1980 I thik it should be a subroutine....but I haven't it in my files. It is called by SYSFUN.PCS in this way

C.... INITIALIZE SECONDS COUNTER
1010 CONTINUE call seconds_since_1980(dtime)
last_time=dtime

where the varaibles are defined at the beggining of SYSFUN.PCS in this way:

IMPLICIT NONE
save last_time
C.... INPUT VARIABLES
INTEGER ISWCH,ICOUT
C.... OUTPUT VARIABLES
INTEGER IVALU
CHARACTER TCHAR*(*),time*8,edate*8
external time,edate
real*8 dtime,last_tim e

3. PZ3MAJ is a subroutine defined as

SUBROUTINE PZ3MAJ
IMPLICIT NONE
C..CG
Ctutte le variabili inserite servono per eliminare un errore
C LNK 2001 dato che in la subroutine PZ3S01 definita con
Ctutte queste variabili.
CIl significato di tutte le variabili si trova nella subrotuine PZ3S01.
C..CG
integer NSTRE
PARAMETER (NSTRE=4)
integer ICELS
integer ICOUT
double precision SNPHG,XMFMG
double precision ALFAF,ALFAG
double precision HEV0P,HES0P
double precision RLOAD
double precision BETA0,BETA1
double precision ESTRE(NSTRE)
double precision DSTAN(NSTRE)
double precision DSTRE(NSTRE)
double precision H0LOD,H0UNL
double precision GAMDM,GAMHU
double precision ETAMX
double precision HUCUR
double precision PINIT
double precision PDEVS
CALL PZ3S01 (ESTRE,SNPHG,XMFMG,ALFAF,ALFAG,HEV0P,HES0P
1,RLOAD,DSTAN,DSTRE,ICELS,BETA0,BETA1,H0LOD,H0UNL,GAMDM,GAMHU
2,ETAMX,HUCUR,PINIT,PDEVS
3,ICOUT)
RETURN
END

it is called by another subroutine (CONSTI.FOR) as

CALL PZ3MAJ(PROPD,LPRPD,ISWDP,ICDAT,ICOUT,DSTRE,DSTAN
1 ,DMATX,GAUSM,GAUSM(5),LPARA,IELEM,IGAUS,VOIDR,ICPRT
1 ,KTEST,NTEST)

where:INTEGER: LPRPD, ISWDP, ICDAT, ICOUT, IELEM, IGAUS, LPARA, ICPRT, NTEST, KTEST(NTEST), NSTRE

DOUBLE PRECISION PROPD(LPRPD), DSTRE(NSTRE), DSTAN NSTRE), DMATX(NSTRE), GAUSM(MGMOD), VOIDR

I tried to introduce all theese variables in the princiapl subroutine PZ3MAJ....but I have others errors,too....is it okand I have to correct theese others errors or do I have to do otherwise?

Can you help me again? .....Sorry for my long written!

G.

0 Kudos
Lorri_M_Intel
Employee
2,028 Views

Hi G. -

Let me do the easiest one first. Is this truly how PZ3MAJ is exactly defined?

SUBROUTINE PZ3MAJ
IMPLICIT NONE

Because, according to this definition, PZ3MAJ has 0 arguments ! If there are arguments, they need to be specified in a parenthesized list before the "IMPLICIT NONE".

Now, the other two. First, the ".PCS" extension is not one that's known to DevStudio. Is SYSFUN.PCS included by a different file, one with a Fortran-like extension, such as .f, .for, .f90, etc?

That said, I think I understood that you said you couldn't find any source code for either EDATE or SECONDS_SINCE_1980 in your project. Are you porting from Salford's F77? I found both of those routines online in a reference manual.

You will have to replace the calls to EDATE and SECONDS_SINCE_1980 with different routines. From the manual I found online, SECONDS_SINCE_1980 (real*8 seconds) returns the number of seconds that have elapsed since 12AM on January 1, 1980. EDATE returns the date in the format DD/MM/YY (that would be the character *8 value).

To replace these, please look at the standard routine DATE_AND_TIME. Also, CVF has a routine, SECNDS, which you might be able to use to replace SECONDS_SINCE_1980, depending on what your code is doing with that routine. You will have to be the best judge of that!

Anyway - I think this will finally resolve your external routine problems! Good luck with the rest!!

- Lorri

0 Kudos
gambato79
Beginner
2,028 Views

Excuse me Lorri, but Ishould haveother two questions.

1. First of all the file SYSFUN.PCS is included in SYSFUN.FOR....then, I eliminated two errors but remain :
SYSFUN.OBJ : error LNK2001: unresolved external symbol _SECONDS_SINCE_1980@4
Debug/dyne1d.exe : fatal error LNK1120: 1 unresolved externals
Error executing link.exe.

dyne1d.exe - 2 error(s), 0 warning(s)

I saw SECONDS_SINCE_1980 routine in the manual on line and the argument is declared in the same wayin may code.I try to replaced it with SECNDS_ and othersbut the error remain. I report you SYSFUN.PCS

c SUBROUTINE SYSFUN(TCHAR,IVALU,ISWCH,ICOUT)
C....
C DUMMY SUBROUTINE FOR SYSTEM DEPENDENT FUNCTIONS
c *** updated for PC FTN77 compiler
c cpu time is now in centi-seconds
C....
IMPLICIT NONE
save last_time
C.... INPUT VARIABLES
INTEGER ISWCH,ICOUT
C.... OUTPUT VARIABLES
INTEGER IVALU
c..CG..edate*8 serve dichiararlo solo se si usa la routin EDATE....che x
c......ho sostituito con DATE...vedi pi avanti.
c..CG..
CHARACTER TCHAR*(*),time*8,edate*8,date*8
external time,edate
real*8 dtime,last_time
c
C.... GOTO SPECIFIC FUNCTIONS
GOTO (1010,1020,1030,1040,1050,1060,1070,1080,1090,1100
1 ,1110),ISWCH
C.... ERROR CASE
WRITE(6,*)'UNKNOWN OPTION IN SYSFUN:',ISWCH
WRITE(ICOUT,*)'UNKNOWN OPTION IN SYSFUN:',ISWCH
CALL STACKP
GOTO 1999
C.... INITIALIZE SECONDS COUNTER
1010 CONTINUE
call seconds_since_1980(dtime)
last_time=dtime
GOTO 1999
C.... GET MAXIMUM ALLOWABLE CPU-SECONDS
1020 CONTINUE
IVALU=2147483640 ! ftn77 maximum integer*4 number
GOTO 1999
C.... GET THE CPU-SECONDS USED SINCE LAST INITIALIZATION
1030 CONTINUE
call seconds_since_1980(dtime)
ivalu=nint(100.0d0*(dtime-last_time))
GOTO 1999
C.... GET THE DATE FOR TODAY
1040 CONTINUE
C.... ALSO FOR THE DATE SUBROUTINE
c ENTRY DATE(TCHAR)
c..CG..per eliminare l'errore LNK2001 ho sostituito la subroutine
c EDATE(che restituisce da data in formato americano MM/DD/YY)
c con DATE (che restituisce da data in formato europeo GG/MM/AA).
c..CG..
tchar=date()//' '
GOTO 1999
C.... GET THE TIME NOW
1050 CONT INUE
C.... ALSO FOR THE TIME SUBROUTINE
c ENTRY TIME(TCHAR)
tchar=time()
GOTO 1999
C.... GET THE PAGE FAULTS UP TO NOW
1060 CONTINUE
IVALU=0
GOTO 1999
C.... GET THE SYSTEM NAME
1070 CONTINUE
TCHAR='SYSTEM NAME'
GOTO 1999
C.... GET THE USERID
1080 CONTINUE
TCHAR='USERID'
GOTO 1999
C.... GET THE GROUP
1090 CONTINUE
TCHAR='CIVIL ENGINEERING'
GOTO 1999
C.... JOBNAME
1100 CONTINUE
TCHAR='DIANA-SWANDYNE II / GLADYS'
GOTO 1999
C.... hardware platform and software operating system
1110 continue
c....
c iplat: 1 PC with Salford Fortran 77/90 compiler
c 2 IBM 3090
c 3 IBM Phoenix
c 4 VAX/VMS
c 5 SUN UNIX
c....
ivalu=1
call sysnam(tchar,ivalu)
goto 1999
C.... COMMON EXIT
1999 CONTINUE
RETURN
END
subroutine date(tchar)
character*(*) tchar
entry time(tchar)
call termin('date function is called')
return
c end

2. Considering another code....simpler than the first; I have a file.for, in wich there are the main program and the subroutines that it calls, a file.dat, which is my input file,and a file.inc. My problem is that my code can't open the file.inc....so I have 30 errors of this type:
...path...esecuzioneeasyup.for(1886) : Error: Cannot open include file 'kindfile'
include 'kindfile'
--------------^
.....path ....esecuzioneeasyup.for(1896) : Error: A kind type parameter must be a compile-time constant. [NKIND]
real (kind=nkind) AMATX(MDIMN,JPRNT),real0
-----------------^
....path.....esecuzioneeasyup.for(2073) : Error: Cannot open include file 'kindfile'
include 'kindfile'
----------------^
....path.....esecuzioneeasyup.for(2084) : Error: A kind type parameter must be a compile-time constant. [NKIND]
real (kind=nkind) avect(ndimn),toler
-----------------^
...path....esecuzioneeasyup.for(2127) : Error: Cannot open include file 'kindfile'
include 'kindfile'
----------------^
....path......esecuzioneeasyup.for(2129) : Error: A kind type parameter must be a compile-time constant. [NKIND]
&n bsp; real (kind=nkind) a(n)

I think it depends on where I put my file.inc.....I tried in every folder inside my workspace...but I didin't solve my problem. Instead if I insert the variables written in file.inc in my code directly the errors decrease...but I would understand howI can do using the file.inc. Besides looking on line I found that some include file have .h extension. What is the difference between .inc and .h?

Thank you very very much again!!!!

G.

0 Kudos
Lorri_M_Intel
Employee
2,028 Views

We are so close to fixing all your problems ... smiley [:-)]

RE: SECONDS_SINCE_1980

That's NOT a CVF routine. It was an extension that was in Salford's F77

You can use the CVF function SECNDS, which requires a real*4 argument and returns either the current time, or the elapsed time. From your code above, you'd change it to:

real*4 rtime, etime
rtime = secnds(0.0)
GOTO 1999
C.... do something here

1030 CONTINUE
etime=secnds(rtime)
ivalu=nint(100.0*(etime))

Now the last one, you can't find the includedfile 'kindfile'.

In the Developer Studio, under Project-> Settings you'll get a dialog box. Select the Fortran tab, and then select "Preprocessor". You'll see a place where you can put the include directory of "kindfile".

I do have a second question; is your file exactly named "kindfile", or is it kindfile.h, or kindfile.fi or kindfile.inc, or something else? When Fortran sees the statement

include "kindfile"

it looks for a file with the exact name "kindfile". No extension. Is that what you've got here?

- Lorri

0 Kudos
fogler
Beginner
2,028 Views
hi guys
your discussion is very intresting
I have similar problem but slightly different.
here is the error mesage
Linking...
dfor.lib(DFORMAIN.OBJ) : error LNK2001: unresolved external symbol _MAIN__
Debug/derpar.exe : fatal error LNK1120: 1 unresolved externals
Error executing link.exe.

Iam trying to run DERPAR(http://netlib.org/toms/502).

Any idea in eliminating error is great help for me.

I used the code as it is with my own inputs to variables.
0 Kudos
Steven_L_Intel1
Employee
2,028 Views
You have no main program. DERPAR is just a subroutine - you need a main program that calls DERPAR with the proper arguments.
0 Kudos
fogler
Beginner
2,028 Views
Thanks Steve for yor reply. Iam new to Fortran programing. I read somewhere that we can run subroutine independently.
0 Kudos
Steven_L_Intel1
Employee
2,028 Views
No, a subroutine cannot be run on its own. You need a main program and some code to display the results. This would be the case in any programming language I am aware of.
0 Kudos
Reply