Silverfrost Forums

Welcome to our forums

#[SOLVED]# I can't see why this is happening to my variables

23 Nov 2013 7:06 (Edited: 23 Nov 2013 8:34) #13351

you don't need to know what I'm going to do with the code the problem is with P2 value as you can see it is used in the second do loop but it gets values that it should not. pay attention to the output that I've provided here. the code is in the first reply for some other unknown reason I couldn't post it here(character limit in posts maybe?).

output(last 5 lines): below 0.890874 P1= 0.920000 below 0.905116 P1= 0.921000 final below 0.905116 1 above 0.905116 P2= 0.904600 above 0.670058 P2= 0.668259

as you can see in the first place P2 should not be 0.904600 and the weirder part is P2 changing to 0.668259 after execution of P2=P2+0.001

23 Nov 2013 7:10 #13352
PROGRAM Shooting_Method
    IMPLICIT NONE
    REAL, PARAMETER :: h = 0.05                 !step size
    INTEGER, PARAMETER :: n = (10/h)          !number of steps
    REAL, DIMENSION(3,4) :: K=0                   !Runge_Kutta coefficients (K1, K2, ...)
    REAL, DIMENSION (0:n) :: g1, g2, g3
    REAL :: P, P1, P2                     !assumed value for g3 initial
    REAL, PARAMETER:: B = 0.5, e = 0.1         !beta and epsilon
    INTEGER :: i, m                     !counter
    P = 0
    P1 = 0.9                          
    P2 = 0.9
    g1(0) = 0
    g2(0) = 0
    i = 0
    !shooting below the target
    DO
        g3(0) = P1
        K(1,1) = h*g2(i)
        K(2,1) = h*g3(i)
        K(3,1) = h*(-g1(i)*g3(i) + B*((ABS(g2(i))**2.) - 1.0))
        K(1,2) = h*(g2(i) + K(2,1)/2.)
        K(2,2) = h*(g3(i) + K(3,1)/2.)
        K(3,2) = h*(-(g1(i)+K(1,1)/2.)*(g3(i)+K(3,1)/2.) + B*((ABS(g2(i)+K(2,1)/2.)**2.) - 1.0))
        K(1,3) = h*(g2(i) + K(2,2)/2.)
        K(2,3) = h*(g3(i) + K(3,2)/2.)
        K(3,3) = h*(-(g1(i)+K(1,2)/2.)*(g3(i)+K(3,2)/2.) + B*((ABS(g2(i)+K(2,2)/2.)**2.) - 1.0))
        K(1,4) = h*(g2(i) + K(2,3))
        K(2,4) = h*(g3(i) + K(3,3))
        K(3,4) = h*(-(g1(i)+K(1,3))*(g3(i)+K(3,3)) + B*((ABS(g2(i)+K(2,3))**2.) - 1.0))
        g1(i+1) = g1(i) + (1/6.0)*(K(1,1) + 2.*K(1,2) + 2.*K(1,3) + K(1,4))
        g2(i+1) = g2(i) + (1/6.0)*(K(2,1) + 2.*K(2,2) + 2.*K(2,3) + K(2,4))
        g3(i+1) = g3(i) + (1/6.0)*(K(3,1) + 2.*K(3,2) + 2.*K(3,3) + K(3,4))
        IF (i == n) THEN
                print*, 'below',g2(n), 'P1=', P1
            IF ( g2(n) < 1 .and. g2(n) > 0.9 ) THEN
                print*, 'final below',g2(n)
                read*, m
                EXIT
            ELSE
                P1 = P1 + 0.001
                i = -1
            END IF
        END IF
        i = i + 1
    END DO

continued...

23 Nov 2013 7:15 #13353
     P2 = P1
    g1(0) = 0
    g2(0) = 0
    i = 0
    !Shooting above the target
    DO
        g3(0) = P2
        K(1,1) = h*g2(i)
        K(2,1) = h*g3(i)
        K(3,1) = h*(-g1(i)*g3(i) + B*((ABS(g2(i))**2.) - 1.0))
        K(1,2) = h*(g2(i) + K(2,1)/2.)
        K(2,2) = h*(g3(i) + K(3,1)/2.)
        K(3,2) = h*(-(g1(i)+K(1,1)/2.)*(g3(i)+K(3,1)/2.) + B*((ABS(g2(i)+K(2,1)/2.)**2.) - 1.0))
        K(1,3) = h*(g2(i) + K(2,2)/2.)
        K(2,3) = h*(g3(i) + K(3,2)/2.)
        K(3,3) = h*(-(g1(i)+K(1,2)/2.)*(g3(i)+K(3,2)/2.) + B*((ABS(g2(i)+K(2,2)/2.)**2.) - 1.0))
        K(1,4) = h*(g2(i) + K(2,3))
        K(2,4) = h*(g3(i) + K(3,3))
        K(3,4) = h*(-(g1(i)+K(1,3))*(g3(i)+K(3,3)) + B*((ABS(g2(i)+K(2,3))**2.) - 1.0))
        g1(i+1) = g1(i) + (1/6.0)*(K(1,1) + 2.*K(1,2) + 2.*K(1,3) + K(1,4))
        g2(i+1) = g2(i) + (1/6.0)*(K(2,1) + 2.*K(2,2) + 2.*K(2,3) + K(2,4))
        g3(i+1) = g3(i) + (1/6.0)*(K(3,1) + 2.*K(3,2) + 2.*K(3,3) + K(3,4))
        IF (i == n) THEN
                print*, 'above',g2(n), 'P2=', P2
            IF ( g2(n) > 1 .and. g2(n) < 1.1 ) THEN
                print*, 'final above',g2(n)
                read*, m
                EXIT
            ELSE
                P2 = P2 + 0.001
                i = -1
            END IF
        END IF
        i = i + 1
    END DO

    g1(0) = 0
    g2(0) = 0
    i = 0

    !finding appropriate initial value through iteration
    DO
    this loop is irrelevant to the question
END PROGRAM Shooting_Method
23 Nov 2013 8:11 #13354

I have not studied your program but I suggest that you step through the code line by line using the debugger. This should show the point where the results are going wrong.

Have you used IMPLICIT NONE to make sure all variables have the required type? Is there an integer divide that is giving unexpected results (1/2 gives zero). Should you be using DOUBLE PRECISION for greater accuracy?

23 Nov 2013 8:29 #13355

Well I just found what caused the error, after 5 hours CheckMate identified it for me. I forgot to use ChekMate... I was exceeding my array limits... thanks for your reply

Please login to reply.