Skip to content

Commit

Permalink
Merge pull request #20 from zebo9x/master
Browse files Browse the repository at this point in the history
Fix double precision configuration
  • Loading branch information
jchelly authored Jun 20, 2023
2 parents 5b9f35f + 7786ac3 commit ffbadfc
Show file tree
Hide file tree
Showing 8 changed files with 51 additions and 34 deletions.
11 changes: 9 additions & 2 deletions main/src/main_window.F90
Original file line number Diff line number Diff line change
Expand Up @@ -983,15 +983,22 @@ subroutine main_window_process_events()
if(gui_button_clicked(yz_button))then
call transform_modify(view_transform,reset_rotation=.true.)
call transform_modify(view_transform,&
rotation=(/0.0,3.14159/2,3.14159/2/))
rotation=&
real((/0.0_pos_kind,&
real(3.14159265358979_real8byte/2, kind=pos_kind),&
real(3.14159265358979_real8byte/2, kind=pos_kind)/), &
kind=pos_kind))
view_transform%axis_aligned = 2
call main_window_redraw()
endif

! Reset the view if button clicked
if(gui_button_clicked(xz_button))then
call transform_modify(view_transform,reset_rotation=.true.)
call transform_modify(view_transform,rotation=(/3.14159/2,0.0,0.0/))
call transform_modify(view_transform,rotation=&
real((/real(3.14159265358979_real8byte/2, kind=pos_kind),&
0.0_pos_kind,0.0_pos_kind/), &
kind=pos_kind))
view_transform%axis_aligned = 3
call main_window_redraw()
endif
Expand Down
16 changes: 10 additions & 6 deletions main/src/mouse_handler.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,10 +25,12 @@ module mouse_handler
integer :: old_mx, old_my

! Rotation speed in radians per pixel
real, parameter :: rot_fac = 1.0*3.14159/180.0
real(kind=pos_kind), parameter :: rot_fac = &
real(1.0*3.14159265358979_real8byte/180.0, &
kind=pos_kind)

! Zoom speed
real, parameter :: zm_fac = 1.05
real(kind=pos_kind), parameter :: zm_fac = 1.05_pos_kind

! Translation speed
real, parameter :: trans_fac = 1.0e-2
Expand Down Expand Up @@ -82,7 +84,7 @@ logical function mouse_handler_process_events(mainwin,drawing_area, &
type (gui_window) :: mainwin
logical, dimension(:) :: show_species
integer, intent(in) :: width, height
real :: zf
real(kind=pos_kind) :: zf
logical :: moved
integer :: ibutton
type (transform_type) :: inv_trans
Expand Down Expand Up @@ -127,7 +129,8 @@ logical function mouse_handler_process_events(mainwin,drawing_area, &
! Button rotates the view
if(dragged(ibutton))then
call transform_modify(view_transform, &
rotation=(/dy*rot_fac, dx*rot_fac, 0.0 /))
rotation=real((/dy*rot_fac, dx*rot_fac, 0.0_pos_kind /),&
kind=pos_kind))
moved = .true.
endif
case(SCALE)
Expand All @@ -142,7 +145,8 @@ logical function mouse_handler_process_events(mainwin,drawing_area, &
if(dragged(ibutton))then
zf = zm_fac**dy
call transform_modify(view_transform, scale=zf, &
rotation=(/0.0, dx*rot_fac, 0.0 /))
rotation=real((/0.0_pos_kind, dx*rot_fac, 0.0_pos_kind /),&
kind=pos_kind))
moved = .true.
endif
case(TRANSLATE_XY)
Expand Down Expand Up @@ -221,7 +225,7 @@ subroutine mouse_handler_select_point(mainwin, mx, my, width, height, &
character(len=10) :: bt
real(kind=pos_kind), dimension(:,:), pointer :: pos
integer, dimension(:), allocatable :: idx
real, dimension(3) :: new_centre
real(kind=pos_kind), dimension(3) :: new_centre

call particle_store_contents(psample,get_nspecies=nspecies,get_np=np)

Expand Down
5 changes: 4 additions & 1 deletion main/src/movie.f90
Original file line number Diff line number Diff line change
Expand Up @@ -607,7 +607,10 @@ type (result_type) function movie_make_rotating()
endif

! Apply rotation for the next frame
call transform_modify(trans, (/ 0.0, real(dtheta), 0.0 /))
call transform_modify(trans, real((/ 0.0_pos_kind,&
real(dtheta, kind=pos_kind),&
0.0_pos_kind /),&
kind=pos_kind))

! Update the progress bar
if(nframes.gt.1) &
Expand Down
9 changes: 5 additions & 4 deletions main/src/particle_store.F90
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,7 @@ module particle_store
real :: time, redshift, expansion
character(len=maxlen) :: time_unit
integer :: idsize
real :: boxsize
real(pos_kind) :: boxsize
end type pdata_type

! These need to be public for pdata_type to be public.
Expand Down Expand Up @@ -877,7 +877,7 @@ type (result_type) function particle_store_sample(pdata, psample, npmax, &
integer(kind=index_kind), dimension(maxspecies) :: np_area, np_sample
integer :: nspecies
integer(kind=index_kind) :: i, j, k, ip
real :: fsample
real(kind=pos_kind) :: fsample
! Function call result
type (result_type) :: fresult
! Array of particle indexes
Expand Down Expand Up @@ -937,8 +937,9 @@ type (result_type) function particle_store_sample(pdata, psample, npmax, &
end do

! Calculate sampling rate
fsample = min(1.0, real(npmax, kind=real8byte) / &
real(sum(np_area(1:nspecies)), kind=real8byte))
fsample = real(min(1.0_real8byte, real(npmax, kind=real8byte) / &
real(sum(np_area(1:nspecies)), kind=real8byte)),&
kind=pos_kind)

! Get indices of particles in the sample
do i = 1, pdata%nspecies, 1
Expand Down
26 changes: 13 additions & 13 deletions main/src/property_plot.f90
Original file line number Diff line number Diff line change
Expand Up @@ -110,9 +110,9 @@ subroutine property_plot_init(new_snapshot)
!
implicit none
logical :: new_snapshot
real, dimension(:,:), pointer :: pos
real, dimension(3) :: rmin, rmax
real :: lbox
real(kind=pos_kind), dimension(:,:), pointer :: pos
real(kind=pos_kind), dimension(3) :: rmin, rmax
real(kind=pos_kind) :: lbox
integer :: nspecies
logical, save :: first_init = .true.

Expand Down Expand Up @@ -156,7 +156,7 @@ subroutine property_plot_init(new_snapshot)
rmax = max(rmax, maxval(pos(1:3,:),2))
end do
lbox = maxval(rmax-rmin)
psize = lbox / 1000.0
psize = lbox / 1000.0_pos_kind
endif

! Choose a random set of colours
Expand Down Expand Up @@ -212,12 +212,12 @@ subroutine property_plot_make_image(width, height, trans, image, &
integer(kind=index_kind), dimension(maxspecies) :: np
real(kind=pos_kind), dimension(:,:), pointer :: pos
! Transformed z coord
real :: z_trans
real(kind=pos_kind) :: z_trans
real(kind=pos_kind), dimension(3) :: pos_trans
! Projected coordinates
integer, dimension(2) :: ip
! z buffer
real, dimension(0:width*height-1) :: zbuf
real(kind=r_prop_kind), dimension(0:width*height-1) :: zbuf
character(len=maxlen) :: proptype
! Pointer to the data
real(kind=r_prop_kind), dimension(:), pointer :: rdata
Expand Down Expand Up @@ -452,7 +452,7 @@ subroutine property_plot_make_image(width, height, trans, image, &
is = ((psize*trans%scale)/(1.0+z_trans))/fov_x*width
is = min(is, max_pixels)
! Figure out what colour index to use
icol = colour_index(ispecies,real(idata(i)))
icol = colour_index(ispecies, real(idata(i), kind=pos_kind))
! Make sure colour index is in range
icol = max(0,min(255,icol))

Expand All @@ -474,22 +474,22 @@ subroutine property_plot_make_image(width, height, trans, image, &
if(.not.rand_colours(ispecies,iprop(ispecies)))then
call add_particle(ip, &
coltab(itab(ispecies,iprop(ispecies)))% &
cdata(1:3,icol),-real(idata(i)))
cdata(1:3,icol),-real(idata(i), kind=pos_kind))
else
call add_particle(ip, &
rcol(1:3,mod(idata(i),&
int(nrand,i_prop_kind))+1), -real(idata(i)))
int(nrand,i_prop_kind))+1), -real(idata(i), kind=pos_kind))
endif
case(SHOW_LOWEST)
! And add the particle to the image array
if(.not.rand_colours(ispecies,iprop(ispecies)))then
call add_particle(ip, &
coltab(itab(ispecies,iprop(ispecies)))% &
cdata(1:3,icol), real(idata(i)))
cdata(1:3,icol), real(idata(i), kind=pos_kind))
else
call add_particle(ip, &
rcol(1:3,mod(idata(i),&
int(nrand,i_prop_kind))+1),real(idata(i)))
int(nrand,i_prop_kind))+1), real(idata(i), kind=pos_kind))
endif
end select
endif
Expand Down Expand Up @@ -548,7 +548,7 @@ integer function colour_index(ispecies, rdata)
!
implicit none
integer :: ispecies
real :: rdata
real(kind=r_prop_kind) :: rdata
real(kind=r_prop_kind) :: rcol

! Figure out what colour index to use
Expand Down Expand Up @@ -577,7 +577,7 @@ subroutine add_particle(ip, col, zval)
integer, dimension(2) :: ip
character, dimension(3) :: col
integer :: k, l
real :: zval
real(kind=r_prop_kind) :: zval

do l = max(0,ip(2)-is), min(height-1,ip(2)+is), 1
do k = max(0,ip(1)-is), min(width-1,ip(1)+is), 1
Expand Down
4 changes: 3 additions & 1 deletion main/src/select_point.f90
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module select_point

use data_types
use f90_gui
use view_parameters
use particle_store
Expand Down Expand Up @@ -92,7 +93,8 @@ logical function select_point_process_events()
"Unable to interpret text as a coordinate")
else
! Apply the new coordinates
call transform_modify(view_transform, centre=(/x,y,z/))
call transform_modify(view_transform, centre=real((/x,y,z/),&
kind=pos_kind))
select_point_process_events = .true.
endif
endif
Expand Down
6 changes: 3 additions & 3 deletions main/src/transform.f90
Original file line number Diff line number Diff line change
Expand Up @@ -73,11 +73,11 @@ subroutine transform_modify(trans, rotation, scale, centre, translation, &
!
implicit none
type (transform_type) :: trans
real, dimension(3), optional :: rotation, centre, translation
real, optional :: scale
real(kind=pos_kind), dimension(3), optional :: rotation, centre, translation
real(kind=pos_kind), optional :: scale
real(kind=int8byte) :: sina, cosa
real(kind=int8byte), dimension(3,3) :: rot
real, optional :: set_scale
real(kind=pos_kind), optional :: set_scale
logical, optional :: reset_rotation
integer :: i

Expand Down
8 changes: 4 additions & 4 deletions main/src/view_parameters.f90
Original file line number Diff line number Diff line change
Expand Up @@ -24,9 +24,9 @@ module view_parameters
real, parameter :: pi = 4.0*atan(1.0)

! Extent of the particle distribution
real, dimension(3) :: posmin, posmax
real, dimension(3), public :: simcentre
real, public :: scalefac
real(kind=pos_kind), dimension(3) :: posmin, posmax
real(kind=pos_kind), dimension(3), public :: simcentre
real(kind=pos_kind), public :: scalefac

! Transform to convert from simulation coordinates to view coordinates
type (transform_type), public :: view_transform
Expand Down Expand Up @@ -109,7 +109,7 @@ subroutine view_parameters_initialise()
simcentre(1:3) = (posmax+posmin)*0.5

! Choose scale such that particles lie in range -0.5 to +0.5
scalefac = 0.25 / maxval(posmax(1:3)-simcentre(1:3))
scalefac = 0.25_pos_kind / maxval(posmax(1:3)-simcentre(1:3))

! Set initial view transform
call transform_initialise(view_transform)
Expand Down

0 comments on commit ffbadfc

Please sign in to comment.