Reconstruct interface from .mod and .o files

I have a set of module files and object files I compiled at some earlier date. In the meantime I accidentally overwrote the source files before version checking the old ones.

I would now like to verify if my procedures still have the same interfaces, and if the compiled object files produce the same results as the new files.

Is their a way to do this?

1 Like

In theory yes, but it may not be easy. You’ll need to refer to the documentation of the format of the .mod files for your compiler (if any is available). It must contain the interfaces for anything that is public from that module. Probably could contain some other stuff.

As for the object file, if you recompile and get exactly the same object file, then you’re good. That should be the case for “equivalent” source code compiled with the same options. Equivalent would include same variable names and order of operations, but should be independent of format.

You could also try a decompiler, but I don’t know of what exists out there for Fortran.

1 Like

I presume it would also need to be the same compiler ran with the same flags. (Hopefully, I didn’t change the Makefile…)

yes

As Brad suggested the first thing I would try is check whether a new mod file matches the old mod file with a checksum for example.

In terms of extracting interfaces from mod files, I recall that lfortran was able to parse gfortran module files.

The relevant issue also links the gfort2py project which also seems to be able to parse gfortran module files:

3 Likes

We have some preliminary support to parse GFortran module files in LFortran and we plan to make it much more usable after we deliver MVP.

3 Likes

Intel Fortran .mod files are its own intermediate language and the format is private. Note also that there is a timestamp in the header, so a checksum comparison against a recompile won’t match.

2 Likes

Minimal documentation for GFortran .mod format in the sources [1]. It’s an gzipped text file with ‘lisp lists’; We just need some brave soul to translate it to human language.

[1] https://gcc.gnu.org/git/?p=gcc.git;a=blob_plain;f=gcc/fortran/module.c;hb=HEAD

3 Likes

Because I couldn’t find the format of .mod file on the net (but the page is now shown in the above comment!! thank you), I played around a bit with the following .mod file.

module mymod
    implicit none
    integer, parameter :: dp = kind(0.0d0)
contains

subroutine mysub1( n, x, z )
    integer  :: n
    real     :: x
    complex  :: z
    print *, n, x, z
end

subroutine mysub2( s, n, x, z )
    character(*), intent(in)    :: s
    integer,      intent(in)    :: n
    real(dp),     intent(out)   :: x
    complex(dp),  intent(inout) :: z
    x = 1.0; z = z + 1.0
    print *, s, n, x, z
end

subroutine mysub3( a1, a2, a3, b1, b2, c, n1, n2 )
    real    :: a1(:), a2(:,:), a3(:,:,:)
    real    :: b1( 123 ), b2( 456, 789 ), c( n1, n2 )
    integer :: n1, n2
    print *, a1, a2, a3, b1, b2, c, n1, n2
end

end module

Following this page (module - Is it possible to determine which Fortran compiler generated a ".mod" file? - Stack Overflow)

  $ gfortran-10 -c mymod.f90
  $ cp mymod.mod mymod.txt.gz
  $ gzip -d mymod.txt.gz
  $ cat mymod.txt

which shows (arrows by me)

GFORTRAN module version '15' created from mymod.f90
...

(2 'dp' 'mymod' '' 1 ((PARAMETER UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
IMPLICIT-SAVE 0 0) () (INTEGER 4 0 0 0 INTEGER ()) 0 0 () (CONSTANT (
INTEGER 4 0 0 0 INTEGER ()) 0 '8' ()) () 0 () () () 0 0)

3 'kind' '(intrinsic)' '' 1 ((PROCEDURE UNKNOWN-INTENT UNKNOWN-PROC
UNKNOWN UNKNOWN 0 0 FUNCTION ARRAY_OUTER_DEPENDENCY) () (UNKNOWN 0 0 0 0
UNKNOWN ()) 0 0 () () 3 () () () 0 0)

4 'mymod' 'mymod' '' 1 ((MODULE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN
UNKNOWN 0 0) () (UNKNOWN 0 0 0 0 UNKNOWN ()) 0 0 () () 0 () () () 0 0)

5 'mysub1' 'mymod' '' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE) () (UNKNOWN 0 0 0 0 UNKNOWN ())
6 0 (7 8 9) <-----
 () 0 () () () 0 0)

10 'mysub2' 'mymod' '' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE) () (UNKNOWN 0 0 0 0 UNKNOWN ())
11 0 (12 13 14 15) <------
 () 0 () () () 0 0)

16 'mysub3' 'mymod' '' 1 ((PROCEDURE UNKNOWN-INTENT MODULE-PROC DECL
UNKNOWN 0 0 SUBROUTINE ALWAYS_EXPLICIT) () (UNKNOWN 0 0 0 0 UNKNOWN ())
17 0 (18 19 20 21 22 23 24 25) <------
 () 0 () () () 0 0)

7 'n' '' '' 6 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) () (INTEGER 4 0 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
8 'x' '' '' 6 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
9 'z' '' '' 6 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0
DUMMY) () (COMPLEX 4 0 0 0 COMPLEX ()) 0 0 () () 0 () () () 0 0)

12 's' '' '' 11 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) ()
(CHARACTER 1 0 0 0 CHARACTER (())) 0 0 () () 0 () () () 0 0)
13 'n' '' '' 11 ((VARIABLE IN UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) ()
(INTEGER 4 0 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
14 'x' '' '' 11 ((VARIABLE OUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY) ()
(REAL 8 0 0 0 REAL ()) 0 0 () () 0 () () () 0 0)
15 'z' '' '' 11 ((VARIABLE INOUT UNKNOWN-PROC UNKNOWN UNKNOWN 0 0 DUMMY)
() (COMPLEX 8 0 0 0 COMPLEX ()) 0 0 () () 0 () () () 0 0)

18 'a1' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () (1 0 ASSUMED_SHAPE
(CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ()) ()) 0 () () () 0 0)
19 'a2' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () (2 0 ASSUMED_SHAPE
(CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ()) () (CONSTANT (INTEGER 4
0 0 0 INTEGER ()) 0 '1' ()) ()) 0 () () () 0 0)
20 'a3' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () (3 0 ASSUMED_SHAPE
(CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ()) () (CONSTANT (INTEGER 4
0 0 0 INTEGER ()) 0 '1' ()) () (CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0
'1' ()) ()) 0 () () () 0 0)

21 'b1' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () (1 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ()) (CONSTANT (INTEGER 4 0 0
0 INTEGER ()) 0 '123' ())) 0 () () () 0 0)
22 'b2' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DIMENSION DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ()) (CONSTANT (INTEGER 4 0 0
0 INTEGER ()) 0 '456' ()) (CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ())
(CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '789' ())) 0 () () () 0 0)
23 'c' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN 0
0 DIMENSION DUMMY) () (REAL 4 0 0 0 REAL ()) 0 0 () (2 0 EXPLICIT (
CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ()) (VARIABLE (INTEGER 4 0 0
0 INTEGER ()) 0 24 () ()) (CONSTANT (INTEGER 4 0 0 0 INTEGER ()) 0 '1' ())
(VARIABLE (INTEGER 4 0 0 0 INTEGER ()) 0 25 () ())) 0 () () () 0 0)

24 'n1' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DUMMY) () (INTEGER 4 0 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
25 'n2' '' '' 17 ((VARIABLE UNKNOWN-INTENT UNKNOWN-PROC UNKNOWN UNKNOWN
0 0 DUMMY) () (INTEGER 4 0 0 0 INTEGER ()) 0 0 () () 0 () () () 0 0)
)

('dp' 0 2 'kind' 0 3 'mymod' 0 4 'mysub1' 0 5 'mysub2' 0 10 'mysub3' 0
16)

so if .mod files are created by Gfortran, it might be possible to get some info somehow (though extremely unreadable…) I hope some tools like gfort2py (?) will show such info in a more readable way :mag:

3 Likes

Yes, here is how to parse it:

3 Likes