Error: Procedure at (1) with assumed-shape dummy argument must have an explicit interface

I’ve tried to follow the directions given. This is the closest I’ve come. I don’t like using the explicit interface because there are too many routines in the program. What do I do?

Thanks,

   LOGICAL FUNCTION RUZE(CARD1,CARD2,LENGTH)
   IMPLICIT NONE
   INTEGER LENGTH
   CHARACTER CARD1*(*)
   CHARACTER*(*) CARD2(*)
  
   RUZE = .FALSE.
  
   IF (CARD1(1:1).EQ.'$')THEN
     IF (CARD2(LENGTH)(LENGTH:LENGTH).EQ.' ')THEN
      GOTO 10
     ELSE
      GOTO 20
     ENDIF 
    ENDIF

10 RUZE = .TRUE.
20 RETURN 
   END
  
  SUBROUTINE MAKE_MOVE(STD)
    IMPLICIT NONE
    LOGICAL RUZE
    CHARACTER(*) :: STD(:) 
    CHARACTER REPRESENT*10
    
    IF(RUZE(REPRESENT(1:7),STD(1:7),7))THEN
     WRITE (*,*) 'STEP1 SUCCESSFUL'
    ENDIF
        
    RETURN
  END

Program PLAYING
 IMPLICIT NONE
 INTEGER MOVES
 PARAMETER (MOVES=100)
 CHARACTER*15 BIGMOVE(MOVES)
 CALL MAKE_MOVE(BIGMOVE)
End Program PLAYING
  gfortran -c -g test.f90 -o teset.o
  gfortran -g test.o -o a.out -lgfortran

CALL MAKE_MOVE(BIGMOVE)
              1
Error: Procedure 'make_move' at (1) with assumed-shape dummy argument 'std' must have an explicit interface

You put all the procedures in a module and USE the module in the main program. See Doctor Fortran Gets Explicit - Again! - Doctor Fortran (stevelionel.com) for some more elaboration.

2 Likes

Take out all declarations of the module procedures (such as LOGICAL RUZE in MAKE_MOVE) - putting the procedure in a module creates the explicit interface. When you add a local declaration, that overrides the one in the module and makes it look like it’s an external procedure (not from a module.)

2 Likes

Bookmarked. I found nice (and fun) stuff there. @@xtio if I recall VAX commands correctly (I was late in the party to remember much of it,) :laughing: