un commit pour montrer aux gens
This commit is contained in:
		
							parent
							
								
									c3c6caafb8
								
							
						
					
					
						commit
						ba2c9f653c
					
				@ -2,7 +2,7 @@
 | 
			
		||||
#    Fortraneries by tTh - Gravity Field
 | 
			
		||||
#
 | 
			
		||||
 | 
			
		||||
GFOPT   = -Wall -Wextra -g -time -pg -I../Modules
 | 
			
		||||
GFOPT   = -Wall -Wextra -g -time -I../Modules
 | 
			
		||||
MODOBJ  = '../Modules/spitpgm.o'
 | 
			
		||||
 | 
			
		||||
all:	essai
 | 
			
		||||
 | 
			
		||||
@ -9,48 +9,107 @@ program essai
 | 
			
		||||
 | 
			
		||||
  implicit none
 | 
			
		||||
 | 
			
		||||
  type(massbody)          :: planet
 | 
			
		||||
  type(massbody)          :: planets(60)
 | 
			
		||||
  integer                 :: foo
 | 
			
		||||
  character(len=100)      :: filename
 | 
			
		||||
 | 
			
		||||
  planet%posx   = 337.314
 | 
			
		||||
  planet%posy   = 164.666
 | 
			
		||||
  planet%mass   = 1e8
 | 
			
		||||
  planet%serial = 42
 | 
			
		||||
  call init_random()
 | 
			
		||||
 | 
			
		||||
  do foo=0, 48
 | 
			
		||||
    write (filename, "(a, i5.5, a)") 'WS/', foo, '.pgm'
 | 
			
		||||
    call build_and_write_a_field(800, 600, planet, filename)
 | 
			
		||||
    planet%posx = planet%posx + 6.99
 | 
			
		||||
    planet%posy = planet%posy + 2.55
 | 
			
		||||
  call create_some_planets(planets, 45e5)
 | 
			
		||||
 | 
			
		||||
  do foo=0, 72
 | 
			
		||||
    write (filename, "(a, i5.5, a)") 'WS/A', foo, '.pgm'
 | 
			
		||||
    call build_and_write_a_field(640, 480, planets, filename)
 | 
			
		||||
    print *, trim(filename)
 | 
			
		||||
    ! OMG! two magic numbers, wtf?
 | 
			
		||||
    planets(1)%posx = planets(1)%posx + 8.08
 | 
			
		||||
    planets(1)%posy = planets(1)%posy + 6.42
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  STOP 'YOLO'
 | 
			
		||||
  STOP 'BECAUSE YOLO'
 | 
			
		||||
 | 
			
		||||
contains
 | 
			
		||||
!-----------------------------------------------------------------------
 | 
			
		||||
!-
 | 
			
		||||
!    Yes, I know, this is a disturbing kluge, but I like it :}
 | 
			
		||||
!    May be, it's time to read the doc of modern Fortran
 | 
			
		||||
!-
 | 
			
		||||
subroutine init_random()
 | 
			
		||||
 | 
			
		||||
  integer, dimension(3) :: tarray
 | 
			
		||||
  integer               :: t3
 | 
			
		||||
  real                  :: dummy
 | 
			
		||||
  call itime(tarray)
 | 
			
		||||
  t3 = 8971*tarray(1) + 443*tarray(2) + tarray(3)
 | 
			
		||||
  write(0, '(A,3I3,A,I6)') "sranding: ", tarray, " --> ", t3
 | 
			
		||||
  call srand(t3)
 | 
			
		||||
  ! after initializing the random generator engine,
 | 
			
		||||
  ! you MUST use it for initializing the initializer
 | 
			
		||||
  dummy = rand()
 | 
			
		||||
  write(0, *) 'dummy was ', dummy
 | 
			
		||||
 | 
			
		||||
end subroutine
 | 
			
		||||
!-----------------------------------------------------------------------
 | 
			
		||||
!-
 | 
			
		||||
!     make a few solid body to play with...
 | 
			
		||||
!-
 | 
			
		||||
subroutine create_some_planets(planets, coef)
 | 
			
		||||
  type(massbody), intent(inout)     :: planets(:)
 | 
			
		||||
  real, intent(in)                  :: coef
 | 
			
		||||
  integer                           :: foo
 | 
			
		||||
  ! real                              :: quux, quuy
 | 
			
		||||
  character(100)                    :: fmt
 | 
			
		||||
 | 
			
		||||
  fmt = "(I4, '   : ', 2(F9.2, '  '), e11.3, I7)"
 | 
			
		||||
 | 
			
		||||
  do foo=1, ubound(planets, 1)
 | 
			
		||||
    if (foo .EQ. 1) then
 | 
			
		||||
      planets(1)%posx   = 20
 | 
			
		||||
      planets(1)%posy   = 20
 | 
			
		||||
      planets(1)%mass   = 9e8
 | 
			
		||||
      planets(1)%serial = 1337
 | 
			
		||||
    else
 | 
			
		||||
      planets(foo)%posx     = rand() * 639.999
 | 
			
		||||
      planets(foo)%posy     = rand() * 479.999
 | 
			
		||||
      planets(foo)%mass     = 7e6 + coef*foo
 | 
			
		||||
      planets(foo)%serial   = foo
 | 
			
		||||
    endif
 | 
			
		||||
    write (*, fmt) foo, planets(foo)
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  ! STOP 'ABEND'
 | 
			
		||||
 | 
			
		||||
end subroutine
 | 
			
		||||
!-----------------------------------------------------------------------
 | 
			
		||||
!-
 | 
			
		||||
!   compute a field with only one body; and write pic file
 | 
			
		||||
!-
 | 
			
		||||
subroutine build_and_write_a_field(szx, szy, moon, fname)
 | 
			
		||||
subroutine build_and_write_a_field(szx, szy, moons, fname)
 | 
			
		||||
  integer, intent(in)                :: szx, szy
 | 
			
		||||
  type(massbody), intent(in)         :: moon
 | 
			
		||||
  type(massbody), intent(in)         :: moons(:)
 | 
			
		||||
  character(len=*), intent(in)       :: fname
 | 
			
		||||
 | 
			
		||||
  real                                  :: maxi, mini
 | 
			
		||||
  integer                            :: errcode
 | 
			
		||||
  real,    dimension(:,:), allocatable  :: field
 | 
			
		||||
  integer                               :: errcode, foo
 | 
			
		||||
  real,    dimension(:,:), allocatable  :: field, tmpf
 | 
			
		||||
  integer, dimension(:,:), allocatable  :: greymap
 | 
			
		||||
 | 
			
		||||
  allocate(field(szx, szy), stat=errcode)
 | 
			
		||||
  allocate(tmpf(szx, szy), stat=errcode)
 | 
			
		||||
 | 
			
		||||
  field = 0.0
 | 
			
		||||
  do foo=1, ubound(moons, 1)
 | 
			
		||||
    call compute_a_field(tmpf, moons(foo))
 | 
			
		||||
    tmpf = tmpf * 0.019
 | 
			
		||||
    field = field + tmpf
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
  call compute_a_field(field, moon)
 | 
			
		||||
  maxi = maxval(field)
 | 
			
		||||
  mini = minval(field)
 | 
			
		||||
  print *, "field: ", mini, maxi, maxi-mini
 | 
			
		||||
  ! print *, "field: ", mini, maxi, maxi-mini
 | 
			
		||||
 | 
			
		||||
  allocate(greymap(szx, szy), stat=errcode)
 | 
			
		||||
  greymap = 65535
 | 
			
		||||
  greymap = 0
 | 
			
		||||
  ! convert from real value to 16 bits int values
 | 
			
		||||
  where (field < 65530.0)
 | 
			
		||||
    greymap = int(field)
 | 
			
		||||
 | 
			
		||||
@ -27,11 +27,12 @@ function compute_gravity(fx, fy, body)
 | 
			
		||||
  rx = fx - body%posx
 | 
			
		||||
  ry = fy - body%posy
 | 
			
		||||
  dist = sqrt( (rx*rx) + (ry*ry) )
 | 
			
		||||
  if (dist .LT. 4.50) then
 | 
			
		||||
    write (0, *) "dist too small ", dist
 | 
			
		||||
  if (dist .LT. 0.11) then
 | 
			
		||||
    ! write (0, *) "dist too small ", dist
 | 
			
		||||
    compute_gravity = 0e0
 | 
			
		||||
  endif
 | 
			
		||||
  else
 | 
			
		||||
    compute_gravity = body%mass / (dist ** 2)
 | 
			
		||||
  endif
 | 
			
		||||
 | 
			
		||||
end function
 | 
			
		||||
 | 
			
		||||
@ -63,7 +64,6 @@ subroutine compute_a_field(field, moon)
 | 
			
		||||
 | 
			
		||||
end subroutine
 | 
			
		||||
!-----------------------------------------------------------------------
 | 
			
		||||
 | 
			
		||||
!-----------------------------------------------------------------------
 | 
			
		||||
 | 
			
		||||
end module
 | 
			
		||||
 | 
			
		||||
@ -4,7 +4,7 @@ set -e				# stop on error
 | 
			
		||||
 | 
			
		||||
make essai
 | 
			
		||||
 | 
			
		||||
./essai
 | 
			
		||||
time ./essai
 | 
			
		||||
 | 
			
		||||
convert -delay 10 WS/*.pgm foo.gif
 | 
			
		||||
convert -delay 20 WS/A*.pgm foo.gif
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		Loading…
	
		Reference in New Issue
	
	Block a user