How can I solve this equation which has condition?

Hi everyone!. I’m a newbie in Fortran.
I try to solve the equation
F(x)=a/x if x > 4 and F(x) = (a/b).(3-x^2) if x <= 4
with a,b are constants that I can change any real number
I use bisection method but in this case, I don’t know how to declare the function. Here is my code

program bisec
implicit none
integer, parameter:: n=1000
double precision f,x1,x2,eps
double precision nroots(n)
integer i,nroots
exteral f
x1=0.0
x2=10.0 ! I change this number.
eps=1.0e-7
call bisection(f,x1,x2,eps,n,roots,nroots)
if (nroots==0) then
write(,) ‘no root found’
stop
end if
write(,) ‘roots of equation are’
do i=1,nroots,1
write (,) i, root(i)
end do
end program bisec

function f
implicit none
double precision f,x
if (x>4.0) then f = a/x
else x <4.0 then f=(a/b)*(3-x**2.0)
end function
subroutine bisection(f,x1,x2,esp,n,roots,nroots)
implicit none
integer, parameter:: n=1000
double precision f,x1,x2,eps,roots(n)
double precision a,b,c,dx,root
integer n,i,j,nroots
interger, parameter::sk =200
dx = (x2-x1)/n
nroots=0
do j =1,n
a=x1+(j-1)*dx
b=a+dx
if (f(a)*f(b))>0) cycle
do i = 1, sk
c=(b+a)/2.0
if (f(c).f(a)<=0) then
b=c
else
a=c
end if
if (abs(a-b)<=eps) exit
end do
root=(a+b)/2.0
if (abs(f(root)<1.0) then
nroots=nroots+1
Roots(nroots)= root
end if
end do
end subroutine bisection

I know I get trouble in declare the funtion, please help me!

1 Like

I have improved your program wrt the syntax and some typos. The most important changes are documented in the comments. There are much more possible improvements, for instance the use of “double precision” and putting the bisect routine in a module and so on, but this should get you started.

! bisect.f90 --
!     Improving sample program
!
program bisec
    implicit none
    integer, parameter :: n=1000
    double precision   :: x1,x2,eps
    double precision   :: roots(n)

    double precision   :: a, b  !<== these were not defined

    integer i, nroots

    a = 1.0       !<== values will be available in the function f,
    b = 2.0       !<== because f is an internal function now.

    x1=0.0
    x2=10.0 ! I change this number.
    eps=1.0e-7
    call bisection(f,x1,x2,eps,n,roots,nroots)
    if (nroots==0) then
        write(*,*) 'no root found'  !<== plain quotes, not "smart" quotes
        stop
    end if
    write(*,*) 'roots of equation are'
    do i=1,nroots,1
        write (*,*) i, roots(i)
    end do

contains

! Using a so-called internal routine/function, then the variables a and b
! are taken from the encompassing program. Avoids having to pass them
! explicitly via the routine "bisect".

function f( x )    !<== argument should be added
    implicit none
    double precision f,x

    if (x>4.0) then
        f = a/x
    else
        f=(a/b)*(3-x**2.0)
    endif
end function

end program bisec

subroutine bisection(f,x1,x2,eps,n,roots,nroots)
    implicit none
    double precision f,x1,x2,eps,roots(n)
    double precision a,b,c,dx,root
    integer n,i,j,nroots
    integer, parameter::sk =200

    dx = (x2-x1)/n
    nroots=0
    do j =1,n
        a=x1+(j-1)*dx
        b=a+dx
        if (f(a)*f(b) > 0) cycle
        do i = 1, sk
            c=(b+a)/2.0
            if (f(c)*f(a) <= 0) then
                b=c
            else
                a=c
            end if
            if (abs(a-b) <= eps) exit
        end do
        root=(a+b)/2.0
        if (abs(f(root)) < 1.0) then
            nroots=nroots+1
            Roots(nroots)= root
        end if
    end do
end subroutine bisection
6 Likes

thank you for your nice comment. I learn a lot form it

1 Like

You’re welcome :wink:

3 Likes

I also thinkk there is another way to solve this. But I still don’t make it run. I think if i make an array 1D, and put the number in this f function. if f(xi) is near 0 with small error then I choose it which means my roots. Are there any ways to solve this?

Welcome, @haidangwy!

1 Like

I try to run this equation
f(x)=0 but there is a condition
if x <=5.84 we have
f=(-50/(1+(exp(x-5.84)/0.5))+(12.33*(3.0-x^2/34.11)+1.41/(x^2.0)
if x >5.84 we have
f = f=(-50/(1+(exp(x-5.84)/0.5))+144.0/x+1.41/(x^2.0)
it just have the difference in this part.
When I declare the function I recieve

f is not a variable

Here is my code at the declaration part

function f(x)
if (x<=5.84) then
f=(-50/(1.0+exp(x-5.84)/0.5))+(12.33*(3.0-x**2/34.1056)+1.41/(x**2)
else
f=(-50/(1.0+exp(x-5.84)/0.5))+144/x**2+1.41/(x**2)
end if
end function f(x)

Hm, you do not define the type of the function. Can you post the complete program, as it is not clear from your message from what point in the code the error originates.

1 Like

As a meta comment on the appearance of your codes shared, I would like to suggest to use indentations when it comes to if-clauses, do-iterations, etc.

Contrasting to other languages (e.g., Python) indentation (probably most often) is functional irrelevant to modern Fortran. However, this form to structure code (cf. Arjen’s improvement of bisect.f90) visually into parts sharing a task/within a logical step helps to read the code. It only is a matter of complexity of the code written and time since initial design of the program that this equally may be helpful to you, too.

If the environment you use does not support this by default, I suggest to pass your code to a code formatter. An equivalent to yapf3 and black in Python is e.g., Peter Seewald’s fprettify, which recognizes a selection of these small units and indents them accordingly (this includes nested loops). While probably not designed to be a code linter (like pylint), loops not properly terminated are easily identified in fprettify's output, too.

1 Like

And here is my code:

program solvingpr1
implicit real*8(a-h,o-z)
integer, parameter:: n=1000
double precision ::x1,x2,esp
double precision:: roots(n)
integer i,nroots
x1=0.0
x2=20.0
eps=1.0e-7
call solving(f,x1,x2,eps,n,roots,nroots)
if (nroots==0) then
write(*,*) 'has no root' 
stop
end if
write (*,*) 'roots of this equation are'
do i=1,nroots,1
write(*,*) i, roots(i), f(roots(i))
end do
contains
function f(x)
implicit real*8(a-h,o-z)
double precision f,x
f=(-50/(1.0+exp(x-5.84)/0.5))+(12.33*(3.0-x**2/34.1056)+1.41/(x**2)
else
f=(-50/(1.0+exp(x-5.84)/0.5))+144/x**2+1.41/(x**2)
endif
end function f(x)

end program solvingpr1


!----------------------------------------------subroutine
subroutine solving(f,x1,x2,esp,n,roots,nroots)
implicit none
integer, parameter:: n=1000
double precision f,x1,x2,eps,roots(n)
double precision a,b,c,dx,root
integer n,i,j,nroots
interger, parameter::sk =200
dx = (x2-x1)/n
nroots=0
do j =1,n
a=x1+(j-1)*dx
b=a+dx
if (f(a)*f(b))>0) cycle
do i = 1, sk
c=(b+a)/2.0
if (f(c).f(a)<=0) then
b=c
else
a=c
end if
if (abs(a-b)<=eps) exit
end do
root=(a+b)/2.0
if (abs(f(root)<1.0) then
nroots=nroots+1
Roots(nroots)= root
end if
end do
end subroutine solving

I think I could solve this problem by the way if x=x1 we have f(x1)=a
then i subtract f(x1)-4.290 then I compare the result with a value which I can accept (eps = 1e-07). and then infer to the root :).
I repeat this for many time. Is it possible?

Thanks for posting that code, but:

  • Pick up on the explicit advice by @nbehrnd - it really really helps to understand the code!
  • Do not use “implicit real*8(a-h,o-z)” - it is a sure method to let simple bugs into your code. Use “implicit none” instead. It forces you to declare all variables, but it prevents stupid mistakes like typing “o” instead of “0”, simply because you did not declare “o” to be a variable. (And do not use “o” as a variable name, by the way)

Looking at you code: “interger” is not a Fortran keyword. And the function f in solving is not defined as a function but as a variable. Hence the call is inconsistent.

1 Like

thank you very much :slight_smile: for your nice comments. It really helps me!

It is good to compile with picky compiler options that point out problems in code that is still legal. With gfortran I suggest -Wall -Wextra -Wconversion-extra For a snippet of your code

implicit none
double precision :: x2,eps
x2 = 20.0
print*,x2
end

gfortran -Wconversion-extra says

xxdouble.f90:3:3:

    3 | x2=20.0
      |   1
Warning: Conversion from 'REAL(4)' to 'REAL(8)' at (1) [-Wconversion-extra]
xxdouble.f90:4:4:

    4 | eps=1.0e-7
      |    1
Warning: Conversion from 'REAL(4)' to 'REAL(8)' at (1) [-Wconversion-extra]

The Quickstart Fortran Tutorial, which I suggest reading, gives the example (slightly abbreviated)

program float
use, intrinsic :: iso_fortran_env, only: dp=>real64
implicit none
real(dp) :: float64
float64 = 1.0_dp ! Explicit suffix for literal constants
end program float

and gives the advice, which I endorse,

Always use a kind suffix for floating-point literal constants.

P.S. Not directed to OP. Should not gfortran with -Wall -Wextra include -Wconversion-extra ? Does FPM warn by default about double precision variables set to single precision literal constants?

2 Likes

@haidangwy ,

An inquiry first: are you a student? and is this a homework problem?

If yes, I suggest studying the numerical computing advancements related to the works of Dekker, Brent et al. on finding zeroes of functions c.f. https://blogs.mathworks.com/cleve/2015/10/26/zeroin-part-2-brents-version/#d354b12f-235d-474e-be05-d4dba9fa6fcc

2 Likes

Thanks Mr.Beliavsky. I’m a student. This is my assignment. I try to write a code for myself with Fortran.
Thank your for your link. I’m going to read this.

I want to thank everybody for helping me :wink:

It’s really interesting. When I solved some problem then new problems come. Today I’ve got a new problem that I want to take my roots from this equation. Let’s say I have 3 roots: 1,2,3. I need to assign them in a,b,c for the further calculation in this program.

a= root(1)
b= root(2)
c= root(3)

How can I do it?

Well, assuming your solution routine returns multiple roots in an array “root” (as was the case in your first post), then that is exactly the syntax you need.

2 Likes

amazing. I did it. I’m happy about it :slight_smile: