| Home | Dev Workstation | Genealogy | Telephones | UNIX Tricks | My Music | Likes/Dislikes | Political Views | Programming Languages RSS Feed | Contact Me

John P. Willis

Opinions presented here are held in all of my roles and capacities, both personal and professional.


Summary

Politics: Leftist (AnCom)
Religion: Militantly Atheist
Occupation: Software Engineer
Preferences: View

Social Networking

Diaspora*
Mastodon
Twitter

Organizations

The GNU Project
The Free Software Foundation
American Civil Liberties Union

Computers & Programming

Programming Languages I Know
Greatest Common Divisor in 19 Languages
Microcomputer OS History
UNIX Tricks
The Datashed (personal datacenter)
Computer Collection
ChivaNet Internet Services
The VAX Pirate's Lair (my old website, ca. 2002)
YOUNGMUMPSTER (my tech blog)
GitLab
GitHub
GCC OS Test Macros

Genealogy

Genealogy Home
English Notable Kin
Scottish Notable Kin

Hobbies

Music
Telephones & PBX

Other Sites

Polls

Geek Code

-----BEGIN GEEK CODE BLOCK-----
Version: 3.1
GCS/E/G/H/IT/L/MU/P/SS d-- s+: a+ C++++ UBLAVHS++++$ P+ L++ E++ W+++$ N+ o? 
K- w++ O+++ M V+++>$ PS+++ PE-- Y+ !PGP t+++ !5 !X R tv b+++ DI++ D--- G e 
h---- r+++ x++++
------END GEEK CODE BLOCK------

Site Info

This site is hosted on a Sun SPARCserver 20 running Apache 2.2, Perl 5, and a home-built CMS.

RSS feed generation is done with a BASH script I have implemented, called Syndicator.

This site contains no JavaScript, no CSS, and should render in any HTML 2.0-compliant browser.

Greatest Common Divisor

Presented in Multiple Languages

COBOL | MUMPS | Java | C | Structured BASIC | FORTRAN 90 | Pascal | Ada | JavaScript | Python | Perl | ColdFusion | PL/2 REXX | PL/I | SNOBOL | Go | Tcl | Rust | Smalltalk-80

The code is available at https://github.com/CoherentLogic/gcd.

COBOL (Iterative)

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. GCD.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500 WORKING-STORAGE SECTION.
000550
000600 77      A PICTURE 9999.
000700 77      B PICTURE 9999.
000800 77      C PICTURE 9999.
000801 77      QUIT PICTURE 99.
000802 77      SCRATCH PICTURE 9999.
000802 77      RESULT PICTURE 9999.
000850
000900 PROCEDURE DIVISION.
001000 PROGRAM-BEGIN.
001100
001110     MOVE 54 TO A.
001120     MOVE 24 TO B.
001130     MOVE 0 TO QUIT.
001140     MOVE 0 TO RESULT.
001150
001200     IF A < B THEN
001300        MOVE A TO C
001400        MOVE B TO A
001500        MOVE C TO B
001600     END-IF.
001700
001800     PERFORM GCD WITH TEST AFTER UNTIL QUIT=1.
001810     IF RESULT IS ZERO THEN
001820        MOVE B TO RESULT
001830     END-IF.
001840
001850     DISPLAY "GCD of 54 and 24 is ".
001860     DISPLAY RESULT.
001870
001880     STOP-RUN.
001900
002000     GCD.
002100        DIVIDE B INTO A GIVING SCRATCH REMAINDER C.
002150
002200        IF C = 0 THEN
002300           MOVE 1 TO QUIT
002400           MOVE B TO RESULT
002500        END-IF.
002600
002700        MOVE B TO A.
002800        MOVE C TO B.

MUMPS (Recursive)

KBBMGCD ;GREATEST COMMON DIVISOR - IN MUMPS
 W "GCD of 54 and 24 is ",$$GCD(54,24),!
 Q
GCD(A,B) Q:B=0 A S R=$$GCD(B,A#B) Q R

Java (Recursive)

public class GCD {

    public static void main(String[] args) {

        System.out.printf("GCD of 54 and 24 is %d\n", gcd(54, 24));

    }

    public static int gcd(int a, int b) {

        if(b == 0) {
            return a;
        }
        else {
            return gcd(b, a % b);
        }

    }

}

C (Recursive)

#include <stdio.h>

int gcd(int, int);

main()
{
  printf("GCD of 54 and 24 is %d\n", gcd(54, 24));
}

int gcd(int a, int b)
{
  if(b == 0) {
    return a;
  }
  else {
    return gcd(b, a % b);
  }
}

Structured BASIC (Recursive)

declare function gcd(a as integer, b as integer) as integer

print "GCD of 54 and 24 is "; gcd(54, 24)

function gcd(a as integer, b as integer) as integer

         if b = 0 then
            return a
         else
            return gcd(b, a mod b)
         end if

end function

FORTRAN 90 (Iterative)

PROGRAM GCD

  IMPLICIT NONE
  INTEGER :: A, B, C

  A = 54
  B = 24

  IF (A .LT. B) THEN
     C = A
     A = B
     B = C
  END IF

  DO
     C = MOD(A, B)
     IF (C .EQ. 0) EXIT
     A = B
     B = C
  END DO

  WRITE(*,*) 'GCD of 54 and 24 is ', B

END PROGRAM GCD

Pascal (Iterative)

program GCD (Input, Output);

var a, b, c, result, quit : Integer;

begin

   a := 54;
   b := 24;
   result := 0;
   quit := 0;

   if a < b then
   begin
      c := a;
      a := b;
      b := c;
   end;

   repeat
      c := a mod b;

      if c = 0 then
      begin
         quit := 1;
         result := b;
      end;

      a := b;
      b := c;
   until quit = 1;

   if result = 0 then result := b;

   writeln('GCD of 54 and 24 is ', result);

end.

Ada (Iterative)

with Ada.Text_IO;
use Ada.Text_IO;
with Ada.Integer_Text_IO;
use Ada.Integer_Text_IO;

procedure GCD is
   A, B, C, Result, Quit : Integer;
begin
   A := 54;
   B := 24;
   Result := 0;
   Quit := 0;

   if A < B then
      C := A;
      A := B;
      B := C;
   end if;

CalcLoop:
    loop
       C := A mod B;

       if C = 0 then
          Quit := 1;
          Result := B;
       end if;

       A := B;
       B := C;

       exit CalcLoop when Quit = 1;
    end loop CalcLoop;

    if Result = 0 then
       Result := B;
    end if;

    Put("GCD of 54 and 24 is ");
    Put(Result);
    New_Line(1);

end GCD;

JavaScript (Recursive)

console.log("GCD of 54 and 24 is %d", gcd(54, 24));

function gcd(a,b) {
    if(b === 0) {
        return a;
    }
    else {
        return gcd(b, a % b);
    }
}

Python (Recursive)

#!/usr/bin/python

def gcd(a, b):

    if b == 0:
        return a
    else:
        return gcd(b, a % b)


print "GCD of 54 and 24 is ", gcd(54, 24)

Perl (Recursive)

#!/usr/bin/perl                                                                                                     
                                                                                                                    
sub gcd {                                                                                                           
    $a = $_[0];                                                                                                     
    $b = $_[1];                                                                                                     
                                                                                                                    
    if($b == 0) {                                                                                                   
        return $a;                                                                                                  
    }                                                                                                               
    else {                                                                                                          
        return gcd($b, $a % $b);                                                                                    
    }                                                                                                               
}                                                                                                                   
                                                                                                                    
print "GCD of 54 and 24 is ", gcd(54, 24);   

ColdFusion (CFScript; Recursive)

Component

component output="false" {

  public any function init() {
    return this;
  }

  public numeric function gcd(required numeric a, required numeric b) {

    if(arguments.b == 0) {
      return arguments.a;
    }
    else {
      return this.gcd(arguments.b, arguments.a % arguments.b);
    }

  }

}

Use in Page

<cfoutput>
  <cfset gcd = new GCD()>
  GCD of 54 and 24 is #gcd.gcd(54, 24)#
</cfoutput>

PL/2 REXX (Recursive)

say "GCD of 54 and 24 is " gcd(54, 24)

exit

gcd: procedure
     parse arg a, b

     if b = 0 then do
        return a
     end
     else do
        return gcd(b, a // b)
     end

PL/I (Recursive)

main:   procedure options (main);

gcd:    procedure(a, b) returns(fixed decimal);

        declare a fixed decimal;
        declare b fixed decimal;

        if b = 0 then
           return(a);
        else
           return(gcd(b, mod(a, b)));

end gcd;

        put list('GCD of 54 and 24 is ', gcd(54, 24));

end main;

SNOBOL (Iterative)

	A = 54
	B = 24
	RESULT = 0

	N = LT(A, B)			:S(FIXIT)

MAIN
REPEAT	C = REMDR(A, B)
	RESULT = EQ(C, 0) B		:S(DONE)
	A = B
	B = C				:(REPEAT)


DONE	OUTPUT = "GCD of 54 and 24 is " RESULT
		  			:(END)

FIXIT	C = A
	A = B
	B = C				:(MAIN)

END

Go (Recursive)

package main

import "fmt"

func main() {
	fmt.Printf("GCD of 54 and 24 is %d\n", gcd(54, 24))
}

func gcd(a, b int) int {

	if(b == 0) {
		return a	
	} else {
		return gcd(b, a % b)
	}

}

Tcl (Recursive)

#!/usr/bin/tclsh

proc gcd {a b} {
    
    if { $b == 0 } {
	return $a
    } else {
	return [gcd $b [expr $a % $b]]
    }	
}

set result [gcd 54 24]
puts "GCD of 54 and 24 is $result" 

Rust (Recursive)

fn gcd(a: i32, b: i32) -> i32 {
   if b == 0 {
      return a;
   } else {
      return gcd(b, a % b);
   }
}

fn main() {
   println!("GCD of 54 and 24 is {}", gcd(54, 24));
}

Smalltalk-80 (Built-In)

| a b result |

a := 54.
b := 24.

result := a gcd: b.

'GCD of 54 and 24 is ' print.
result printNl.

Revision History

$Log: gcd.shtml,v $
Revision 1.18  2019/09/05 00:45:13  jpw
Add license

Revision 1.17  2019/09/03 03:28:20  jpw
Add sidebar

Revision 1.16  2019/09/01 03:18:22  jpw
Add Smalltalk-80 example

Revision 1.15  2019/08/31 22:11:36  jpw
Add Rust example

Revision 1.14  2019/08/31 18:41:02  jpw
Add Tcl example

Revision 1.13  2019/08/31 17:38:20  jpw
Add Go example

Revision 1.12  2019/08/31 15:14:27  jpw
Add horizontal rules between examples

Revision 1.11  2019/08/31 03:22:53  jpw
Add SNOBOL example

Revision 1.10  2019/08/30 21:03:49  jpw
Add GitHub link

Revision 1.9  2019/08/30 20:44:04  jpw
Fix headers

Revision 1.8  2019/08/30 20:38:13  jpw
Add PL/I example

Revision 1.7  2019/08/29 21:00:04  jpw
Add PL/2 REXX example

Revision 1.6  2019/08/29 16:05:44  jpw
Fix TITLE tag

Revision 1.5  2019/08/29 00:37:35  jpw
Add ColdFusion example

Revision 1.4  2019/08/29 00:29:15  jpw
Add Perl example

Revision 1.3  2019/08/29 00:20:18  jpw
Add Python

Revision 1.2  2019/08/28 22:49:26  jpw
Add links to each language

Revision 1.1  2019/08/28 22:44:37  jpw
Initial revision



Copyright © 2019 John P. Willis
Last modified $Date: 2019/09/05 00:45:13 $

You are visitor number 00436

$Id: gcd.shtml,v 1.18 2019/09/05 00:45:13 jpw Exp $

Creative Commons License
This work is licensed under a Creative Commons Attribution-NonCommercial-NoDerivatives 4.0 International License.