Skip to main content

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index] [List Home]
Re: [photran] Parsing errors, but compilations is successful

Syntax Error:  Unexpected subroutine:
--------------------------------------------------
SUBROUTINE TEST(DQ, Q, X, NL, NR, TAU, DT)
    IMPLICIT NONE
    
    !---INPUT/OUTPUT ARGUMENTS
    INTEGER,  INTENT(IN)    :: NL, NR
    REAL(WP), INTENT(IN)    :: TAU, DT
    REAL(WP), INTENT(IN)    :: X(NL-NBP:NR+NBP)
    REAL(WP), INTENT(IN)    :: Q(NL-NBP:NR+NBP, 1:NEQ)
    REAL(WP), INTENT(OUT)   :: DQ(NL-NBP:NR+NBP, 1:NEQ)
   
    !---LOCAL VARIABLES
    INTEGER :: J
    REAL(WP), ALLOCATABLE, DIMENSION(:,:) :: FLUX
        
    ALLOCATE(FLUX(NL-NBP:NR+NBP, 1:NEQ))
    DQ = 0.0_WP

    CALL PREDICT_TVD_FLUXES(FLUX, Q, X, NL, NR, TAU, DT)    
    FORALL (J = NL:NR) DQ(J,:) =  - TAU*(FLUX(J,:) - FLUX(J-1,:))    

    DEALLOCATE(FLUX)
    
END SUBROUTINE TEST
-----------------------------------------------------



Syntax Error: Unexpected deallocate
-----------------------------------------------
SUBROUTINE TEST2(FLUX, Q, NL, NR)
    IMPLICIT NONE

    !---INPUT/OUTPUT ARGUMENTS
    INTEGER,  INTENT(IN)    :: NL, NR
    REAL(WP), INTENT(IN)    :: Q(NL-NBP:NR+NBP, 1:NEQ)
    REAL(WP), INTENT(OUT)   :: FLUX(NL-NBP:NR+NBP, 1:NEQ)

    !---LOCAL VARIABLES
    INTEGER   :: J, JP1, K, NS, NF
    REAL(WP)  :: M_HALF, M_PLUS, M_MINUS, P_PLUS, P_MINUS, DW
    REAL(WP), PARAMETER :: ALPHA = 0.1875_WP, BETA = 0.125_WP
    REAL(WP), ALLOCATABLE, DIMENSION(:)   :: A_NUM, A_LOC, M_L, M_R, FV
    REAL(WP), ALLOCATABLE, DIMENSION(:,:) :: QP, FC, FP, FLXC, FLXP

    ALLOCATE(A_NUM(NL-NBP:NR+NBP), A_LOC(NL-NBP:NR+NBP))
    ALLOCATE(M_L(NL-NBP:NR+NBP-1), M_R(NL-NBP:NR+NBP-1), FV(1:NPE))

    ALLOCATE(QP(NL-NBP:NR+NBP, 1:NPP))
    ALLOCATE(FC(NL-NBP:NR+NBP, 1:NPE), FP(NL-NBP:NR+NBP, 1:NPE))
    ALLOCATE(FLXC(NL-NBP:NR+NBP, 1:NPE), FLXP(NL-NBP:NR+NBP, 1:NPE))

    DO K = 1, NPHASE

      !  irrelevant code

    ENDDO

    DEALLOCATE(A_NUM, A_LOC, M_L, M_R, FV)
    DEALLOCATE(QP, FC, FP, FLXC, FLXP)


END SUBROUTINE TEST2
---------------------------------------



Syntax Error: Unexpected call
------------------------------------------------
SUBROUTINE TEST3(S_NC, U_NC, U, X, NL, NR)
    IMPLICIT NONE
        
    !---INPUT/OUTPUT ARGUMENTS
    INTEGER,  INTENT(IN)    :: NL, NR 
    REAL(WP), INTENT(IN)    :: X(NL-NBP:NR+NBP)
    REAL(WP), INTENT(IN)    :: U(NL-NBP:NR+NBP, NEQ)
    REAL(WP), INTENT(IN)    :: U_NC(NL-NBP:NR+NBP, NEQ)
    REAL(WP), INTENT(OUT)   :: S_NC(NL-NBP:NR+NBP, NEQ)

    !---LOCAL VARIABLES
    INTEGER   :: I
    REAL(WP), ALLOCATABLE, DIMENSION(:,:) :: DQ, H, H_PLUS, H_MINUS
 
    ALLOCATE(DQ(NL-NBP+1:NR+NBP, NEQ))
    ALLOCATE(H(NEQ, NEQ), H_PLUS(NEQ, NEQ), H_MINUS(NEQ, NEQ))
    
    FORALL(I=NL-NBP+1:NR+NBP) DQ(I,:) = U_NC(I,:) - U_NC(I-1,:)
           
    DO I=NL-NBP+1, NR+NBP-1
       CALL INTERFACE_MATRIX(H, U(I,:), X(I))                        !THIS CALL RESULTS IN ERROR
       H_PLUS  = (H + ABS(H))/2.0_WP
       H_MINUS = H - H_PLUS
       
       S_NC(I,:)= MATMUL(H_PLUS, DQ(I,:)) + MATMUL(H_MINUS, DQ(I+1,:))
    ENDDO

    DEALLOCATE(DQ, H, H_PLUS, H_MINUS)
    
END SUBROUTINE TEST3

---------------------------------------------------------------------


----- Original Message ----
From: Ralph Johnson <johnson@xxxxxxxxxxx>
To: Photran Information <photran@xxxxxxxxxxx>
Sent: Friday, May 29, 2009 4:10:18 PM
Subject: Re: [photran] Parsing errors, but compilations is successful

On Fri, May 29, 2009 at 8:50 AM, S Kalogerakos <sk287@xxxxxxxxx> wrote:
>
> Hi,
>
> I saw from previous posts that other users have similar problems.  Basically some fortran (F90) files give a Syntax Error of some kind, but they compile successfully.  It may have something to do with fixed-format issues, but I was not able to find any way of forcing the editor to only choose one type.

Can you post the Fortran source code?   There might very well be bugs
in the parser, and this is how we would find them.

The Photran parser cannot understand preprocessor commands.  So, if
you are using the C preprocessor then this could explain it.

-Ralph Johnson
_______________________________________________
photran mailing list
photran@xxxxxxxxxxx
https://dev.eclipse.org/mailman/listinfo/photran



      


Back to the top