Silverfrost Forums

Welcome to our forums

Error in Checkmate -.NET?

28 Mar 2016 3:31 #17350

I am using since years a program for the Cholesky Decomposition, which is incorporated in several programs. Recently I tried to run one of these programs with the compiler option Checkmate -.NET in Plato as well as in Visual Studio Community 2013. In both environments the program failed with the error message

Salford.Fortran.Checkexception: 420: Reference through NULL Fortran Pointer. The option Checkmate-Win32 does not give this error. I have tried to localize the problem and I ended up with the two programs, which demonstrate the problem:

WinApp

!   ##############
    Program Case01
!   ##############

      Implicit None

!     ------------------------------------------------------------------
      Double Precision , Dimension (:,:), Allocatable :: A
      Double Precision , Dimension (:  ), Allocatable :: X, B, diag
 
      Integer                                         :: j, k, n, nwrite

      Logical                                         :: Fail

      Double Precision                                :: sum
 
      Interface
        SUBROUTINE choldc (a, p, fail)
          Double Precision , DIMENSION (:,:), INTENT (INOUT) :: a
          Double Precision , DIMENSION (:  ), INTENT (OUT)   :: p
          Logical                           , INTENT (out)   :: fail  
        End SUBROUTINE choldc
      End Interface
 
!     ------------------------------------------------------------------
 
      n = 3
 
      Allocate  ( A     ( 1:n, 1:n ) )
      Allocate  ( B     ( 1:n               ) )
      Allocate  ( X     ( 1:n               ) )
      Allocate  ( diag  ( 1:n               ) )
 
!     ------------------------------------------------------------------

      nwrite = 10
      Open ( Unit = nwrite, File = 'Case01.out' )

!     --- Example for normal system

      a (1,1) = 10206.0625000d+00
      a (1,2) = 9.62500000000d+00
      a (1,3) = 4.81250000000d+00
      b (  1) = 55.7644855000d+00
      a (2,1) = 0.00000000000d+00
      a (2,2) = 0.125000000000d+00
      a (2,3) = 6.250000000000d-02
      b (  2) = 0.699064500000d+00
      a (3,1) = 0.00000000000d+00
      a (3,2) = 0.00000000000d+00
      a (3,3) = 6.250000000000d-02
      b (  3) = 0.335322250000d+00

!     --- Fill in below the diagonal from symmetry

      Do j = 2, n
        Do k = 1, j-1
          A(j,k) = A(k,j)
        end Do
      End Do
 
!     ------------------------------------------------------------------
 
!     --- Calculate Cholesky factor L
 
!          L is stored in lower triangle of A,
!          except for its diagonal elements
!          which are returned in diag
 
 
!     ###########
      Call Choldc ( A    (1:n, 1:n),  &
                    diag (1:n)     ,  &
                    Fail                 )
!     ########### 
 
!     ------------------------------------------------------------------
 
!     ======================
      if ( .not. Fail ) then
!     ======================

        Write ( nwrite, * )
        Write ( nwrite, * ) ' Problem runs OK'
        Write ( nwrite, * ) ' ###############'
        Write ( nwrite, * )
 
        Write (   *   , * )
        Write (   *   , * ) ' Problem runs OK:'
        Write (   *   , * ) ' ################'
        Write (   *   , * )
 
        Pause
        Stop
!       ++++
 
!     ======
      end if
!     ======
 
!   ##################
    End Program Case01
!   ##################
 





      Subroutine choldc ( A, p, Fail )

        Implicit None

        Double Precision , Dimension (:,:)  , Intent (inout) :: A
        Double Precision , Dimension (:)    , Intent (out)   :: p
        Logical                             , Intent (out)   :: Fail

        Logical                                              :: HPFortran

        Fail = .false.
 
!!!     HPFortran = .false.
        HPFortran = .true.
 
!       ---------------------
        If ( HPFortran ) Then
!       ---------------------
 
          Call Choldc_95 
 
!       ---- 
        Else
!       ---- 
 
          Call Choldc_77 
 
!       ------ 
        End If
!       ------ 

!     ------------------------------------------------------------------

      Contains

!     ------------------------------------------------------------------


      SUBROUTINE choldc_77 

        Implicit None

!       ----------------------------------------------------------------    
    
        Fail = .false.
!       --- Just for formal reasons
        p(1) = a(1,1)
        p(2) = a(2,2)
        p(3) = a(3,3)
        Return

      END SUBROUTINE choldc_77


      Subroutine choldc_95 

        Implicit None

        fail = .false.
!       --- Just for formal reasons
        p(1) = a(1,1)
        p(2) = a(2,2)
        p(3) = a(3,3)
        Return

      End Subroutine choldc_95

End Subroutine choldc

Both programs can also be run with little batch files:

  1. Checkmate-Win32 (LinkListCheckMate):

    Load Case01.obj Load choldc.obj File Case01.exe

and RunCheckMate.bat:

del comp.lis
del *.dbk
del *.obj
del *.exe
ftn95 Case01.f95 /Checkmate /Debug   >> comp.lis
ftn95 Choldc.f95 /Checkmate /Debug   >> comp.lis
slink LinkListCheckMate              >> comp.lis
sdbg Case01.exe
  1. Checkmate-.NET (LinkListNet; normally I do not work with batch files for .NET)

    Case01.exe Case01.dbk choldc.dbk

and RunNET.bat:

del comp.lis
del *.mod
del *.dbk
del *.exe

ftn95 Case01.f95 /Checkmate /Full_Debug /clr /clr_ver 4 >> comp.lis
ftn95 Choldc.f95 /Checkmate /Full_Debug /clr /clr_ver 4 >> comp.lis
  
DBK_Link4 @linklistNET                                  >> comp.lis

Case01.exe

Have I somewhere overlooked something? Best regards KL

28 Mar 2016 3:36 #17351

I try to continue:

      Subroutine choldc ( A, p, Fail )

        Implicit None

        Double Precision , Dimension (:,:)  , Intent (inout) :: A
        Double Precision , Dimension (:)    , Intent (out)   :: p
        Logical                             , Intent (out)   :: Fail

        Logical                                              :: HPFortran

        Fail = .false.
 
!!!     HPFortran = .false.
        HPFortran = .true.
 
!       ---------------------
        If ( HPFortran ) Then
!       ---------------------
 
          Call Choldc_95 
 
!       ---- 
        Else
!       ---- 
 
          Call Choldc_77 
 
!       ------ 
        End If
!       ------ 

!     ------------------------------------------------------------------

      Contains

!     ------------------------------------------------------------------


      SUBROUTINE choldc_77 

        Implicit None

!       ----------------------------------------------------------------    
    
        Fail = .false.
!       --- Just for formal reasons
        p(1) = a(1,1)
        p(2) = a(2,2)
        p(3) = a(3,3)
        Return

      END SUBROUTINE choldc_77


      Subroutine choldc_95 

        Implicit None

        fail = .false.
!       --- Just for formal reasons
        p(1) = a(1,1)
        p(2) = a(2,2)
        p(3) = a(3,3)
        Return

      End Subroutine choldc_95

End Subroutine choldc
28 Mar 2016 3:46 #17352

Both programs can also be run with little batch files:

  1. Checkmate-Win32 (LinklistCheckmate, RunCheckmate.bat:)

    Load Case01.obj Load choldc.obj File Case01.exe

and

del comp.lis
del *.dbk
del *.obj
del *.exe
ftn95 Case01.f95 /Checkmate /Debug   >> comp.lis
ftn95 Choldc.f95 /Checkmate /Debug   >> comp.lis
slink LinkListCheckMate              >> comp.lis
sdbg Case01.exe
  1. Checkmate-.NET (LinkListNet, RunNet.bat; normally I do not work with batch files for .NET)

    Case01.exe Case01.dbk choldc.dbk

and

del comp.lis
del *.mod
del *.dbk
del *.exe

ftn95 Case01.f95 /Checkmate /Full_Debug /clr /clr_ver 4 >> comp.lis
ftn95 Choldc.f95 /Checkmate /Full_Debug /clr /clr_ver 4 >> comp.lis
  
DBK_Link4 @linklistNET                                  >> comp.lis

Case01.exe

Have I somewhere overlooked something? Best regards KL

29 Mar 2016 8:33 #17360

Hi KL

Nice to know that you are using the Cholesky Decomposition program. May I know the areas of application of this Cholesky algorithm, that you use. Do you also deal with the Sparse Networks (Largely zeros) and what is the speed performance of this algorithm, say for Matrix inverse calculations?

Do you have the comparative speed performances of different algorithms.

29 Mar 2016 11:56 #17362

Thank you very much for your interest, Moorthy. I use the algorithm from Numerical Recipes both in FORTRAN 77 and Fortran 90. In this book you find also a comprehensive discussion of solutions of linear algebraic equations. Best regards, KL

7 Jun 2016 9:00 #17565

The same happens with FTN95 8.0. Any ideas?

7 Jun 2016 10:54 #17567

You could use /inhibit_check 10 with /check etc. I have not checked your code but this check relates to checking the overwriting of a DO-loop index. It might be a problem with your code or it might be a bug in the compiler.

8 Jun 2016 3:08 #17601

Thank you Paul, I will test your proposal.

The problem is

either Checkmate/Win32 overlooks an error,

or Checkmate/.NET reports an error, which is no error.

Regards, Klaus

9 Jun 2016 6:53 #17609

Paul, using the option /inhibit_check 10 solves this problem. But I do not know why.

The new Plato version offers 9 different (standard) compiler options: Checkmate, Debug and Release, each combined with .NET, Win32 and x64. Only the combination Checkmate/.NET fails, all other 8 combinations succeed.

Of course the code snippet is rather nonsense, but the original 'full' code is a standard algorithm used frequently by many users. Finding a hidden or an indirect error in the program would be very helpful, the more since this 'technique' is applied in other algorithms also. Klaus

9 Jun 2016 8:23 #17610

The failure is probably in FTN95/.NET but I hope that you can manage by using the work-around. If a fix is critical for you work then please let me know.

9 Jun 2016 12:27 #17612

Thank you very much, Paul.

This 'error' (if it is an error at all) is not critical for me. Please inform me, if something is questionable in my program.

Klaus

9 Jun 2016 12:32 #17613

OK. At the moment there is no reason to think that there is anything wrong with your code.

26 Oct 2016 8:51 #18236

Paul, did anything happen with this 'error'? Best regards KL

26 Oct 2016 10:05 #18237

No. This is still on the list of things to do.

Please login to reply.