forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Problem with SDBG

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
KL
Guest





PostPosted: Thu Oct 25, 2007 4:11 pm    Post subject: Problem with SDBG Reply with quote

Dear Paul,

I have a problem with the debugger. Unfortunately, the demonstration program is quite long although I have cut it to what is necessary. The main program “Driver_Broyden” calls “Allocate_Broyden_A” and “Initialize_Broyden_A”. All programs use the modules “DataTypes” and “CommonData_Broyden. The full program uses the subroutine “Broyden_A”, which needs an interface. The full program shows a strange effect: the debugger gives completely wrong information for the fields “mat_broyden” and “vec_broyden”: the numbers are wrong and the type is INTEGER*4 instead of Real*8. However, the code seems to run fine.

The same effect can be achieved with the attached code fragment. It is interesting to note that the printout is correct. The effect does not appear if the interface block is commented out. I have used the latest version FTN95 V5.10.

I would be pleased if you could help solving this problem.

Best regards

Klaus Lassmann

Run.bat:

Code:


del comp.lis
del *.obj
del *.exe

ftn95 DataTypes.f95            /checkmate /underflow  >> comp.lis
ftn95 CommonData_Broyden.f95   /checkmate /underflow  >> comp.lis
ftn95 Driver_Broyden.f95       /checkmate /underflow  >> comp.lis
ftn95 Allocate_Broyden_A.f95   /checkmate /underflow  >> comp.lis
ftn95 Initialize_Broyden_A.f95 /checkmate /underflow  >> comp.lis

slink LinkFile
 
sdbg Broyden.exe
 


LinkFile:
Code:

LOAD DataTypes
LOAD CommonData_Broyden
LOAD Driver_Broyden
LOAD Allocate_Broyden_A
LOAD Initialize_Broyden_A
file Broyden.exe


DataTypes.f95:

Code:

      MODULE DataTypes
        INTEGER  , PARAMETER :: I4B    = SELECTED_INT_KIND (9)
        INTEGER  , PARAMETER :: I2B    = SELECTED_INT_KIND (4)
        INTEGER  , PARAMETER :: I1B    = SELECTED_INT_KIND (2)
        INTEGER  , PARAMETER :: SP     = KIND (1.0)
        INTEGER  , PARAMETER :: dp     = KIND (1.0D0)
        INTEGER  , PARAMETER :: LGT    = KIND (.true.)
      END MODULE DataTypes


CommonData_Broyden.f95:
Code:


  Module CommonData_Broyden
 
    Use DataTypes
    Implicit None
 
!                                  stored in vec_Broyden :
!                                              x_Broyden_new    = unknown
!                                              x_Broyden_old    = previous unknown
!                                              F_Broyden_new    = new Function value
!                                              F_Broyden_old    = old Function value

!                                  stored in mat_Broyden :           
!                                              B_Broyden_m1     = invers Broyden matrix
 
    Real (dp), Dimension (:,:)  , Allocatable , save :: vec_Broyden

    Real (dp), Dimension (:,:,:), Allocatable , save :: mat_Broyden 

    Logical (lgt)                                    :: Method_A      = .true.
    Logical (lgt)                                    :: Update_simple = .false.

  End Module CommonData_Broyden



Driver_Broyden.f95:
[code:1:a3906c7643]
Winapp

Program Driver_broyden

! --- Driver_broyden is the driver for subroutine Broyden

Use DataTypes
Use CommonData_Broyden

Implicit None

Interface
Subroutine Broyden_A ( Iter , &
x_new , &
x_old , &
f_new , &
f_old , &
B_m1 , &
Update_simple )
Use DataTypes
Implicit None
Back to top
KL
Guest





PostPosted: Thu Oct 25, 2007 4:15 pm    Post subject: Problems with SDBG Reply with quote

Paul, I am sorry, but my message was not correctly sent. I had checked it and everything looked fine. Should I send it again or is the message too long?
Klaus
Back to top
KL
Guest





PostPosted: Thu Oct 25, 2007 5:20 pm    Post subject: Problems with SDBG Reply with quote

Paul, I just try sending the 3 missing programs.
Driver_Broyden.f95:
Code:

  Winapp

  Program Driver_broyden
 
!   ---     Driver_broyden is the driver for subroutine Broyden
 
    Use DataTypes
    Use CommonData_Broyden
 
    Implicit None

       Interface
          Subroutine Broyden_A ( Iter            ,  &
                                 x_new           ,  &
                                 x_old           ,  &
                                 f_new           ,  &
                                 f_old           ,  &
                                 B_m1            ,  &
                                 Update_simple         )
            Use DataTypes
            Implicit None
            Integer (i4b),                   Intent (in)    :: Iter
            Real    (dp) , Dimension (:)   , Intent (inout) :: x_new , &
                                                               x_old , &
                                                               f_new , &
                                                               f_old
            Real    (dp) , Dimension (:,:) , Intent (inout) :: B_m1
            Logical (lgt)                                   :: Update_simple
          End Subroutine Broyden_A
      End Interface


    Integer (i4b)             :: i, nrd, nwr, nDim, its


!   --- Open File
 
    nrd = 10
    Open ( Unit = nrd, File = 'broyden.inp')

    nwr = 11
    open ( unit = nwr, file = 'broyden.out')
 
!   --- Read Data
 
    Read  ( nrd, * )             nDim
    Write ( nwr, * )  'nDim = ', nDim

    Call Allocate_Broyden_A   (nDim)
!   #######################     

! STOP


    Call Initialize_Broyden_A (nDim)
!   #########################     


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

    Read  ( nrd, * )       ( vec_Broyden (i,1), i = 1, nDim )   ! x_new

    its = 0
 
    Write ( nwr, * )  its, ( vec_Broyden (i,1), i = 1, nDim )
 

!     Call Broyden_A ( Its                           ,  &
!                      vec_Broyden (1:nDim,       1) ,  &
!                      vec_Broyden (1:nDim,       2) ,  &
!                      vec_Broyden (1:nDim,       3) ,  &
!                      vec_Broyden (1:nDim,       4) ,  &
!                      mat_Broyden (1:nDim,1:nDim,1) ,  &
!                      Update_simple                )
 
    Stop

  End Program Driver_broyden
   


Allocate_Broyden.f95

Code:


  Subroutine Allocate_Broyden_A (n)
 
    Use DataTypes
    Use CommonData_Broyden
 
    Implicit None
    Integer (i4b), Intent (in) :: n
     
    Allocate ( vec_Broyden (1:n,    1:4) )
                   
    Allocate ( mat_Broyden (1:n,1:n,1:1) )


  End Subroutine Allocate_Broyden_A
 


Initialize_Broyden.f95

Code:


  Subroutine Initialize_Broyden_A (n)
 
    Use DataTypes
    Use CommonData_Broyden
 
    Implicit None
    Integer (i4b) :: i, n
     
!                                                                  -1
                    mat_Broyden (1:n,1:n,1)         = 0._dp     ! B

!    The Forall statement should better not be used

!    Forall (i=1:n) mat_Broyden (i, i, 1) = 1._dp

     Do i = 1, n
                    mat_Broyden (i, i, 1) = 1._dp
     End Do

  End Subroutine Initialize_Broyden_A
   


Input file broyden.inp:

Code:
2
0.8     0.4

Back to top
Robert



Joined: 29 Nov 2006
Posts: 445
Location: Manchester

PostPosted: Thu Nov 01, 2007 12:01 pm    Post subject: Reply with quote

Hi KL

Can you email your source files to ftn95@silverfrost.com
Back to top
View user's profile Send private message Visit poster's website
KL
Guest





PostPosted: Thu Nov 01, 2007 7:01 pm    Post subject: Problems with DDBG Reply with quote

Robert,

I have sent all files per given e-mail. Please let me know if you cannot open the attachments.

Best regards

Klaus Lassmann
Back to top
Robert



Joined: 29 Nov 2006
Posts: 445
Location: Manchester

PostPosted: Wed Nov 07, 2007 7:43 pm    Post subject: Reply with quote

Hmm... that is odd because we don't seem to have them. Did it have a .zip attachment?
Back to top
View user's profile Send private message Visit poster's website
KL
Guest





PostPosted: Thu Nov 08, 2007 5:52 pm    Post subject: Problems with SDBG Reply with quote

Robert, I have sent the files again via "ftn95@silverfrost.com". This time as Test46.zip.
Klaus
Back to top
KL
Guest





PostPosted: Tue Nov 20, 2007 4:43 pm    Post subject: Problems with SDBG Reply with quote

Robert, could you verify my problem?

Klaus
Back to top
KL
Guest





PostPosted: Sun Nov 25, 2007 5:07 pm    Post subject: Problems with SDBG Reply with quote

Robert,

I have checked the problem again and found that in the DOS box there is indicated error "unknown type 17". I looked carefully again to all details of the program, but I could find any error. May be that I have overlooked a trivial error already many times.

Unfortunately, this error occurs also in a much larger code, which I work on at the moment and this error makes a further development nearly impossible. So it would be really helpful, if you could give me your opinion.

Thank you very much and best regards

Klaus Lassmann
Back to top
KL
Guest





PostPosted: Fri Dec 07, 2007 6:18 pm    Post subject: Problems with SDBG Reply with quote

Robert,

anything new?

Klaus
Back to top
Robert



Joined: 29 Nov 2006
Posts: 445
Location: Manchester

PostPosted: Tue Dec 18, 2007 1:35 am    Post subject: Reply with quote

This is fixed in the next compiler release.
Back to top
View user's profile Send private message Visit poster's website
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group