Skip to content

Commit

Permalink
Add files via upload
Browse files Browse the repository at this point in the history
  • Loading branch information
imronuke authored Oct 1, 2017
1 parent 50305d5 commit 0fca07d
Showing 1 changed file with 25 additions and 3 deletions.
28 changes: 25 additions & 3 deletions src/mod_InpOutp.f90
Original file line number Diff line number Diff line change
Expand Up @@ -234,7 +234,7 @@ SUBROUTINE inp_echo()
INTEGER :: nline

WRITE(ounit, *) ' ###########################################################'
WRITE(ounit, *) ' # ADPRES 1.0 #'
WRITE(ounit, *) ' # ADPRES 1.1 #'
WRITE(ounit, *) ' # ABU DHABI POLYTECHNIC REACTOR SIMULATOR #'
WRITE(ounit, *) ' ########################################################### '
WRITE(ounit, *)
Expand Down Expand Up @@ -359,7 +359,7 @@ SUBROUTINE inp_comments ()
END DO

1012 FORMAT(A2, I5,' ',A100)
1014 FORMAT(2X, 'AT LINE', I3, ' : WRONG CARD ', A8)
1014 FORMAT(2X, 'AT LINE', I3, ' : THIS IS A WRONG INPUT CARD : ', A8)



Expand Down Expand Up @@ -466,6 +466,8 @@ SUBROUTINE inp_xsec (xbunit)
INTEGER :: ios ! IOSTAT status
REAL :: dum
INTEGER, DIMENSION(:), ALLOCATABLE :: group
LOGICAL :: cnuf = .TRUE.
LOGICAL :: csigf = .TRUE.

WRITE(ounit,*)
WRITE(ounit,*)
Expand Down Expand Up @@ -499,6 +501,16 @@ SUBROUTINE inp_xsec (xbunit)
xchi(i,g), (xsigs(i,g,h), h = 1, ng)
message = ' error in cross section data'
CALL er_message(ounit, ios, ln, message)

! Check CXs values
IF (xsigtr(i,g) <= 0.0) THEN
WRITE(ounit,1020)i, g
STOP
END IF
IF (xnuf(i,g) > 0.) cnuf = .FALSE.
IF (xsigf(i,g) > 0.) csigf = .FALSE.


xD(i,g) = 1.d0/(3.d0*xsigtr(i,g))
dum = 0.0
DO h= 1, ng
Expand All @@ -508,6 +520,15 @@ SUBROUTINE inp_xsec (xbunit)
END DO
END DO

IF (cnuf) THEN
WRITE(ounit, *) "ERROR: The Problem has no fission material (nu*fission for all materials are zero)"
STOP
END IF
IF (cnuf) THEN
WRITE(ounit, *) "ERROR: The Problem has no fission material (fission xsec for all materials are zero)"
STOP
END IF

! Writing output
IF (oxsec) THEN
DO i= 1, nmat
Expand All @@ -534,6 +555,7 @@ SUBROUTINE inp_xsec (xbunit)
1011 FORMAT(2X, A7, A12, A13, A12, A11, 2A13, A15)
1010 FORMAT(2X, I6, F13.6, 3F12.6, 3F13.6)
1015 FORMAT(4X, I3, F16.6, 20F12.6)
1020 FORMAT(2X, 'ERROR: Transport cross section (sigtr)is zero or less in material: ', I3, ' ;group: ', I3)

DEALLOCATE(group)

Expand Down Expand Up @@ -1462,7 +1484,7 @@ SUBROUTINE inp_adf (xbunit)

! ADF PRINT OPTION
READ(xbunit, *, IOSTAT=ios) ind, ln, zp
IF (ios == 0 .AND. zp >=1 .AND. zp <= nz) THEN
IF (ios == 0 .AND. zp >=1) THEN
WRITE(ounit,*)
WRITE(ounit,'(A,I3)') ' ADF VALUES ON PLANAR NUMBER : ', zp

Expand Down

0 comments on commit 0fca07d

Please sign in to comment.