replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - Segmentation fault (reason not understood) help !!!!!!!!!!!
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 

Segmentation fault (reason not understood) help !!!!!!!!!!!

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
joemezni



Joined: 14 Jan 2013
Posts: 8

PostPosted: Wed Jan 23, 2013 8:26 pm    Post subject: Segmentation fault (reason not understood) help !!!!!!!!!!! Reply with quote

Hi all,
I have problem reading the data from a the software nastran.
I wrote a fortran function that read an output file from the software nastran , it reads all the keys correctly but when it comes to reading the main data which a matrix 441*9, the compiler said :

Segmentation fault

this is the output of the compilation
key= 3
M_D_Y 1 20 13
key= 7
NASTRAN
key= 2
Label=XXXXXXXX
key= -1
EOR
key= 0
EOF
key= 2
B_N BGPDTS
key= -1
EOR
key= 7
101 441 0 2646 2 0 441
key= -2
key= 1
Lgcrec= 0
key= 2
B_N BGPDT
key= -3
key= 1
type= 0
key= 5292
Segmentation fault



and this is my subroutine:

subroutine readtableBGPDT(Fileunit,Filename,Nnodes,dcoor)
implicit none
integer,parameter::iwp = selected_real_kind(Cool
type xyzcoord
integer,dimension(6)::wert
real(iwp),dimension(3)::xyzcoord
end type xyzcoord
integer::key,M,D,Y,i,Logirecord,tyype
integer,intent(in)::Nnodes,Fileunit
character,dimension(25)::T
character,dimension(Cool::L,BlckName,BlckName2
character(len=*),intent(in)::Filename
integer,dimension(7)::Trailor,Ta
type(xyzcoord),dimension(Nnodes,9)::dcoor
!
open(unit=Fileunit,file=Filename,status='old',form='unformatted',action='read')
!
rewind(Fileunit)
read(Fileunit) key
write(*,*)'key=',key
read(Fileunit) M,D,Y
write(*,*)'M_D_Y',M,D,Y
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)(T(i),i=1,7)
write(*,*)(T(i),i=1,7)
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)L
write(*,*)'Label=',L
read(Fileunit)key
write(*,*)'key=',key
write(*,*)'EOR'
read(Fileunit)key
write(*,*)'key=',key
write(*,*)'EOF'
!
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)BlckName
write(*,*)'B_N ',BlckName
read(Fileunit)key
write(*,*)'key=',key
write(*,*)'EOR'
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)(Ta(i),i=1,7)
write(*,*)(Ta(i),i=1,7)
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)Logirecord
write(*,*)'Lgcrec=',Logirecord
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)BlckName2
write(*,*)'B_N ',BlckName2
read(Fileunit)key
write(*,*)'key=',key
!
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)tyype
write(*,*)'type=',tyype
read(Fileunit)key
write(*,*)'key=',key
read(Fileunit)dcoor
write(*,'(I8,I8,I8,I8,I8,I8,F12.4,F12.4,F12.4)')dcoor
read(Fileunit)key
write(*,*)'key=',key
close(Fileunit)
end subroutine readtableBGPDT


and this the program that tests the above subroutine:
program ttz
implicit none
integer:: Fileunit=18 ,Nnodes=441
real,dimension(441,9)::dcoor
character(len=9)::Filename
parameter(Filename='bgpdt.op2')
call readtableBGPDT(Fileunit,Filename,Nnodes,dcoor)
write(*,*) '--------------------------'
write(*,'(9F10.4)') dcoor(1,1:9)
write(*,*) '--------------------------'
write(*,'(9F10.4)') dcoor(2,1:9)
write(*,*) '--------------------------'
write(*,'(9F10.4)') dcoor(3,1:9)
write(*,*) '--------------------------'
write(*,'(9F10.4)') dcoor(4,1:9)
write(*,*) '--------------------------'
end program ttz
Back to top
View user's profile Send private message
davidb



Joined: 17 Jul 2009
Posts: 560
Location: UK

PostPosted: Wed Jan 23, 2013 9:50 pm    Post subject: Reply with quote

One problem is that the Actual argument DCOOR and the Dummy argument DCOOR have different types. They MUST have the same type.

The real argument is an array of type REAL

The dummy argument is an array of type as follows:

Code:

type xyzcoord
   integer,dimension(6)::wert
   real(iwp),dimension(3)::xyzcoord
end type xyzcoord


In fact there is no way of calling this subroutine with this argument. As the derived type does not have an explicit interface, the derived type must have the SEQUENCE attribute like this:

Code:

type xyzcoord
   SEQUENCE
   integer,dimension(6)::wert
   real(iwp),dimension(3)::xyzcoord
end type xyzcoord

_________________
Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl


Last edited by davidb on Thu Jan 24, 2013 11:25 am; edited 1 time in total
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Thu Jan 24, 2013 7:35 am    Post subject: Reply with quote

David,

If TYPE xyzcoord was placed in a MODULE, used in both the main and subroutine, would SEQUENCE still be required ?
I would not have assumed it was, but your answer made me wonder.

John
Back to top
View user's profile Send private message
jalih



Joined: 30 Jul 2012
Posts: 196

PostPosted: Thu Jan 24, 2013 8:55 am    Post subject: Re: Reply with quote

JohnCampbell wrote:

If TYPE xyzcoord was placed in a MODULE, used in both the main and subroutine, would SEQUENCE still be required ?

I think, if type definition and subroutine are put inside a module then the SEQUENCE would not be required as module procedure has an excplicit interface and compiler can check actual and dummy arguments for consistency.
Back to top
View user's profile Send private message
davidb



Joined: 17 Jul 2009
Posts: 560
Location: UK

PostPosted: Thu Jan 24, 2013 11:17 am    Post subject: Re: Reply with quote

JohnCampbell wrote:
David,

If TYPE xyzcoord was placed in a MODULE, used in both the main and subroutine, would SEQUENCE still be required ?
I would not have assumed it was, but your answer made me wonder.

John


It depends! (Jalih's answer is along the right lines, but an explicit interface to the subroutine is not needed Wink)

If the Derived Type is declared in the interface to the module containing the subroutine then it doesn't need to be a SEQUENCE type, or if the derived type is declared in a module and then used by the subroutine and caller it doesn't need to be a SEQUENCE type.

For example, the following code is OK since the derived type is defined in a module.

Code:

module mmm

   type x_t
      real :: a
      real :: b
   end type

contains

   subroutine proc1(x)
      type(x_t) :: x
      ! do something with x
   end subroutine proc1

end module mmm

! external subroutine
subroutine proc2(x)
   use mmm, only: x_t
   type(x_t) :: x
   ! Do something with x
end subroutine proc2

program anon
   use mmm
   type(x_t) :: x
   call proc1(x)
   call proc2(x)
end


Note that an explicit interface to the subroutine IS NOT REQUIRED, as in the call to proc2.

However, in the following code, SEQUENCE is required because there is no definition of the Derived Type in the interface to the module.

Code:

module mmm

contains

   subroutine proc1(x)

      type x_t
         sequence
         real :: a
         real :: b
      end type

      type(x_t) :: x

      ! do something with x

   end subroutine proc1

end module mmm

! external subroutine
subroutine proc2(x)
   type x_t
      sequence
      real :: a
      real :: b
   end type
   type(x_t) :: x
   ! Do something with x
end subroutine proc2

program anon
   use mmm

   type x_t
      sequence
      real :: a
      real :: b
   end type

   type(x_t) :: x
   call proc1(x)
   call proc2(x)
end


If SEQUENCE was omitted from this example, then the Type(x_t) in each subroutine would technically be different from the Type(x_t) in the main program.

In fact, it is impossible to ever call a subroutine (or function) which has a non-sequence defined type dummy argument where the type definition is given local to the subroutine (or function).

However, there is a bug in Silverfrost's FTN95 compiler, which causes it to accept code like the call to proc1 in the second code listed above with the SEQUENCE omitted. This is currently being investigated by Paul (I have another thread on this).

The compiler DOES detect such errors when the subroutine is an external subroutine (not in a module), like the call to proc2, hence there is a need for the OP to address this when he fixes his code.
_________________
Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Fri Jan 25, 2013 12:35 am    Post subject: Reply with quote

David,

My typical use of derived type is in the example below, as I would define the derived type in the module. Do you expect that sequence is necessary in this case ?

John
Code:
module mmm

      type x_t
         real    :: a(3)
         real    :: b(2)
         integer :: i(5)
      end type
      type(x_t), parameter :: x_t_zero = x_t ( (/ 0., 0., 0. /), (/ 0., 0. /), (/ 0, 0, 0, 0, 0 /) )

contains

   subroutine proc1(x)

      type(x_t) :: x

      ! do something with x
      write (*,*) 'Proc1'
      write (*,*) ' a', x%a
      write (*,*) ' b', x%b
      write (*,*) ' i', x%i

   end subroutine proc1

end module mmm

! external subroutine
subroutine proc2(x)
   use mmm
   type(x_t) :: x
   ! Do something with x
      write (*,*) 'Proc2'
      write (*,*) ' a', x%a
      write (*,*) ' b', x%b
      write (*,*) ' i', x%i
end subroutine proc2

program anon
   use mmm

   type(x_t) :: x
   integer   :: k
!
   forall (k=1:3) X%a(k) = k
   forall (k=1:2) X%b(k) = k*4
   forall (k=1:5) X%i(k) = 7-k
!
   call proc1 (x)
   call proc2 (x)
end
Back to top
View user's profile Send private message
davidb



Joined: 17 Jul 2009
Posts: 560
Location: UK

PostPosted: Fri Jan 25, 2013 1:33 am    Post subject: Re: Reply with quote

JohnCampbell wrote:

Do you expect that sequence is necessary in this case ?


No, it isn't necessary.
_________________
Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl
Back to top
View user's profile Send private message
joemezni



Joined: 14 Jan 2013
Posts: 8

PostPosted: Fri Jan 25, 2013 9:30 am    Post subject: Reply with quote

Hi guys
I thank you all for these information , i learned from you how to sequence a derived data type.
The problem was also in the declaration, the right decleration is

type(xyzcoord)::dcoor(Nnodes)

and not

type(xyzcoord)::dcoor(Nnodes,9) , 9 is length of the new type xyzcoord

That was my mistake

my question now is how to get only only the last 3 terms of the type xyzcoord
i used this

data = dcoor%xyzcoord but it does not work
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Fri Jan 25, 2013 12:30 pm    Post subject: Reply with quote

The following example might give you some ideas on how to use a derived type, as an allocatable data structure in a module.
Code:
module node_info
!
  type xyzcoord
    integer*4, dimension(6) :: wert
    real*8,    dimension(3) :: xyzcoord
  end type xyzcoord
!
  type (xyzcoord), parameter :: xyzcoord_free  = xyzcoord ( (/ 0,0,0,0,0,0 /), (/ 0.d0, 0.d0, 0.d0 /) )
  type (xyzcoord), parameter :: xyzcoord_fixed = xyzcoord ( (/ 1,1,1,1,1,1 /), (/ 0.d0, 0.d0, 0.d0 /) )
  type (xyzcoord), parameter :: xyzcoord_pined = xyzcoord ( (/ 1,1,1,0,0,0 /), (/ 0.d0, 0.d0, 0.d0 /) )
!
  integer*4 :: Nnodes
  type (xyzcoord), allocatable, dimension(:) :: dcoor
end module node_info

use node_info
!
   Nnodes = 300                      ! determine/define the number of nodes
   allocate ( dcoor(Nnodes) )        ! allocate storage for these nodes
!
   dcoor = xyzcoord_fixed            ! initialise all nodes
!
   write (*,*) dcoor(51)%xyzcoord    ! will write out node 51 coordinates 
!
   dcoor(51)%xyzcoord = (/ 1., 3., 5.1 /)   ! redefine node 51 coordinates  ( mixed kind !!)
   write (*,*) dcoor(51)%xyzcoord    ! will write out node 51 coordinates 
!
   dcoor(51)%xyzcoord(2) =    3.5    ! redefine node 51 Y ordinates 
   write (*,*) dcoor(51)%xyzcoord    ! will write out node 51 coordinates 
!   
end
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General 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