Deutsch   English   Français   Italiano  
<v562fc$3m4do$1@dont-email.me>

View for Bookmarking (what is this?)
Look up another Usenet article

Path: ...!eternal-september.org!feeder3.eternal-september.org!news.eternal-september.org!.POSTED!not-for-mail
From: Lawrence D'Oliveiro <ldo@nz.invalid>
Newsgroups: comp.lang.fortran
Subject: Vintage Lunar Lander Game
Date: Sat, 22 Jun 2024 08:37:00 -0000 (UTC)
Organization: A noiseless patient Spider
Lines: 283
Message-ID: <v562fc$3m4do$1@dont-email.me>
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
Injection-Date: Sat, 22 Jun 2024 10:37:01 +0200 (CEST)
Injection-Info: dont-email.me; posting-host="e2ad63ef29eb171d8254bd46738c313e";
	logging-data="3871160"; mail-complaints-to="abuse@eternal-september.org";	posting-account="U2FsdGVkX190fLpLr3S5P9GmAkE4Z78p"
User-Agent: Pan/0.158 (Avdiivka; )
Cancel-Lock: sha1:cRabiQqo51pygZ5iqC8yBj6jgWs=
Bytes: 10943

!+
! My translation of the Fortran translation of the original Lunar
! Lander program from <https://www.cs.brandeis.edu/~storer/LunarLander/LunarLander.html>.
!-

program lunar_lander
    implicit none

    integer, parameter :: useprec = kind(0.0d0)
      ! need to use double precision; single precision is not enough
      ! to give correct results for second perfect game from above page
    real(kind = useprec) :: altitude, next_altitude, next_velocity, fuel_rate, elapsed
    real(kind = useprec) :: mass_total, mass_empty, time_subinterval, time_interval, velocity
    logical :: endgame, out_of_fuel, done_update
    real(kind = useprec), parameter :: G = 0.001
    real(kind = useprec), parameter :: Z = 1.8

    call intro

    do
        ! play another game
        print "(A//)", "FIRST RADAR CHECK COMING UP"
        print "(A)", "COMMENCE LANDING PROCEDURE"
        print "(A)", "TIME,SECS   ALTITUDE,MILES+FEET   VELOCITY,MPH   FUEL,LBS   FUEL RATE"

        altitude = 120
        velocity = 1
        mass_total = 32500
        mass_empty = 16500
        elapsed = 0
        out_of_fuel = .false.
        endgame = .false.
        do
            time_interval = 10
            write (*, fmt = "(i7, i16, i7, F15.2, F12.1, A9)", advance = "no") &
                nint(elapsed), int(altitude), nint(5280 * (altitude - int(altitude))), &
                3600 * velocity, mass_total - mass_empty, "K=:"
            call get_fuel_rate

            do
                if (mass_total - mass_empty .lt. 0.001) then
                    out_of_fuel = .true.
                    endgame = .true.
                    exit
                end if
                if (time_interval .lt. 0.001) &
                    exit ! start a new interval
                time_subinterval = time_interval
                if (mass_empty + time_subinterval * fuel_rate .gt. mass_total) &
                    time_subinterval = (mass_total - mass_empty) / fuel_rate
                      ! calculate only as far as ahead as fuel will allow
                call delta
                done_update = .false.
                if (next_altitude .le. 0) then
                    call down_to_the_ground
                    done_update = .true.
                else if (velocity .gt. 0 .and. next_velocity .lt. 0) then
                    call going_back_up
                    done_update = .true.
                end if
                if (endgame) &
                    exit
                if (.not. done_update) &
                    call update
            end do
            if (endgame) &
                exit
        end do
        call final_status

        print "(///A)", "TRY AGAIN?"
        if (.not. yn()) then
            print "(A)", "CONTROL OUT"
            exit
        end if
    end do

contains

    subroutine intro
        print "(A)", "CONTROL CALLING LUNAR MODULE. MANUAL CONTROL IS NECESSARY"
        print "(A)", "YOU MAY RESET FUEL RATE K EACH 10 SECS TO 0 OR ANY VALUE"
        print "(A)", "BETWEEN 8 & 200 LBS/SEC. YOU'VE 16000 LBS FUEL. ESTIMATED"
        print "(A)", "FREE FALL IMPACT TIME-120 SECS. CAPSULE WEIGHT-32500 LBS"
    end subroutine

    subroutine get_fuel_rate
        ! asks the user what fuel rate to apply for the next interval.
        integer :: ios
        do
            read (*, *, iostat = ios) fuel_rate
            if (ios .eq. 0) then
                if ( &
                        fuel_rate .gt. 200 &
                    .or. &
                        fuel_rate .lt. 0 &
                    .or. &
                        fuel_rate .lt. 8 .and. fuel_rate .gt. 0 &
                ) &
                    ios = 1
            end if
            if (ios .eq. 0) &
                exit
            write (*, fmt = "(A)", advance = "no") "NOT POSSIBLE"
            call dots
            write (*, fmt = "(A)", advance = "no") "K=:"
        end do
    end subroutine

    subroutine dots
        integer :: loop
        do loop = 1, 51
            write (*, fmt = "(A)", advance = "no") "."
        end do
    end subroutine

    logical function yn() result(y)
        ! prompts the user for an answer to a yes/no question.
        character(len = 3) :: ans
        do
            write (*, fmt = "(A)", advance = "no") "(ANS. YES OR NO):"
            read *, ans
            if (ans .eq. "Y" .or. ans .eq. "y" .or. ans .eq. "YES" .or. ans .eq. "yes") then
                y = .true.
                exit
            else if (ans .eq. "N" .or. ans .eq. "n" .or. ans .eq. "NO" .or. ans .eq. "no") then
                y = .false.
                exit
            end if
        end do
    end function

    subroutine update
        ! updates the time and spacecraft fuel, altitude and velocity.
        elapsed = elapsed + time_subinterval
        time_interval = time_interval - time_subinterval
        mass_total = mass_total - time_subinterval * fuel_rate
        altitude = next_altitude
        velocity = next_velocity
    end subroutine

    subroutine delta
        ! calculates the new velocity and altitude at the end of the
        ! current time subinterval.
        real(kind = useprec) :: delta_v, delta_v2, delta_v4

        delta_v = time_subinterval * fuel_rate / mass_total
        delta_v2 = delta_v * delta_v ! just to shorten ...
        delta_v4 = delta_v2 * delta_v2 ! ... some formulas
        next_velocity = &
                velocity &
            + &
                G * time_subinterval &
            - &
                    Z &
                * &
                    ( &
                        delta_v &
                    + &
                        delta_v2 / 2 &
                    + &
                        delta_v2 * delta_v / 3 &
                    + &
                        delta_v4 / 4 &
                    + &
                        delta_v4 * delta_v / 5 &
                    )
        next_altitude = &
                altitude &
            - &
                G * time_subinterval * time_subinterval / 2 &
            - &
                velocity * time_subinterval &
            + &
                    Z &
                * &
                    time_subinterval &
                * &
                    ( &
                        delta_v / 2 &
                    + &
                        delta_v2 / 6 &
========== REMAINDER OF ARTICLE TRUNCATED ==========