2020-08-02 01:22:39 -07:00
|
|
|
program test
|
|
|
|
|
implicit none
|
2020-08-02 12:38:09 -07:00
|
|
|
1 format(1i10)
|
2020-08-02 01:22:39 -07:00
|
|
|
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16), parameter :: base = 2, chunk = 1000000000
|
2020-08-02 01:22:39 -07:00
|
|
|
double precision :: S
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16) :: i, len
|
2020-08-02 01:22:39 -07:00
|
|
|
|
2020-08-02 12:38:09 -07:00
|
|
|
open(1, file = "prev.txt")
|
|
|
|
|
write(1,1) 1
|
|
|
|
|
close(1)
|
2020-08-02 01:22:39 -07:00
|
|
|
|
2020-08-02 12:38:09 -07:00
|
|
|
S = 0.5
|
|
|
|
|
|
|
|
|
|
do i = 2, 63
|
|
|
|
|
len = next()
|
|
|
|
|
call rename("array.txt", "prev.txt")
|
|
|
|
|
S = S + (real(len) / 2.0 ** i)
|
2020-08-02 01:22:39 -07:00
|
|
|
print *, "ITERATION", i
|
2020-08-02 12:38:09 -07:00
|
|
|
print *, "NUMBER ", len
|
2020-08-02 01:22:39 -07:00
|
|
|
print *, "SUM ", S
|
|
|
|
|
print *, ""
|
|
|
|
|
call flush()
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
function is_fourth_free (x)
|
|
|
|
|
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16), intent (in) :: x
|
|
|
|
|
integer (kind = 16) :: i
|
2020-08-02 01:22:39 -07:00
|
|
|
logical :: is_fourth_free
|
|
|
|
|
|
|
|
|
|
i = 2
|
|
|
|
|
do while (i * i * i * i <= x)
|
|
|
|
|
if (mod(x, i * i * i * i) == 0) then
|
|
|
|
|
is_fourth_free = .false.
|
|
|
|
|
return
|
|
|
|
|
end if
|
|
|
|
|
i = i + 1
|
|
|
|
|
end do
|
|
|
|
|
is_fourth_free = .true.
|
|
|
|
|
|
|
|
|
|
end function is_fourth_free
|
|
|
|
|
|
|
|
|
|
function is_square_free (x)
|
|
|
|
|
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16), intent (in) :: x
|
|
|
|
|
integer (kind = 16) :: i
|
2020-08-02 01:22:39 -07:00
|
|
|
logical :: is_square_free
|
|
|
|
|
|
|
|
|
|
i = 2
|
|
|
|
|
do while (i * i <= x)
|
|
|
|
|
if (mod(x, i * i) == 0) then
|
|
|
|
|
is_square_free = .false.
|
|
|
|
|
return
|
|
|
|
|
end if
|
|
|
|
|
i = i + 1
|
|
|
|
|
end do
|
|
|
|
|
is_square_free = .true.
|
|
|
|
|
|
|
|
|
|
end function is_square_free
|
|
|
|
|
|
|
|
|
|
function is_prime (x)
|
|
|
|
|
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16), intent (in) :: x
|
|
|
|
|
integer (kind = 16) :: i
|
2020-08-02 01:22:39 -07:00
|
|
|
logical :: is_prime
|
|
|
|
|
|
|
|
|
|
if (x < 2 .or. mod(x, 2) == 0) then
|
|
|
|
|
is_prime = .false.
|
|
|
|
|
return
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
i = 3
|
|
|
|
|
do while (i * i <= x)
|
|
|
|
|
if (mod(x, i) == 0) then
|
|
|
|
|
is_prime = .false.
|
|
|
|
|
return
|
|
|
|
|
end if
|
|
|
|
|
i = i + 2
|
|
|
|
|
end do
|
|
|
|
|
is_prime = .true.
|
|
|
|
|
|
|
|
|
|
end function is_prime
|
|
|
|
|
|
|
|
|
|
function step (x)
|
|
|
|
|
implicit none
|
|
|
|
|
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16), intent (in) :: x
|
|
|
|
|
integer (kind = 16) :: i, t, count
|
|
|
|
|
integer (kind = 16), dimension (:), allocatable :: step
|
|
|
|
|
integer (kind = 16), dimension (base) :: temp
|
2020-08-02 01:22:39 -07:00
|
|
|
|
|
|
|
|
count = 0
|
|
|
|
|
|
|
|
|
|
do i = 0, base - 1
|
|
|
|
|
t = x * base + i
|
|
|
|
|
if (is_fourth_free(t)) then
|
|
|
|
|
count = count + 1
|
|
|
|
|
temp(count) = t
|
|
|
|
|
end if
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
allocate(step(count))
|
|
|
|
|
|
|
|
|
|
do i = 1, count
|
|
|
|
|
step(i) = temp(i)
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
end function step
|
|
|
|
|
|
2020-08-02 12:38:09 -07:00
|
|
|
function next()
|
|
|
|
|
implicit none
|
|
|
|
|
1 format(1i10)
|
|
|
|
|
|
2020-08-02 14:17:01 -07:00
|
|
|
integer (kind = 16), dimension (:), allocatable :: temp, temp2
|
2020-08-02 15:45:40 -07:00
|
|
|
integer (kind = 16) :: current, next, i, j, templen, ios
|
2020-08-02 12:38:09 -07:00
|
|
|
logical :: done
|
|
|
|
|
|
|
|
|
|
templen = 0
|
|
|
|
|
next = 0
|
|
|
|
|
done = .false.
|
|
|
|
|
allocate(temp(chunk))
|
|
|
|
|
|
|
|
|
|
open(1, file = "array.txt")
|
|
|
|
|
open(2, file = "prev.txt")
|
|
|
|
|
|
|
|
|
|
do while (.not. done)
|
|
|
|
|
read(2, 1, iostat = ios) current
|
|
|
|
|
if (ios .ne. 0) then
|
|
|
|
|
done = .true.
|
|
|
|
|
exit
|
|
|
|
|
end if
|
2020-08-02 01:22:39 -07:00
|
|
|
|
2020-08-02 12:38:09 -07:00
|
|
|
temp2 = step(current)
|
|
|
|
|
do i = 1, size(temp2)
|
|
|
|
|
templen = templen + 1
|
|
|
|
|
temp(templen) = temp2(i)
|
|
|
|
|
next = next + 1
|
|
|
|
|
if (templen >= chunk) then
|
|
|
|
|
write(1,1) temp
|
|
|
|
|
call flush(1)
|
|
|
|
|
deallocate(temp)
|
|
|
|
|
allocate(temp(chunk))
|
|
|
|
|
templen = 0
|
|
|
|
|
end if
|
2020-08-02 01:22:39 -07:00
|
|
|
end do
|
|
|
|
|
deallocate(temp2)
|
|
|
|
|
end do
|
|
|
|
|
|
2020-08-02 12:38:09 -07:00
|
|
|
write(1,1) temp(:templen)
|
2020-08-02 01:22:39 -07:00
|
|
|
deallocate(temp)
|
|
|
|
|
|
2020-08-02 12:38:09 -07:00
|
|
|
close(1)
|
|
|
|
|
close(2)
|
|
|
|
|
|
2020-08-02 01:22:39 -07:00
|
|
|
end function next
|
|
|
|
|
|
|
|
|
|
end program test
|