replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - Access violation
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 

Access violation

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



Joined: 01 Jul 2009
Posts: 1

PostPosted: Thu Jul 02, 2009 2:53 pm    Post subject: Access violation Reply with quote

I have been involved in trying to get some Fortran 90 running on the PC that was previously run on Unix systems using other compilers. Compilation was done with 'Global save on'

The messages are:

Access violation
The instructions at address 036d410a attempted to read from location 20727774

036d4070 __CONCAT (+009a)
0043ff00 LP_NETWORK!NEW_NODE_INDS [+105]
00404609 EVALUATOR!PREPARE_NETWORK_CMAT [+0558]

The routine with the problem is

SUBROUTINE new_node_inds ( cmat, nodes, error_status )

! Escargot Stage 1 Functional Specification Issue 2 Draft 6
! "4.2 Disconnection Generators" ... first equation (Cool

! Allocates two independent variables for the node:
! Create a disconnection power variable for the demand not met at the node.
! This variable greatly improves the likelyhood of a feasible solution.
! Put it into the initial basis except for the reference node.
! Give it a large arbitrary limit.
! Create a voltage phase angle variable.
! Omit it from the initial basis except for the reference node.
! Give it a large arbitrary limit.

TYPE(cons_matrix), INTENT(INOUT) :: cmat ! Constraint matrix
TYPE(node_data), INTENT(INOUT), TARGET :: nodes(Smile ! Node data
INTEGER, INTENT(OUT) :: error_status ! Error status code

! Global data
! costs (IN)

! Local data
CHARACTER(*), PARAMETER :: proc_id = mod_id//"nni:" ! Subroutine identifier
TYPE(obj_ref), DIMENSION(1:2) :: node_obj ! Object reference for
! node variable
INTEGER :: inode ! Node number

! ------------------- Executable code ------------------- !

error_status = success

! All nodes
DO inode = 1, numnod
node_obj = (/ obj_ref("node",nodes(inode)%inp%name, inode) , &
obj_ref("pwr","",0 ) /)

! The disconnection generator makes up any supply that cannot be met
nodes(inode)%work%inds%pwr = new_ind (cmat, &
& "Disconnection power at node "//nodes(inode)%inp%name, &
& cost=costs%disc, inicst=zero, low=zero, high=lims%medpwr, &
& objs=node_obj)
IF ( nodes(inode)%work%inds%pwr .LE. 0 ) THEN
error_status = sev_error
CALL message ( proc_id//"dvn", sev_error, &
"Error allocating disconnection variable for node [NAME]" , &
nodes(inode)%inp%name )
RETURN
END IF

! The nodal phase angle is an independent variable.
node_obj(2) = obj_ref("ang","",0)
IF ( nodes(inode)%work%section == inode ) THEN

! For a reference node, the nodal angle must be basic.
nodes(inode)%work%inds%ang = new_ind (cmat, &
& "Phase angle at Node "//nodes(inode)%inp%name, &
& cost=zero, inicst=zero, low=zero, high=zero, &
& objs=node_obj)
ELSE IF ( nodes(inode)%work%section > 0 ) THEN

! For a non-reference node, the nodal angle must be non-basic.
! The corresponding power balance dependent variable must be
! made basic to ensure the correct number of basic variables.
nodes(inode)%work%inds%ang = new_ind (cmat, &
& "Phase angle at Node "//nodes(inode)%inp%name, &
& cost=zero, inicst=zero, low=-lims%bigang, &
& high=lims%bigang, objs=node_obj)
! If ( nodes(inode)%work%section < 0 ), inode is not in use
END IF
IF ( nodes(inode)%work%inds%ang <= 0 ) THEN
error_status = sev_error
CALL message ( proc_id//"dph", sev_error, &
"Error allocating phase angle variable for node [NAME]" , &
nodes(inode)%inp%name
Back to top
View user's profile Send private message
JohnHorspool



Joined: 26 Sep 2005
Posts: 270
Location: Gloucestershire UK

PostPosted: Thu Jul 02, 2009 3:45 pm    Post subject: Reply with quote

Glyn,

You are new to this forum and I suspect new to Silverfrost.

Some points:-

1). your post has been truncated, there is a limit to post size.

2). when posting code use the "code" button to avoid unexpected and unwanted smileys appearing:-

Code:
C     this is code
      write(6,*)'hello world'


3). use the excellent debugging facilities with this compiler to track down the "Access violation" problem
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