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

error775

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



Joined: 24 Aug 2011
Posts: 2

PostPosted: Wed Aug 31, 2011 10:30 am    Post subject: error775 Reply with quote

I have a program with error775.please help me to run it.what should I do?

PROGRAM p72
!-------------------------------------------------------------------------
! Program 7.2 Plane or axisymmetric analysis of steady seepage using
! 4-node rectangular quadrilaterals. Mesh numbered
! in x(r)- or y(z)- direction.
!-------------------------------------------------------------------------

IMPLICIT NONE
INTEGER,PARAMETER::iwp=SELECTED_REAL_KIND(15)
INTEGER::fixed_freedoms,i,iel,k,loaded_nodes,nci,ndim=2,nels,neq,nip=4, &
nod=4,nn,np_types,nxe,nye,determinant
REAL(iwp)::det,one=1.0_iwp,penalty=1.0e20_iwp,zero=0.0_iwp
CHARACTER(LEN=15)::dir,element='quadrilateral',type_2d
!-----------------------dynamic arrays------------------------------------
INTEGER,ALLOCATABLE::etype(Smile,g_num(:,Smile,kdiag(Smile,node(Smile,num(Smile
REAL(iwp),ALLOCATABLE::coord(:,Smile,der(:,Smile,deriv(:,Smile,disps(Smile,fun(Smile, &
gc(Smile,g_coord(:,Smile,jac(:,Smile,kay(:,Smile,kc(:,Smile,kv(Smile,kvh(Smile,loads(Smile, &
points(:,Smile,prop(:,Smile,value(Smile,weights(Smile,x_coords(Smile,y_coords(Smile
!-----------------------input and initialisation--------------------------
OPEN(10,FILE='fe95.dat')
OPEN(11,FILE='fe95.res')
READ(10,*)type_2d,dir,nxe,nye,np_types
CALL mesh_size(element,nod,nels,nn,nxe,nye)
neq=nn
ALLOCATE(points(nip,ndim),g_coord(ndim,nn),coord(nod,ndim), &
jac(ndim,ndim),weights(nip),der(ndim,nod),deriv(ndim,nod), &
kc(nod,nod),num(nod),g_num(nod,nels),kay(ndim,ndim),etype(nels), &
x_coords(nxe+1),y_coords(nye+1),prop(ndim,np_types),gc(ndim),fun(nod), &
kdiag(neq),loads(0:neq),disps(0:neq))
READ(10,*)prop
etype=1
IF(np_types>1)READ(10,*)etype
READ(10,*)x_coords,y_coords
!-----------------------loop the elements to find global arrays sizes-----
kdiag=0
elements_1: DO iel=1,nels
CALL geom_rect(element,iel,x_coords,y_coords,coord,num,dir)
g_num(:,iel)=num
g_coord(:,num)=TRANSPOSE(coord)
CALL fkdiag(kdiag,num)
END DO elements_1
CALL mesh(g_coord,g_num,12)
DO i=2,neq
kdiag(i)=kdiag(i)+kdiag(i-1)
END DO
ALLOCATE(kv(kdiag(neq)),kvh(kdiag(neq)))
WRITE(11,'(2(A,I5))') &
"There are",neq," equations and the skyline storage is",kdiag(neq)
CALL sample(element,points,weights)
!-----------------------global conductivity matrix assembly---------------
kv=zero
gc=one
elements_2: DO iel=1,nels
kay=zero
DO i=1,ndim
kay(i,i)=prop(i,etype(iel))
END DO
num=g_num(:,iel)
coord=TRANSPOSE(g_coord(:,num))
kc=zero
gauss_pts_1: DO i=1,nip
CALL shape_der(der,points,i)
CALL shape_fun(fun,points,i)
jac=MATMUL(der,coord)
det=determinant(jac)
CALL invert(jac)
deriv=MATMUL(jac,der)
IF(type_2d=='axisymmetric')gc=MATMUL(fun,coord)
kc=kc+MATMUL(MATMUL(TRANSPOSE(deriv),kay),deriv)*det*weights(i)*gc(1)
END DO gauss_pts_1
CALL fsparv(kv,kc,num,kdiag)
END DO elements_2
kvh=kv
!-----------------------specify boundary values---------------------------
loads=zero
READ(10,*)loaded_nodes
IF(loaded_nodes/=0)READ(10,*)(k,loads(k),i=1,loaded_nodes)
READ(10,*)fixed_freedoms
IF(fixed_freedoms/=0)THEN
ALLOCATE(node(fixed_freedoms),value(fixed_freedoms))
READ(10,*)(node(i),value(i),i=1,fixed_freedoms)
kv(kdiag(node))=kv(kdiag(node))+penalty
loads(node)=kv(kdiag(node))*value
END IF
!-----------------------equation solution---------------------------------
CALL sparin(kv,kdiag)
CALL spabac(kv,loads,kdiag)
!-----------------------retrieve nodal net flow rates---------------------
CALL linmul_sky(kvh,loads,disps,kdiag)
WRITE(11,'(/A)')" Node Total Head Flow rate"
DO k=1,nn
WRITE(11,'(I5,2E12.4)')k,loads(k),disps(k)
END DO
disps(0)=zero
WRITE(11,'(/A)')" Inflow Outflow"
WRITE(11,'(5X,2E12.4)')
Back to top
View user's profile Send private message
Robert



Joined: 29 Nov 2006
Posts: 457
Location: Manchester

PostPosted: Wed Aug 31, 2011 10:54 am    Post subject: Reply with quote

Can you give us a clue: on which line do you get the error?
Back to top
View user's profile Send private message Visit poster's website
jjgermis



Joined: 21 Jun 2006
Posts: 404
Location: N�rnberg, Germany

PostPosted: Wed Aug 31, 2011 11:56 am    Post subject: Reply with quote

Perhaps you could include the program as code and not as normal test. This makes reading it easier.
Code:
1.) The begin of the code block starts with [code]
2.) The code is ended by [/code]
Back to top
View user's profile Send private message
brucebowler
Guest





PostPosted: Wed Aug 31, 2011 1:02 pm    Post subject: Reply with quote

And since it's not "all there", can you make a trim out the stuff that's irrelevant and post a smaller version that exhibits the problem?
Back to top
JohnCampbell



Joined: 16 Feb 2006
Posts: 2615
Location: Sydney

PostPosted: Thu Sep 01, 2011 2:25 am    Post subject: Reply with quote

Are you developing this code, as the error 775 is probably due to using an END rather than an END DO statement.

Your use of ALLOCATE is beyond my experience, although it may be valid.
I would not have used the ALLOCATE statements like:
.... x_coords(nxe+1),y_coords(nye+1) ... or
ALLOCATE(kv(kdiag(neq)),kvh(kdiag(neq)))

and preferred each array in a seperate allocate statement

Your use of arrays appears luxurious by my old practices, but can work for a smallish problem.

Code:
!-----------------------dynamic arrays------------------------------------
INTEGER,ALLOCATABLE::  &
  etype(:),     &  ! nels
  g_num(:,:),   &  ! nod,nels
  kdiag(:),     &  ! neq
  node(:),      &  ! fixed_freedoms
  num(:)           ! nod

REAL(iwp),ALLOCATABLE::  &
  coord(:,:),   &  ! nod,ndim
  der(:,:),     &  ! ndim,nod
  deriv(:,:),   &  ! ndim,nod
  disps(:),     &  ! 0:neq
  fun(:),       &  ! nod
  gc(:),        &  ! ndim
  g_coord(:,:), &  ! ndim,nn
  jac(:,:),     &  ! ndim,ndim
  kay(:,:),     &  ! ndim,ndim
  kc(:,:),      &  ! nod,nod
  kv(:),        &  ! kdiag(neq)   ?? I'd use a variable nstif = kdiag(neq)
  kvh(:),       &  ! kdiag(neq)   ??
  loads(:),     &  ! 0:neq
  points(:,:),  &  ! nip,ndim
  prop(:,:),    &  ! ndim,np_types
  value(:),     &  ! fixed_freedoms
  weights(:),   &  ! nip
  x_coords(:)   &  ! nxe+1        ?? I'd use a variable nxe1 = nxe+1
  y_coords(:)      ! nye+1        ??


I'd also import this into excel and calculate the byte size of each array to check where the memory might disappear.

John
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