Box the compass

From Rosetta Code
Revision as of 01:38, 29 January 2012 by Markjreed (talk | contribs) (→‎{{header|UNIX Shell}}: Add trans)
Task
Box the compass
You are encouraged to solve this task according to the task description, using any language you may know.

Avast me hearties!

There be many a land lubber that knows naught of the pirate ways and gives direction by degree! They know not how to box the compass!

Task description

  1. Create a function that takes a heading in degrees and returns the correct 32-point compass heading.
  2. Use the function to print and display a table of Index, Compass point, and Degree; rather like the corresponding columns from, the first table of the wikipedia article, but use only the following 33 headings as input:
[0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5, 84.37, 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75, 185.62, 185.63, 202.5, 219.37, 219.38, 236.25, 253.12, 253.13, 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38]. (They should give the same order of points but are spread throughout the ranges of acceptance).
Notes;
  • The headings and indices can be calculated from this pseudocode:
for i in 0..32 inclusive:
    heading = i * 11.25
    case i %3:
      if 1: heading += 5.62; break
      if 2: heading -= 5.62; break
    end
    index = ( i mod 32) + 1
  • The column of indices can be thought of as an enumeration of the thirty two cardinal points (see talk page)..

Ada

Inspired by the C++ program, but without the need for a specific library.

<lang Ada>with Ada.Text_IO;

procedure Box_The_Compass is

  type Degrees is digits 5 range 0.00 .. 359.99;
  type Index_Type is mod 32;
  function Long_Name(Short: String) return String is
     function Char_To_Name(Char: Character) return String is
     begin
        case Char is
           when 'N' | 'n' => return Char & "orth";
           when 'S' | 's' => return Char & "outh";
           when 'E' | 'e' => return Char & "ast";
           when 'W' | 'w' => return Char & "est";
           when 'b' => return " by ";
           when '-' => return "-";
           when others => raise Constraint_Error;
        end case;
     end Char_To_Name;
  begin
     if Short'Length = 0 or else Short(Short'First)=' ' then
        return "";
     else
        return Char_To_Name(Short(Short'First))
          & Long_Name(Short(Short'First+1 .. Short'Last));
     end if;
  end Long_Name;
  procedure Put_Line(Angle: Degrees) is
     function Index(D: Degrees) return Index_Type is
     begin
        return Index_Type(Integer(Degrees'Rounding(D/11.25)) mod 32);
     end Index;
     I: Integer := Integer(Index(Angle))+1;
     package DIO is new Ada.Text_IO.Float_IO(Degrees);
     Abbr: constant array(Index_Type) of String(1 .. 4)
       := ("N   ", "Nbe ", "N-ne", "Nebn", "Ne  ", "Nebe", "E-ne", "Ebn ",
           "E   ", "Ebs ", "E-se", "Sebe", "Se  ", "Sebs", "S-se", "Sbe ",
           "S   ", "Sbw ", "S-sw", "Swbs", "Sw  ", "Swbw", "W-sw", "Wbs ",
           "W   ", "Wbn ", "W-nw", "Nwbw", "Nw  ", "Nwbn", "N-nw", "Nbw ");
  begin
     DIO.Put(Angle, Fore => 3, Aft => 2, Exp => 0); -- format "zzx.xx"
     Ada.Text_IO.Put(" |");
     if I <= 9 then
        Ada.Text_IO.Put(" ");
     end if;
     Ada.Text_IO.Put_Line(" "  & Integer'Image(I) & " | "
                            & Long_Name(Abbr(Index(Angle))));
  end Put_Line;
  Difference: constant array(0..2) of Degrees'Base
    := (0=> 0.0, 1=> +5.62, 2=> - 5.62);

begin

  Ada.Text_IO.Put_Line(" angle | box | compass point");
  Ada.Text_IO.Put_Line(" ---------------------------------");
  for I in 0 .. 32 loop
     Put_Line(Degrees(Degrees'Base(I) * 11.25 + Difference(I mod 3)));
  end loop;

end Box_The_Compass;</lang>

Output:

 angle | box | compass point
 ---------------------------------
  0.00 |   1 | North
 16.87 |   2 | North by east
 16.88 |   3 | North-northeast
 33.75 |   4 | Northeast by north
 50.62 |   5 | Northeast
 50.63 |   6 | Northeast by east
 67.50 |   7 | East-northeast
 84.37 |   8 | East by north
 84.38 |   9 | East
101.25 |  10 | East by south
118.12 |  11 | East-southeast
118.13 |  12 | Southeast by east
135.00 |  13 | Southeast
151.87 |  14 | Southeast by south
151.88 |  15 | South-southeast
168.75 |  16 | South by east
185.62 |  17 | South
185.63 |  18 | South by west
202.50 |  19 | South-southwest
219.37 |  20 | Southwest by south
219.38 |  21 | Southwest
236.25 |  22 | Southwest by west
253.12 |  23 | West-southwest
253.13 |  24 | West by south
270.00 |  25 | West
286.87 |  26 | West by north
286.88 |  27 | West-northwest
303.75 |  28 | Northwest by west
320.62 |  29 | Northwest
320.63 |  30 | Northwest by north
337.50 |  31 | North-northwest
354.37 |  32 | North by west
354.38 |   1 | North

ALGOL 68

Works with: ALGOL 68 version Revision 1 - no extensions to language used.
Works with: ALGOL 68G version Any - tested with release 1.18.0-9h.tiny.

<lang algol68>#!/usr/local/bin/a68g --script #

[]STRING

 long  by nesw = (" by ", "North", "East", "South", "West"),
 short by nesw = ("b", "N", "E", "S", "W");

MODE MINUTES = REAL; # minutes type # INT last minute=360*60; INT point width=last minute OVER 32;

PROC direction name = (REAL direction in minutes, []STRING locale directions)STRING: (

 STRING by = locale directions[1];
 []STRING nesw = locale directions[@-1];
 PRIO MASK = 7; # same PRIOrity as * and / #
 OP MASK = (INT n, BITS lower)INT: ABS (BIN n AND NOT lower),
    DECAP = (STRING s)STRING: IF UPB s > 1 THEN REPR (ABS s[1]-ABS "A"+ABS "a")+s[2:] ELSE s FI;
 PROC point name = (INT in point)STRING: (
   INT point = in point MOD 32 # 32 points of a compass #;
   IF point MOD 8 = 0 THEN
  1. name the principle point: eg. N, E, S or W #
     nesw[point OVER 8]
   ELIF point MOD 4 = 0 THEN
  1. name the half: eg. NE, SE, SW or NW #
     point name((point+8)MASK 2r1111)+DECAP point name(point MASK 2r1111 + 8)
   ELIF point MOD 2 = 0 THEN
  1. name the quarter: eg. N-NE, E-NE, E-SE, S-SE, S-SW, W-SW, W-NW or N-NW #
     point name((point+4)MASK 2r111)+"-"+point name(point MASK 2r111 + 4)
   ELSE # Name the sixteenth point: #
  1. eg. NbE,NEbN,NEbE,EbN,EbS,SEbE,SEbS,SbE,SbW,SWbS,SWbW,WbS,WbN,NWbW,NWbN,NbW #
     INT opp point = point OVER 8 + ABS NOT ODD (point OVER 2);
     point name((point+2)MASK 2r11)+ by +nesw(opp point MOD 4)
   FI
 );
 point name(ROUND(direction in minutes/point width))

);

PROC traditional name = (MINUTES minutes)STRING: (

 INT degrees = ROUND(minutes / 60);
 degrees=0  |"Tramontana"          |:
 degrees=45 |"Greco or Bora"       |:
 degrees=90 |"Levante"             |:
 degrees=135|"Sirocco"             |:
 degrees=180|"Ostro"               |:
 degrees=225|"Libeccio"            |:
 degrees=270|"Poniente or Zephyrus"|:
 degrees=315|"Mistral"             |:
 degrees=360|"Tramontana"          |""

);

  1. First generate the test set results #

test:(

 printf($"Test:"l$);
 FOR i FROM 0 TO 32 DO
   REAL heading = i * 11.25 +
     CASE i MOD 3 IN
       +5.62,
       -5.62
       OUT 0
     ESAC;
   INT index = ( i MOD 32) + 1;
   printf(($zd" ", g23k, zzd.zzl$, index , direction name(heading*60, long by nesw), heading))
 OD

);

table:(

 OP OVER = (REAL r, INT base)INT: ENTIER ABS r OVER  base,
    MOD = (REAL r, INT base)REAL: ( INT i = ENTIER r; i MOD base + r - i);
 printf(
   $l"Table:"l
   " #|Compass point"22k"|Abbr|Traditional wind point| Lowest°′ | Middle°′ | Highest°′"l$
 );
 OP DEGMIN = (REAL minutes)STRUCT(INT d, REAL m): (minutes MOD last minute OVER 60, minutes MOD 60);
 FOR point FROM 1 TO 32 DO
   REAL centre = (point-1) * point width;
   REAL from =  centre - point width/2,
        to   =  centre + point width/2-1/120;
   printf((
           $g(-2)"|"$, point,
           $g$, direction name(centre, long by nesw),
           $22k"|"g$, direction name(centre, short by nesw),
           $27k"|"g$, traditional name(centre),
           $50k$, $"|"g(-3)"°", dd.dd"′"$, DEGMIN from, DEGMIN centre, DEGMIN to,
           $l$
         ))
 OD

)</lang> Output:

Test:
 1 North                0.00
 2 North by East       16.87
 3 North-Northeast     16.88
 4 Northeast by North  33.75
 5 Northeast           50.62
 6 Northeast by East   50.63
 7 East-Northeast      67.50
 8 East by North       84.37
 9 East                84.38
10 East by South      101.25
11 East-Southeast     118.12
12 Southeast by East  118.13
13 Southeast          135.00
14 Southeast by South 151.87
15 South-Southeast    151.88
16 South by East      168.75
17 South              185.62
18 South by West      185.63
19 South-Southwest    202.50
20 Southwest by South 219.37
21 Southwest          219.38
22 Southwest by West  236.25
23 West-Southwest     253.12
24 West by South      253.13
25 West               270.00
26 West by North      286.87
27 West-Northwest     286.88
28 Northwest by West  303.75
29 Northwest          320.62
30 Northwest by North 320.63
31 North-Northwest    337.50
32 North by West      354.37
 1 North              354.38

Table:
 #|Compass point     |Abbr|Traditional wind point| Lowest°′ | Middle°′ | Highest°′
 1|North             |N   |Tramontana            |354°22.50′|  0°00.00′|  5°37.49′
 2|North by East     |NbE |                      |  5°37.50′| 11°15.00′| 16°52.49′
 3|North-Northeast   |N-NE|                      | 16°52.50′| 22°30.00′| 28°07.49′
 4|Northeast by North|NEbN|                      | 28°07.50′| 33°45.00′| 39°22.49′
 5|Northeast         |NE  |Greco or Bora         | 39°22.50′| 45°00.00′| 50°37.49′
 6|Northeast by East |NEbE|                      | 50°37.50′| 56°15.00′| 61°52.49′
 7|East-Northeast    |E-NE|                      | 61°52.50′| 67°30.00′| 73°07.49′
 8|East by North     |EbN |                      | 73°07.50′| 78°45.00′| 84°22.49′
 9|East              |E   |Levante               | 84°22.50′| 90°00.00′| 95°37.49′
10|East by South     |EbS |                      | 95°37.50′|101°15.00′|106°52.49′
11|East-Southeast    |E-SE|                      |106°52.50′|112°30.00′|118°07.49′
12|Southeast by East |SEbE|                      |118°07.50′|123°45.00′|129°22.49′
13|Southeast         |SE  |Sirocco               |129°22.50′|135°00.00′|140°37.49′
14|Southeast by South|SEbS|                      |140°37.50′|146°15.00′|151°52.49′
15|South-Southeast   |S-SE|                      |151°52.50′|157°30.00′|163°07.49′
16|South by East     |SbE |                      |163°07.50′|168°45.00′|174°22.49′
17|South             |S   |Ostro                 |174°22.50′|180°00.00′|185°37.49′
18|South by West     |SbW |                      |185°37.50′|191°15.00′|196°52.49′
19|South-Southwest   |S-SW|                      |196°52.50′|202°30.00′|208°07.49′
20|Southwest by South|SWbS|                      |208°07.50′|213°45.00′|219°22.49′
21|Southwest         |SW  |Libeccio              |219°22.50′|225°00.00′|230°37.49′
22|Southwest by West |SWbW|                      |230°37.50′|236°15.00′|241°52.49′
23|West-Southwest    |W-SW|                      |241°52.50′|247°30.00′|253°07.49′
24|West by South     |WbS |                      |253°07.50′|258°45.00′|264°22.49′
25|West              |W   |Poniente or Zephyrus  |264°22.50′|270°00.00′|275°37.49′
26|West by North     |WbN |                      |275°37.50′|281°15.00′|286°52.49′
27|West-Northwest    |W-NW|                      |286°52.50′|292°30.00′|298°07.49′
28|Northwest by West |NWbW|                      |298°07.50′|303°45.00′|309°22.49′
29|Northwest         |NW  |Mistral               |309°22.50′|315°00.00′|320°37.49′
30|Northwest by North|NWbN|                      |320°37.50′|326°15.00′|331°52.49′
31|North-Northwest   |N-NW|                      |331°52.50′|337°30.00′|343°07.49′
32|North by West     |NbW |                      |343°07.50′|348°45.00′|354°22.49′

AutoHotkey

Translation of: C++
Works with: AutoHotkey_L

<lang AHK>get_Index(angle){

   return Mod(floor(angle / 11.25 +0.5), 32) + 1

}

get_Abbr_From_Index(i){

   static points
      := [ "N", "NbE", "NNE", "NEbN", "NE", "NEbE", "ENE", "EbN"
          ,"E", "EbS", "ESE", "SEbE", "SE", "SEbS", "SSE", "SbE"
          ,"S", "SbW", "SSW", "SWbS", "SW", "SWbW", "WSW", "WbS"
          ,"W", "WbN", "WNW", "NWbW", "NW", "NWbN", "NNW", "NbW" ]
   return points[i]

}

Build_Name_From_Abbr(a){

   Loop Parse, a
   {
       i := A_Index
       if ((i = 2) && (SubStr(a, i, 1) != "b") && (StrLen(a) == 3))
           retval .= "-"
       retval .= {N: "north", S: "south", E: "east"
                , W: "west" , b: " by "}[A_LoopField]
   }
   return Chr(Asc(SubStr(retval, 1, 1))-32) . SubStr(retval, 2)

}

test

headings:= [0.00, 16.87, 16.88, 33.75, 50.62, 50.63, 67.50, 84.37, 84.38, 101.25

         , 118.12, 118.13, 135.00, 151.87, 151.88, 168.75, 185.62, 185.63
         , 202.50, 219.37, 219.38, 236.25, 253.12, 253.13, 270.00, 286.87
         , 286.88, 303.75, 320.62, 320.63, 337.50, 354.37, 354.38]

For n, a in headings {

   i := get_Index(a)
   out .= SubStr(" " i, -1) " "
       . SubStr(Build_Name_From_Abbr(get_Abbr_From_Index(i))
       . "                    ", 1, 24) . SubStr("  " a, -5)  . "`r`n" ; 

} clipboard := out</lang>

Output
 1 North                     0.00
 2 North by east            16.87
 3 North-northeast          16.88
 4 Northeast by north       33.75
 5 Northeast                50.62
 6 Northeast by east        50.63
 7 East-northeast           67.50
 8 East by north            84.37
 9 East                     84.38
10 East by south           101.25
11 East-southeast          118.12
12 Southeast by east       118.13
13 Southeast               135.00
14 Southeast by south      151.87
15 South-southeast         151.88
16 South by east           168.75
17 South                   185.62
18 South by west           185.63
19 South-southwest         202.50
20 Southwest by south      219.37
21 Southwest               219.38
22 Southwest by west       236.25
23 West-southwest          253.12
24 West by south           253.13
25 West                    270.00
26 West by north           286.87
27 West-northwest          286.88
28 Northwest by west       303.75
29 Northwest               320.62
30 Northwest by north      320.63
31 North-northwest         337.50
32 North by west           354.37
 1 North                   354.38

AWK

<lang awk>#!/usr/bin/awk -f BEGIN {

 split("N NbE NNE NEbN NE NEbE ENE EbN E EbS ESE SEbE SE SEbS SSE SbE S SbW SSW SWbS SW SWbW WSW WbS W WbN WNW NWbW NW NWbN NNW NbW",A," "); 

}

function ceil(x) { y = int(x) return y < x ? y + 1 : y }

function compassbox(d) {

   return ceil( ( (d + 360 / 64) % 360) * 32 / 360); 

}

{

   box = compassbox($1);
   printf "%6.2f : %2d\t%s\n",$1,box,A[box];

} </lang> Output:

  0.00 :  1	N
 16.87 :  2	NbE
 16.88 :  3	NNE
 33.75 :  4	NEbN
 50.62 :  5	NE
 50.63 :  6	NEbE
 67.50 :  7	ENE
 84.37 :  8	EbN
 84.38 :  9	E
101.25 : 10	EbS
118.12 : 11	ESE
118.13 : 12	SEbE
135.00 : 13	SE
151.87 : 14	SEbS
151.88 : 15	SSE
168.75 : 16	SbE
185.62 : 17	S
185.63 : 18	SbW
202.50 : 19	SSW
219.37 : 20	SWbS
219.38 : 21	SW
236.25 : 22	SWbW
253.12 : 23	WSW
253.13 : 24	WbS
270.00 : 25	W
286.87 : 26	WbN
286.88 : 27	WNW
303.75 : 28	NWbW
320.62 : 29	NW
320.63 : 30	NWbN
337.50 : 31	NNW
354.37 : 32	NbW
354.38 :  1	N

BBC BASIC

<lang bbcbasic> DIM bearing(32)

     bearing() = 0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5, 84.37, \
     \ 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75, \
     \ 185.62, 185.63, 202.5, 219.37, 219.38, 236.25, 253.12, 253.13, \
     \ 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38
     
     FOR i% = 0 TO 32
       box% = FNcompassbox(bearing(i%), compass$)
       PRINT ; bearing(i%), ; box%, compass$
     NEXT
     END
     
     DEF FNcompassbox(bearing, RETURN box$)
     LOCAL pt%
     pt% = INT(bearing / 360 * 32 + 0.5) MOD 32
     box$ = FNpt(pt%)
     LEFT$(box$,1) = CHR$(ASC(LEFT$(box$,1))-32)
     = pt% + 1
     
     DEF FNpt(pt%)
     LOCAL pt$() : DIM pt$(3)
     IF pt% AND 1 THEN = FNpt((pt% + 1) AND 28) + " by " + \
     \                   FNpt(((2 - (pt% AND 2)) * 4) + pt% AND 24)
     IF pt% AND 2 THEN = FNpt((pt% + 2) AND 24) + "-" + FNpt((pt% OR 4) AND 28)
     IF pt% AND 4 THEN = FNpt((pt% + 8) AND 16) + FNpt((pt% OR 8) AND 24)
     pt$() = "north", "east", "south", "west"
     = pt$(pt% DIV 8)

</lang> Output:

0         1         North
16.87     2         North by east
16.88     3         North-northeast
33.75     4         Northeast by north
50.62     5         Northeast
50.63     6         Northeast by east
67.5      7         East-northeast
84.37     8         East by north
84.38     9         East
101.25    10        East by south
118.12    11        East-southeast
118.13    12        Southeast by east
135       13        Southeast
151.87    14        Southeast by south
151.88    15        South-southeast
168.75    16        South by east
185.62    17        South
185.63    18        South by west
202.5     19        South-southwest
219.37    20        Southwest by south
219.38    21        Southwest
236.25    22        Southwest by west
253.12    23        West-southwest
253.13    24        West by south
270       25        West
286.87    26        West by north
286.88    27        West-northwest
303.75    28        Northwest by west
320.62    29        Northwest
320.63    30        Northwest by north
337.5     31        North-northwest
354.37    32        North by west
354.38    1         North

C

This example is incorrect. Please fix the code and remove this message.

Details: There should be no index 33 as both the wp article and task showed.

Like Wikipedia's article, this program uses indexes to count the headings. There are now 33 headings, from 1 to 33, because 0.0 and 354.38 are different angles. (This differs from the task pseudocode, which mapped the 32 compass points to indexes.)

<lang C>#include <stdio.h>

int main() {

       int i, j;
       double degrees[] = { 0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5,
               84.37, 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88,
               168.75, 185.62, 185.63, 202.5, 219.37, 219.38, 236.25, 253.12,
               253.13, 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5,
               354.37, 354.38 };
       char * names =  "North                 "
                       "North by east         "
                       "North-northeast       "
                       "Northeast by north    "
                       "Northeast             "
                       "Northeast by east     "
                       "East-northeast        "
                       "East by north         "
                       "East                  "
                       "East by south         "
                       "East-southeast        "
                       "Southeast by east     "
                       "Southeast             "
                       "Southeast by south    "
                       "South-southeast       "
                       "South by east         "
                       "South                 "
                       "South by west         "
                       "South-southwest       "
                       "Southwest by south    "
                       "Southwest             "
                       "Southwest by west     "
                       "West-southwest        "
                       "West by south         "
                       "West                  "
                       "West by north         "
                       "West-northwest        "
                       "Northwest by west     "
                       "Northwest             "
                       "Northwest by north    "
                       "North-northwest       "
                       "North by west         "
                       "North                 ";
       for (i = 0; i < 33; i++) {
               j = .5 + degrees[i] * 32 / 360;
               printf("%2d  %.22s  %6.2f\n", i + 1, names + (j % 32) * 22,
                       degrees[i]);
       }
       return 0;

}</lang>Output:

 1  North                     0.00
 2  North by east            16.87
 3  North-northeast          16.88
 4  Northeast by north       33.75
 5  Northeast                50.62
 6  Northeast by east        50.63
 7  East-northeast           67.50
 8  East by north            84.37
 9  East                     84.38
10  East by south           101.25
11  East-southeast          118.12
12  Southeast by east       118.13
13  Southeast               135.00
14  Southeast by south      151.87
15  South-southeast         151.88
16  South by east           168.75
17  South                   185.62
18  South by west           185.63
19  South-southwest         202.50
20  Southwest by south      219.37
21  Southwest               219.38
22  Southwest by west       236.25
23  West-southwest          253.12
24  West by south           253.13
25  West                    270.00
26  West by north           286.87
27  West-northwest          286.88
28  Northwest by west       303.75
29  Northwest               320.62
30  Northwest by north      320.63
31  North-northwest         337.50
32  North by west           354.37
33  North                   354.38

C++

Using the Boost libraries

Library: Boost

<lang cpp>#include <string>

  1. include <boost/array.hpp>
  2. include <boost/assign/list_of.hpp>
  3. include <boost/format.hpp>
  4. include <boost/foreach.hpp>
  5. include <iostream>
  6. include <math.h>

using std::string; using namespace boost::assign;

int get_Index(float angle) {

  return static_cast<int>(floor(angle / 11.25 +0.5 )) % 32 + 1;

}

string get_Abbr_From_Index(int i) {

   static boost::array<std::string, 32> points(list_of
           ("N")("NbE")("NNE")("NEbN")("NE")("NEbE")("ENE")("EbN")
           ("E")("EbS")("ESE")("SEbE")("SE")("SEbS")("SSE")("SbE")
           ("S")("SbW")("SSW")("SWbS")("SW")("SWbW")("WSW")("WbS")
           ("W")("WbN")("WNW")("NWbW")("NW")("NWbN")("NNW")("NbW"));
   return points[i-1];

}

string Build_Name_From_Abbreviation(string a) {

   string retval;
   for (int i = 0; i < a.size(); ++i){
       if ((1 == i) && (a[i] != 'b') && (a.size() == 3)) retval += "-";
       switch (a[i]){
           case 'N' : retval += "north"; break; 
           case 'S' : retval += "south"; break; 
           case 'E' : retval += "east";  break; 
           case 'W' : retval += "west";  break; 
           case 'b' : retval += " by ";  break;
       }
   }
   retval[0] = toupper(retval[0]);
   return retval;

}

int main() {

   boost::array<float,33> headings(list_of
           (0.0)(16.87)(16.88)(33.75)(50.62)(50.63)(67.5)(84.37)(84.38)(101.25)
           (118.12)(118.13)(135.0)(151.87)(151.88)(168.75)(185.62)(185.63)(202.5)
           (219.37)(219.38)(236.25)(253.12)(253.13)(270.0)(286.87)(286.88)(303.75)
           (320.62)(320.63)(337.5)(354.37)(354.38));
   int i;
   boost::format f("%1$4d %2$-20s %3$_7.2f");
   BOOST_FOREACH(float a, headings)
   {
       i = get_Index(a);
       std::cout << f % i %  Build_Name_From_Abbreviation(get_Abbr_From_Index(i)) % a << std::endl;
   }
   return 0;

}</lang> Output:

   1 North                   0.00
   2 North by east          16.87
   3 North-northeast        16.88
   4 Northeast by north     33.75
   5 Northeast              50.62
   6 Northeast by east      50.63
   7 East-northeast         67.50
   8 East by north          84.37
   9 East                   84.38
  10 East by south         101.25
  11 East-southeast        118.12
  12 Southeast by east     118.13
  13 Southeast             135.00
  14 Southeast by south    151.87
  15 South-southeast       151.88
  16 South by east         168.75
  17 South                 185.62
  18 South by west         185.63
  19 South-southwest       202.50
  20 Southwest by south    219.37
  21 Southwest             219.38
  22 Southwest by west     236.25
  23 West-southwest        253.12
  24 West by south         253.13
  25 West                  270.00
  26 West by north         286.87
  27 West-northwest        286.88
  28 Northwest by west     303.75
  29 Northwest             320.62
  30 Northwest by north    320.63
  31 North-northwest       337.50
  32 North by west         354.37
   1 North                 354.38

Clojure

Translation of: Tcl

<lang lisp>(ns boxing-the-compass

 (:use [clojure.string :only [capitalize]]))

(def headings

    (for [i (range 0 (inc 32))]
      (let [heading (* i 11.25)]

(case (mod i 3) 1 (+ heading 5.62) 2 (- heading 5.62) heading))))

(defn angle2compass

 [angle]
 (let [dirs ["N" "NbE" "N-NE" "NEbN" "NE" "NEbE" "E-NE" "EbN"

"E" "EbS" "E-SE" "SEbE" "SE" "SEbS" "S-SE" "SbE" "S" "SbW" "S-SW" "SWbS" "SW" "SWbW" "W-SW" "WbS" "W" "WbN" "W-NW" "NWbW" "NW" "NWbN" "N-NW" "NbW"] unpack {\N "north" \E "east" \W "west" \S "south" \b " by " \- "-"} sep (/ 360 (count dirs)) dir (int (/ (mod (+ angle (/ sep 2)) 360) sep))]

   (capitalize (apply str (map unpack (dirs dir))))))

(print

(apply str (map-indexed #(format "%2s %-18s %7.2f\n"

(inc (mod %1 32)) (angle2compass %2) %2) headings)))</lang> Output:

 1 North                 0.00
 2 North by east        16.87
 3 North-northeast      16.88
 4 Northeast by north   33.75
 5 Northeast            50.62
 6 Northeast by east    50.63
 7 East-northeast       67.50
 8 East by north        84.37
 9 East                 84.38
10 East by south       101.25
11 East-southeast      118.12
12 Southeast by east   118.13
13 Southeast           135.00
14 Southeast by south  151.87
15 South-southeast     151.88
16 South by east       168.75
17 South               185.62
18 South by west       185.63
19 South-southwest     202.50
20 Southwest by south  219.37
21 Southwest           219.38
22 Southwest by west   236.25
23 West-southwest      253.12
24 West by south       253.13
25 West                270.00
26 West by north       286.87
27 West-northwest      286.88
28 Northwest by west   303.75
29 Northwest           320.62
30 Northwest by north  320.63
31 North-northwest     337.50
32 North by west       354.37
 1 North               354.38

D

Translation of: Java

<lang d>import std.stdio, std.string, std.math, std.array;

struct boxTheCompass {

   /*immutable*/ static string[32] points;
   /*pure nothrow*/ static this() {
       enum cardinal = ["north", "east", "south", "west"];
       enum desc = ["1", "1 by 2", "1-C", "C by 1", "C", "C by 2",
                    "2-C", "2 by 1"];
       foreach (i; 0 .. 4) {
           immutable s1 = cardinal[i];
           immutable s2 = cardinal[(i + 1) % 4];
           immutable sc = (s1 == "north" || s1 == "south") ?
                          (s1 ~ s2) : (s2 ~ s1);
           foreach (j; 0 .. 8)
               points[i * 8 + j] = desc[j].replace("1", s1).
                                   replace("2", s2).replace("C",sc);
       }
   }
   static string opCall(in double degrees) /*pure nothrow*/ {
       immutable testD = (degrees / 11.25) + 0.5;
       return capitalize(points[cast(int)floor(testD % 32)]);
   }

}

void main() {

   foreach (i; 0 .. 33) {
       immutable heading = i * 11.25 + [0, 5.62, -5.62][i % 3];
       writefln("%s\t%18s\t%s", i % 32 + 1,
                boxTheCompass(heading), heading);
   }

}</lang> Output:

1                North  0
2        North by east  16.87
3      North-northeast  16.88
4   Northeast by north  33.75
5            Northeast  50.62
6    Northeast by east  50.63
7       East-northeast  67.5
8        East by north  84.37
9                 East  84.38
10       East by south  101.25
11      East-southeast  118.12
12   Southeast by east  118.13
13           Southeast  135
14  Southeast by south  151.87
15     South-southeast  151.88
16       South by east  168.75
17               South  185.62
18       South by west  185.63
19     South-southwest  202.5
20  Southwest by south  219.37
21           Southwest  219.38
22   Southwest by west  236.25
23      West-southwest  253.12
24       West by south  253.13
25                West  270
26       West by north  286.87
27      West-northwest  286.88
28   Northwest by west  303.75
29           Northwest  320.62
30  Northwest by north  320.63
31     North-northwest  337.5
32       North by west  354.37
1                North  354.38

Euphoria

<lang euphoria>constant names = {"North","North by east","North-northeast","Northeast by north",

   "Northeast","Northeast by east","East-northeast","East by north","East",
   "East by south","East-southeast","Southeast by east","Southeast","Southeast by south",
   "South-southeast","South by east","South","South by west","South-southwest",
   "Southwest by south","Southwest","Southwest by west","West-southwest",
   "West by south","West","West by north","West-northwest","Northwest by west",
   "Northwest","Northwest by north","North-northwest","North by west"}

function deg2ind(atom degree)

   return remainder(floor(degree*32/360+.5),32)+1

end function

sequence degrees degrees = {} for i = 0 to 32 do

   degrees &= i*11.25 + 5.62*(remainder(i+1,3)-1)

end for

integer j for i = 1 to length(degrees) do

   j = deg2ind(degrees[i])
   printf(1, "%6.2f  %2d  %-22s\n", {degrees[i], j, names[j]})

end for</lang>

Output:

  0.00   1  North
 16.87   2  North by east
 16.88   3  North-northeast
 33.75   4  Northeast by north
 50.62   5  Northeast
 50.63   6  Northeast by east
 67.50   7  East-northeast
 84.37   8  East by north
 84.38   9  East
101.25  10  East by south
118.12  11  East-southeast
118.13  12  Southeast by east
135.00  13  Southeast
151.87  14  Southeast by south
151.88  15  South-southeast
168.75  16  South by east
185.62  17  South
185.63  18  South by west
202.50  19  South-southwest
219.37  20  Southwest by south
219.38  21  Southwest
236.25  22  Southwest by west
253.12  23  West-southwest
253.13  24  West by south
270.00  25  West
286.87  26  West by north
286.88  27  West-northwest
303.75  28  Northwest by west
320.62  29  Northwest
320.63  30  Northwest by north
337.50  31  North-northwest
354.37  32  North by west
354.38   1  North

Fortran

Works with: Fortran version 90 and later

<lang fortran>Program Compass

 implicit none
 integer :: i, ind
 real :: heading
 do i = 0, 32
   heading = i * 11.25
   if (mod(i, 3) == 1) then
     heading = heading + 5.62
   else if (mod(i, 3) == 2) then
           heading = heading - 5.62
   end if
   ind = mod(i, 32) + 1
   write(*, "(i2, a20, f8.2)") ind, compasspoint(heading), heading
 end do

contains

function compasspoint(h)

 character(18) :: compasspoint
 character(18) :: points(32) = (/ "North             ", "North by east     ", "North-northeast   ", & 
            "Northeast by north", "Northeast         ", "Northeast by east ", "East-northeast    ", &
            "East by north     ", "East              ", "East by south     ", "East-southeast    ", &
            "Southeast by east ", "Southeast         ", "Southeast by south", "South-southeast   ", &
            "South by east     ", "South             ", "South by west     ", "South-southwest   ", &
            "Southwest by south", "Southwest         ", "Southwest by west ", "West-southwest    ", &
            "West by south     ", "West              ", "West by north     ", "West-northwest    ", &
            "Northwest by west ", "Northwest         ", "Northwest by north", "North-northwest   ", &
            "North by west     "  /)  
 real, intent(in) :: h
 real :: x
 x = h / 11.25 + 1.5
 if (x >= 33.0) x = x - 32.0
 compasspoint = points(int(x))

end function compasspoint end program Compass</lang> Output:

 1  North                 0.00
 2  North by east        16.87
 3  North-northeast      16.88
 4  Northeast by north   33.75
 5  Northeast            50.62
 6  Northeast by east    50.63
 7  East-northeast       67.50
 8  East by north        84.37
 9  East                 84.38
10  East by south       101.25
11  East-southeast      118.12
12  Southeast by east   118.13
13  Southeast           135.00
14  Southeast by south  151.87
15  South-southeast     151.88
16  South by east       168.75
17  South               185.62
18  South by west       185.63
19  South-southwest     202.50
20  Southwest by south  219.37
21  Southwest           219.38
22  Southwest by west   236.25
23  West-southwest      253.12
24  West by south       253.13
25  West                270.00
26  West by north       286.87
27  West-northwest      286.88
28  Northwest by west   303.75
29  Northwest           320.62
30  Northwest by north  320.63
31  North-northwest     337.50
32  North by west       354.37
 1  North               354.38

Go

<lang go>package main

import "fmt"

// function required by task func degrees2compasspoint(h float32) string {

   return compassPoint[cpx(h)]

}

// cpx returns integer index from 0 to 31 corresponding to compass point. // input heading h is in degrees. Note this index is a zero-based index // suitable for indexing into the table of printable compass points, // and is not the same as the index specified to be printed in the output. func cpx(h float32) int {

   x := int(h/11.25+.5) % 32
   if x < 0 {
       x += 32
   }
   return x

}

// printable compass points var compassPoint = []string{

   "North",
   "North by east",
   "North-northeast",
   "Northeast by north",
   "Northeast",
   "Northeast by east",
   "East-northeast",
   "East by north",
   "East",
   "East by south",
   "East-southeast",
   "Southeast by east",
   "Southeast",
   "Southeast by south",
   "South-southeast",
   "South by east",
   "South",
   "South by west",
   "South-southwest",
   "Southwest by south",
   "Southwest",
   "Southwest by west",
   "West-southwest",
   "West by south",
   "West",
   "West by north",
   "West-northwest",
   "Northwest by west",
   "Northwest",
   "Northwest by north",
   "North-northwest",
   "North by west",

}

func main() {

   fmt.Println("Index  Compass point         Degree")
   for i, h := range []float32{0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5,
       84.37, 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75,
       185.62, 185.63, 202.5, 219.37, 219.38, 236.25, 253.12, 253.13, 270.0,
       286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38} {
       index := i%32 + 1 // printable index computed per pseudocode
       fmt.Printf("%4d   %-19s %7.2f°\n", index, degrees2compasspoint(h), h)
   }

}</lang>

Index  Compass point         Degree
   1   North                  0.00°
   2   North by east         16.87°
   3   North-northeast       16.88°
   4   Northeast by north    33.75°
   5   Northeast             50.62°
   6   Northeast by east     50.63°
   7   East-northeast        67.50°
   8   East by north         84.37°
   9   East                  84.38°
  10   East by south        101.25°
  11   East-southeast       118.12°
  12   Southeast by east    118.13°
  13   Southeast            135.00°
  14   Southeast by south   151.87°
  15   South-southeast      151.88°
  16   South by east        168.75°
  17   South                185.62°
  18   South by west        185.63°
  19   South-southwest      202.50°
  20   Southwest by south   219.37°
  21   Southwest            219.38°
  22   Southwest by west    236.25°
  23   West-southwest       253.12°
  24   West by south        253.13°
  25   West                 270.00°
  26   West by north        286.87°
  27   West-northwest       286.88°
  28   Northwest by west    303.75°
  29   Northwest            320.62°
  30   Northwest by north   320.63°
  31   North-northwest      337.50°
  32   North by west        354.37°
   1   North                354.38°

Haskell

<lang haskell> import Data.Char import Data.Maybe import Text.Printf

dirs = ["N", "NbE", "N-NE", "NEbN", "NE", "NEbE", "E-NE", "EbN",

       "E", "EbS", "E-SE", "SEbE", "SE", "SEbS", "S-SE", "SbE", 
       "S", "SbW", "S-SW", "SWbS", "SW", "SWbW", "W-SW", "WbS", 
       "W", "WbN", "W-NW", "NWbW", "NW", "NWbN", "N-NW", "NbW"]

-- Given an index between 0 and 31 return the corresponding compass point name. pointName = capitalize . concatMap (fromMaybe "?" . fromChar) . (dirs !!)

 where fromChar c = lookup c [('N', "north"), ('S', "south"), ('E', "east"), 
                              ('W', "west"),  ('b', " by "),  ('-', "-")]
       capitalize (c:cs) = toUpper c : cs

-- Convert degrees to a compass point index between 0 and 31. pointIndex d = (round (d*1000) + 5625) `mod` 360000 `div` 11250

printPointName d = let deg = read d :: Double

                      idx = pointIndex deg
                  in printf "%2d  %-18s  %6.2f°\n" (idx+1) (pointName idx) deg

main = do

 input <- getContents
 mapM_ printPointName $ lines input

</lang> Output:

 1  North                 0.00°
 2  North by east        16.87°
 3  North-northeast      16.88°
 4  Northeast by north   33.75°
 5  Northeast            50.62°
 6  Northeast by east    50.63°
 7  East-northeast       67.50°
 8  East by north        84.37°
 9  East                 84.38°
10  East by south       101.25°
11  East-southeast      118.12°
12  Southeast by east   118.13°
13  Southeast           135.00°
14  Southeast by south  151.87°
15  South-southeast     151.88°
16  South by east       168.75°
17  South               185.62°
18  South by west       185.63°
19  South-southwest     202.50°
20  Southwest by south  219.37°
21  Southwest           219.38°
22  Southwest by west   236.25°
23  West-southwest      253.12°
24  West by south       253.13°
25  West                270.00°
26  West by north       286.87°
27  West-northwest      286.88°
28  Northwest by west   303.75°
29  Northwest           320.62°
30  Northwest by north  320.63°
31  North-northwest     337.50°
32  North by west       354.37°
 1  North               354.38°

Icon and Unicon

This example is incomplete. 354.38? Please ensure that it meets all task requirements and remove this message.

<lang Icon>link strings,numbers

procedure main()

every heading := 11.25 * (i := 0 to 32) do {

  case i%3 of {
     1: heading +:= 5.62
     2: heading -:= 5.62
     }
  write(right(i+1,3)," ",left(direction(heading),20)," ",fix(heading,,7,2))
  } 

end

procedure direction(d) # compass heading given +/- degrees static dirs initial {

  every put(dirs := [],
            replacem(!["N","NbE","N-NE","NEbN","NE","NEbE","E-NE","EbN",
                       "E","EbS","E-SE","SEbE","SE","SEbS","S-SE","SbE",

"S","SbW","S-SW","SWbS","SW","SWbW","W-SW","WbS", "W","WbN","W-NW","NWbW","NW","NWbN","N-NW","NbW"],

                      "N","north","E","east","W","west","S","south","b"," by "))   
  }

  return dirs[round(((((d%360)+360)%360)/11.25)%32 + 1)]

end</lang>

strings for replacem numbers for round, fix

Output:

  1 north                   0.00
  2 north by east          16.87
  3 north-northeast        16.88
  4 northeast by north     33.75
  5 northeast              50.62
  6 northeast by east      50.63
  7 east-northeast         67.50
  8 east by north          84.37
  9 east                   84.38
 10 east by south         101.25
 11 east-southeast        118.12
 12 southeast by east     118.13
 13 southeast             135.00
 14 southeast by south    151.87
 15 south-southeast       151.88
 16 south by east         168.75
 17 south                 185.62
 18 south by west         185.63
 19 south-southwest       202.50
 20 southwest by south    219.37
 21 southwest             219.38
 22 southwest by west     236.25
 23 west-southwest        253.12
 24 west by south         253.13
 25 west                  270.00
 26 west by north         286.87
 27 west-northwest        286.88
 28 northwest by west     303.75
 29 northwest             320.62
 30 northwest by north    320.63
 31 north-northwest       337.50
 32 north by west         354.37

J

<lang j>require'strings' subs=: 'N,north,S,south,E,east,W,west,b, by ,' dirs=: subs (toupper@{., }.)@rplc~L:1 0&(<;._2) 0 :0 -. ' ',LF

 N,NbE,N-NE,NEbN,NE,NEbE,E-NE,EbN,E,EbS,E-SE,SEbE,SE,SEbS,S-SE,SbE,
 S,SbW,S-SW,SWbS,SW,SWbW,W-SW,WbS,W,WbN,W-NW,NWbW,NW,NWbN,N-NW,NbW,

) indice=: 32 | 0.5 <.@+ %&11.25 deg2pnt=: dirs {~ indice</lang>

Example use:

<lang j> i.10 0 1 2 3 4 5 6 7 8 9

  deg2pnt i.10

┌─────┬─────┬─────┬─────┬─────┬─────┬─────────────┬─────────────┬─────────────┬─────────────┐ │North│North│North│North│North│North│North by east│North by east│North by east│North by east│ └─────┴─────┴─────┴─────┴─────┴─────┴─────────────┴─────────────┴─────────────┴─────────────┘</lang>

Required example:

<lang j> (":@>:@indice,.' ',.>@deg2pnt,.' ',.":@,.)(*&11.25 + 5.62 * 0 1 _1 {~ 3&|) i.33 1 North 0 2 North by east 16.87 3 North-northeast 16.88 4 Northeast by north 33.75 5 Northeast 50.62 6 Northeast by east 50.63 7 East-northeast 67.5 8 East by north 84.37 9 East 84.38 10 East by south 101.25 11 East-southeast 118.12 12 Southeast by east 118.13 13 Southeast 135 14 Southeast by south 151.87 15 South-southeast 151.88 16 South by east 168.75 17 South 185.62 18 South by west 185.63 19 South-southwest 202.5 20 Southwest by south 219.37 21 Southwest 219.38 22 Southwest by west 236.25 23 West-southwest 253.12 24 West by south 253.13 25 West 270 26 West by north 286.87 27 West-northwest 286.88 28 Northwest by west 303.75 29 Northwest 320.62 30 Northwest by north 320.63 31 North-northwest 337.5 32 North by west 354.37 1 North 354.38</lang>

Java

Translation of: Visual Basic .NET

<lang java>public class BoxingTheCompass{

   private static String[] points = new String[32];

   public static void main(String[] args){
       buildPoints();

       double heading = 0;

       for(int i = 0; i<= 32;i++){
           heading = i * 11.25;
           switch(i % 3){
               case 1:
                   heading += 5.62;
                   break;
               case 2:
                   heading -= 5.62;
                   break;
               default:
           }

           System.out.printf("%s\t%18s\t%s°\n",(i % 32) + 1, initialUpper(getPoint(heading)), heading);
       }
   }

   private static void buildPoints(){
       String[] cardinal = {"north", "east", "south", "west"};
       String[] pointDesc = {"1", "1 by 2", "1-C", "C by 1", "C", "C by 2", "2-C", "2 by 1"};

       String str1, str2, strC;

       for(int i = 0;i <= 3;i++){
           str1 = cardinal[i];
           str2 = cardinal[(i + 1) % 4];
           strC = (str1.equals("north") || str1.equals("south")) ? (str1 + str2): (str2 + str1);
           for(int j = 0;j <= 7;j++){
               points[i * 8 + j] = pointDesc[j].replace("1", str1).replace("2", str2).replace("C", strC);
           }
       }
   }

   private static String initialUpper(String s){
       return s.substring(0, 1).toUpperCase() + s.substring(1);
   }

   private static String getPoint(double degrees){
       double testD = (degrees / 11.25) + 0.5;
       return points[(int)Math.floor(testD % 32)];
   }

}</lang> Output:

1	             North	0.0°
2	     North by east	16.87°
3	   North-northeast	16.88°
4	Northeast by north	33.75°
5	         Northeast	50.62°
6	 Northeast by east	50.63°
7	    East-northeast	67.5°
8	     East by north	84.37°
9	              East	84.38°
10	     East by south	101.25°
11	    East-southeast	118.12°
12	 Southeast by east	118.13°
13	         Southeast	135.0°
14	Southeast by south	151.87°
15	   South-southeast	151.88°
16	     South by east	168.75°
17	             South	185.62°
18	     South by west	185.63°
19	   South-southwest	202.5°
20	Southwest by south	219.37°
21	         Southwest	219.38°
22	 Southwest by west	236.25°
23	    West-southwest	253.12°
24	     West by south	253.13°
25	              West	270.0°
26	     West by north	286.87°
27	    West-northwest	286.88°
28	 Northwest by west	303.75°
29	         Northwest	320.62°
30	Northwest by north	320.63°
31	   North-northwest	337.5°
32	     North by west	354.37°
1	             North	354.38°

Liberty BASIC

<lang lb>dim point$( 32)

for i =1 to 32

   read d$: point$( i) =d$

next i

for i = 0 to 32

   heading = i *11.25
   if ( i mod 3) =1 then
       heading = heading +5.62
   else
       if ( i mod 3) =2 then heading = heading -5.62
   end if
   ind = i mod 32 +1
   print ind, compasspoint$( heading), heading

next i

end

function compasspoint$( h)

   x = h /11.25 +1.5
   if (x >=33.0) then x =x -32.0
   compasspoint$ = point$( int( x))

end function

data "North ", "North by east ", "North-northeast " data "Northeast by north", "Northeast ", "Northeast by east ", "East-northeast " data "East by north ", "East ", "East by south ", "East-southeast " data "Southeast by east ", "Southeast ", "Southeast by south", "South-southeast " data "South by east ", "South ", "South by west ", "South-southwest " data "Southwest by south", "Southwest ", "Southwest by west ", "West-southwest " data "West by south ", "West ", "West by north ", "West-northwest " data "Northwest by west ", "Northwest ", "Northwest by north", "North-northwest " data "North by west</lang>

Output:

1             North                       0
2             North by east               16.87
3             North-northeast             16.88
4             Northeast by north          33.75
5             Northeast                   50.62
6             Northeast by east           50.63
7             East-northeast              67.5
8             East by north               84.37
9             East                        84.38
10            East by south               101.25
11            East-southeast              118.12
12            Southeast by east           118.13
13            Southeast                   135
14            Southeast by south          151.87
15            South-southeast             151.88
16            South by east               168.75
17            South                       185.62
18            South by west               185.63
19            South-southwest             202.5
20            Southwest by south          219.37
21            Southwest                   219.38
22            Southwest by west           236.25
23            West-southwest              253.12
24            West by south               253.13
25            West                        270
26            West by north               286.87
27            West-northwest              286.88
28            Northwest by west           303.75
29            Northwest                   320.62
30            Northwest by north          320.63
31            North-northwest             337.5
32            North by west               354.37
1             North                       354.38

K

The representation of the names was inspired by Tcl (etc.).

<lang K> d:("N;Nbe;N-ne;Nebn;Ne;Nebe;E-ne;Ebn;")

  d,:("E;Ebs;E-se;Sebe;Se;Sebs;S-se;Sbe;")
  d,:("S;Sbw;S-sw;Swbs;Sw;Swbw;W-sw;Wbs;")
  d,:("W;Wbn;W-nw;Nwbw;Nw;Nwbn;N-nw;Nbw;N")
  split:{1_'(&x=y)_ x:y,x}
  dd:split[d;";"]
  / lookup table
  s1:"NEWSnewsb-"
  s2:("North";"East";"West";"South";"north";"east";"west";"south";" by ";"-")
  c:.({`$x}'s1),'{`$x}'s2   / create the dictionary
  cc:{,/{$c[`$$x]}'x}       / lookup function
  / calculate the degrees
  f:{m:x!3;(11.25*x)+:[1=m;+5.62;2=m;-5.62;0]}</lang>
 

The table: <lang K> `0:{((2$(1+x!32))," ",(-19$cc@dd[x]),(6.2$f@x))}'!#dd

1  North                0.00
2  North by east       16.87
3  North-northeast     16.88
4  Northeast by north  33.75
5  Northeast           50.62
6  Northeast by east   50.63
7  East-northeast      67.50
8  East by north       84.37
9  East                84.38

10 East by south 101.25 11 East-southeast 118.12 12 Southeast by east 118.13 13 Southeast 135.00 14 Southeast by south 151.87 15 South-southeast 151.88 16 South by east 168.75 17 South 185.62 18 South by west 185.63 19 South-southwest 202.50 20 Southwest by south 219.37 21 Southwest 219.38 22 Southwest by west 236.25 23 West-southwest 253.12 24 West by south 253.13 25 West 270.00 26 West by north 286.87 27 West-northwest 286.88 28 Northwest by west 303.75 29 Northwest 320.62 30 Northwest by north 320.63 31 North-northwest 337.50 32 North by west 354.37

1  North              354.38</lang>

<lang logo>; List of abbreviated compass point labels make "compass_points [ N NbE N-NE NEbN NE NEbE E-NE EbN

                      E EbS E-SE SEbE SE SEbS S-SE SbE
                      S SbW S-SW SWbS SW SWbW W-SW WbS
                      W WbN W-NW NWbW NW NWbN N-NW NbW ]
List of angles to test

make "test_angles [ 0.00 16.87 16.88 33.75 50.62 50.63 67.50

                   84.37  84.38 101.25 118.12 118.13 135.00 151.87
                  151.88 168.75 185.62 185.63 202.50 219.37 219.38
                  236.25 253.12 253.13 270.00 286.87 286.88 303.75
                  320.62 320.63 337.50 354.37 354.38 ]
make comparisons case-sensitive

make "caseignoredp "false

String utilities
search and replace

to replace_in :src :from :to

 output map [ ifelse equalp ? :from [:to] [?] ] :src

end

pad with spaces

to pad :string :length

 output cascade [lessp :length count ?] [word ? "\ ] :string

end

capitalize first letter

to capitalize :string

 output word (uppercase first :string) butfirst :string

end

convert compass point abbreviation to full text of label

to expand_point :abbr

 foreach [[N north] [E east] [S south] [W west] [b \ by\ ]] [
   make "abbr replace_in :abbr (first ?) (last ?)
 ]
 output capitalize :abbr

end

modulus function that returns 1..N instead of 0..N-1

to adjusted_modulo :n :d

 output sum 1 modulo (difference :n 1) :d

end

convert a compass angle from degrees into a box index (1..32)

to compass_point :degrees

 make "degrees modulo :degrees 360
 output adjusted_modulo (sum 1 int quotient (sum :degrees 5.625) 11.25) 32

end

Now output the table of test data

print (sentence (pad "Degrees 7) "\| (pad "Closest\ Point 18) "\| "Index ) foreach :test_angles [

 local "index
 make "index compass_point ?
 local "abbr
 make "abbr item :index :compass_points
 local "label
 make "label expand_point :abbr
 print (sentence (form ? 7 2) "\| (pad :label 18) "\| (form :index 2 0) )

]

and exit

bye </lang>

Output:

Degrees | Closest Point      | Index
   0.00 | North              |  1
  16.87 | North by east      |  2
  16.88 | North-northeast    |  3
  33.75 | Northeast by north |  4
  50.62 | Northeast          |  5
  50.63 | Northeast by east  |  6
  67.50 | East-northeast     |  7
  84.37 | East by north      |  8
  84.38 | East               |  9
 101.25 | East by south      | 10
 118.12 | East-southeast     | 11
 118.13 | Southeast by east  | 12
 135.00 | Southeast          | 13
 151.87 | Southeast by south | 14
 151.88 | South-southeast    | 15
 168.75 | South by east      | 16
 185.62 | South              | 17
 185.63 | South by west      | 18
 202.50 | South-southwest    | 19
 219.37 | Southwest by south | 20
 219.38 | Southwest          | 21
 236.25 | Southwest by west  | 22
 253.12 | West-southwest     | 23
 253.13 | West by south      | 24
 270.00 | West               | 25
 286.87 | West by north      | 26
 286.88 | West-northwest     | 27
 303.75 | Northwest by west  | 28
 320.62 | Northwest          | 29
 320.63 | Northwest by north | 30
 337.50 | North-northwest    | 31
 354.37 | North by west      | 32
 354.38 | North              |  1

Lua

Translation of: Logo

<lang lua>-- List of abbreviated compass point labels compass_points = { "N", "NbE", "N-NE", "NEbN", "NE", "NEbE", "E-NE", "EbN",

                  "E", "EbS", "E-SE", "SEbE", "SE", "SEbS", "S-SE", "SbE",
                  "S", "SbW", "S-SW", "SWbS", "SW", "SWbW", "W-SW", "WbS",
                  "W", "WbN", "W-NW", "NWbW", "NW", "NWbN", "N-NW", "NbW" }

-- List of angles to test test_angles = { 0.00, 16.87, 16.88, 33.75, 50.62, 50.63, 67.50,

               84.37,  84.38, 101.25, 118.12, 118.13, 135.00, 151.87,
              151.88, 168.75, 185.62, 185.63, 202.50, 219.37, 219.38,
              236.25, 253.12, 253.13, 270.00, 286.87, 286.88, 303.75,
              320.62, 320.63, 337.50, 354.37, 354.38 }


-- capitalize a string function capitalize(s)

 return s:sub(1,1):upper() .. s:sub(2)

end

-- convert compass point abbreviation to full text of label function expand_point(abbr)

 for from, to in pairs( { N="north", E="east", S="south", W="west",
                            b=" by " }) do
   abbr = abbr:gsub(from, to)
 end
 return capitalize(abbr)

end

-- modulus function that returns 1..N instead of 0..N-1 function adjusted_modulo(n, d)

 return 1 + (n - 1) % d

end

-- convert a compass angle from degrees into a box index (1..32) function compass_point(degrees)

 degrees = degrees % 360
 return adjusted_modulo(1 + math.floor( (degrees+5.625) / 11.25), 32)

end

-- Now output the table of test data header_format = "%-7s | %-18s | %s" row_format = "%7.2f | %-18s | %2d" print(header_format:format("Degrees", "Closest Point", "Index")) for i, angle in ipairs(test_angles) do

 index = compass_point(angle)
 abbr  = compass_points[index]
 label  = expand_point(abbr)
 print(row_format:format(angle, label, index))

end</lang>

Output:

Degrees | Closest Point      | Index
   0.00 | North              |  1
  16.87 | North by east      |  2
  16.88 | North-northeast    |  3
  33.75 | Northeast by north |  4
  50.62 | Northeast          |  5
  50.63 | Northeast by east  |  6
  67.50 | East-northeast     |  7
  84.37 | East by north      |  8
  84.38 | East               |  9
 101.25 | East by south      | 10
 118.12 | East-southeast     | 11
 118.13 | Southeast by east  | 12
 135.00 | Southeast          | 13
 151.87 | Southeast by south | 14
 151.88 | South-southeast    | 15
 168.75 | South by east      | 16
 185.62 | South              | 17
 185.63 | South by west      | 18
 202.50 | South-southwest    | 19
 219.37 | Southwest by south | 20
 219.38 | Southwest          | 21
 236.25 | Southwest by west  | 22
 253.12 | West-southwest     | 23
 253.13 | West by south      | 24
 270.00 | West               | 25
 286.87 | West by north      | 26
 286.88 | West-northwest     | 27
 303.75 | Northwest by west  | 28
 320.62 | Northwest          | 29
 320.63 | Northwest by north | 30
 337.50 | North-northwest    | 31
 354.37 | North by west      | 32
 354.38 | North              |  1

Mathematica

<lang Mathematica>Map[List[Part[#,1], dirs[[Part[#,1]]], ToString@Part[#,2]<>"°"]&,

 Map[{Floor[Mod[ #+5.625 , 360]/11.25]+1,#}&,input] ]//TableForm</lang>
1	North			0.°
2	North by east		16.87°
3	North-northeast		16.88°
4	Northeast by north	33.75°
5	Northeast		50.62°
6	Northeast by east	50.63°
7	East-northeast		67.5°
8	East by north		84.37°
9	East			84.38°
10	East by Southeast	101.25°
11	East-southeast		118.12°
12	Southeast by east	118.13°
13	Southeast		135.°
14	Southeast by south	151.87°
15	South-southeast		151.88°
16	South by east		168.75°
17	South			185.62°
18	South by West		185.63°
19	South-southwest		202.5°
20	Southwest by south	219.37°
21	Southwest		219.38°
22	Southwest by west	236.25°
23	West-southwest		253.12°
24	West by south		253.13°
25	West			270.°
26	West by north		286.87°
27	West-northwest		286.88°
28	Northwest by west	303.75°
29	Northwest		320.62°
30	Northwest by north	320.63°
31	North-northwest		337.5°
32	North by west		354.37°
1	North			354.38°

MATLAB / Octave

<lang MATLAB>function b = compassbox(d)

   b = ceil(mod(d+360/64,360)*32/360); 

end; </lang> Output:

>> x=[0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5, 84.37, 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75, 185.62, 185.63, 202.5, 219.37, 219.38, 236.25, 253.12, 253.13, 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38]';
printf(' angle : box\n'); printf('%6.2f : %2i\n',[x,compassbox(x)]');
 angle : box
  0.00 :  1
 16.87 :  2
 16.88 :  3
 33.75 :  4
 50.62 :  5
 50.63 :  6
 67.50 :  7
 84.37 :  8
 84.38 :  9
101.25 : 10
118.12 : 11
118.13 : 12
135.00 : 13
151.87 : 14
151.88 : 15
168.75 : 16
185.62 : 17
185.63 : 18
202.50 : 19
219.37 : 20
219.38 : 21
236.25 : 22
253.12 : 23
253.13 : 24
270.00 : 25
286.87 : 26
286.88 : 27
303.75 : 28
320.62 : 29
320.63 : 30
337.50 : 31
354.37 : 32
354.38 :  1

MUMPS

The TCL implementation was the starting point, but this isn't an exact translation. <lang MUMPS>BOXING(DEGREE)

;This takes in a degree heading, nominally from 0 to 360, and returns the compass point name.
QUIT:((DEGREE<0)||(DEGREE>360)) "land lubber can't read a compass"
NEW DIRS,UNP,UNPACK,SEP,DIR,DOS,D,DS,I,F
SET DIRS="N^NbE^N-NE^NEbN^NE^NEbE^E-NE^EbN^E^EbS^E-SE^SEbE^SE^SEbS^S-SE^SbE^"
SET DIRS=DIRS_"S^SbW^S-SW^SWbS^SW^SWbW^W-SW^WbS^W^WbN^W-NW^NWbW^NW^NWbN^N-NW^NbW"
SET UNP="NESWb"
SET UNPACK="north^east^south^west^ by "
SET SEP=360/$LENGTH(DIRS,"^")
SET DIR=(DEGREE/SEP)+1.5
SET DIR=$SELECT((DIR>33):DIR-32,1:DIR)
SET DOS=$NUMBER(DIR-.5,0)
SET D=$PIECE(DIRS,"^",DIR)
SET DS=""
FOR I=1:1:$LENGTH(D) DO
. SET F=$FIND(UNP,$EXTRACT(D,I)) SET DS=DS_$SELECT((F>0):$PIECE(UNPACK,"^",F-1),1:$E(D,I))
KILL DIRS,UNP,UNPACK,SEP,DIR,D,I,F
QUIT DOS_"^"_DS

BOXWRITE

NEW POINTS,UP,LO,DIR,P,X
SET POINTS="0.0,16.87,16.88,33.75,50.62,50.63,67.5,84.37,84.38,101.25,118.12,118.13,135.0,151.87,"
SET POINTS=POINTS_"151.88,168.75,185.62,185.63,202.5,219.37,219.38,236.25,253.12,253.13,270.0,286.87,"
SET POINTS=POINTS_"286.88,303.75,320.62,320.63,337.5,354.37,354.38"
SET UP="ABCDEFGHIJKLMNOPQRSTUVWXYZ"
SET LO="abcdefghijklmnopqrstuvwxyz"
FOR P=1:1:$LENGTH(POINTS,",") DO
. SET X=$$BOXING($PIECE(POINTS,",",P))
. ;Capitalize the initial letter of the direction
. SET DIR=$PIECE(X,"^",2)
. SET DIR=$TRANSLATE($EXTRACT(DIR,1),LO,UP)_$EXTRACT(DIR,2,$LENGTH(DIR))
. WRITE $PIECE(X,"^"),?5,DIR,?40,$JUSTIFY($PIECE(POINTS,",",P),10,2),!
KILL POINTS,UP,LO,DIR,P,X
QUIT</lang>

Output:

Debugger executing 'BOXWRITE^COMPASS'
1    North                                    0.00
2    North by east                           16.87
3    North-northeast                         16.88
4    Northeast by north                      33.75
5    Northeast                               50.62
6    Northeast by east                       50.63
7    East-northeast                          67.50
8    East by north                           84.37
9    East                                    84.38
10   East by south                          101.25
11   East-southeast                         118.12
12   Southeast by east                      118.13
13   Southeast                              135.00
14   Southeast by south                     151.87
15   South-southeast                        151.88
16   South by east                          168.75
17   South                                  185.62
18   South by west                          185.63
19   South-southwest                        202.50
20   Southwest by south                     219.37
21   Southwest                              219.38
22   Southwest by west                      236.25
23   West-southwest                         253.12
24   West by south                          253.13
25   West                                   270.00
26   West by north                          286.87
27   West-northwest                         286.88
28   Northwest by west                      303.75
29   Northwest                              320.62
30   Northwest by north                     320.63
31   North-northwest                        337.50
32   North by west                          354.37
1    North                                  354.38

NetRexx

<lang NetRexx>/* NetRexx */ options replace format comments java crossref savelog symbols nobinary utf8

class RCBoxTheCompass

properties public constant

 _FULL = '_FULL'

properties indirect

 headings = Rexx
 rosepoints = Rexx

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method RCBoxTheCompass() public

 setHeadings(makeHeadings)
 setRosepoints(makeRosepoints)
 return

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method main(args = String[]) public static

 box = RCBoxTheCompass()
 cp = box.getCompassPoints
 loop r_ = 1 to cp[0]
   say cp[r_]
   end r_
 say
 hx = box.getHeadingsReport(box.getHeadings)
 loop r_ = 1 to hx[0]
   say hx[r_]
   end r_
 say
 return

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method getDecimalAngle(degrees, minutes, seconds) public static returns Rexx

 degrees = degrees * 10 % 10
 minutes = minutes * 10 % 10
 angle = degrees + (minutes / 60 + (seconds / 60 / 60))
 return angle

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method getDegreesMinutesSeconds(angle) public static returns Rexx

 degrees = angle * 100 % 100
 minutes = ((angle - degrees) * 60) * 100 % 100
 seconds = ((((angle - degrees) * 60) - minutes) * 60) * 100 % 100
 return degrees minutes seconds

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method getHeadingsReport(bearings) public returns Rexx

 r_ = 0
 table = 
 r_ = r_ + 1; table[0] = r_; table[r_] = 'Idx' -
                                         'Abbr' -
                                         'Compass Point'.left(20) -
                                         'Degrees'.right(10)
 loop h_ = 1 to bearings[0]
   heading = bearings[h_]
   index = getRosepointIndex(heading)
   parse getRosepoint(index) p_abbrev p_full
   r_ = r_ + 1; table[0] = r_; table[r_] = index.right(3) -
                                           p_abbrev.left(4) -
                                           p_full.left(20) -
                                           heading.format(6, 3).right(10)
   end h_
 return table

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method getRosepointIndex(heading) public returns Rexx

 one_pt = 360 / 32
 hn = heading // 360
 hi = hn % one_pt
 if hn > hi * one_pt + one_pt / 2 then do
   hi = hi + 1 -- greater than max range for this point; bump to next point
   end
 idx = hi // 32 + 1 -- add one to get index into rosepoints indexed string
 return idx

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method getRosepoint(index) public returns Rexx

 rp = getRosepoints
 return rp[index] rp[index, _FULL]

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method makeRosepoints() private returns Rexx

 p_ = 0
 rp = 
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'N';    rp[p_, _FULL] = 'North'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NbE';  rp[p_, _FULL] = 'North by East'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NNE';  rp[p_, _FULL] = 'North-Northeast'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NEbn'; rp[p_, _FULL] = 'Northeast by North'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NE';   rp[p_, _FULL] = 'Northeast'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NEbE'; rp[p_, _FULL] = 'Northeast by East'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'ENE';  rp[p_, _FULL] = 'East-Northeast'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'EbN';  rp[p_, _FULL] = 'East by North'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'E';    rp[p_, _FULL] = 'East'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'EbS';  rp[p_, _FULL] = 'East by South'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'ESE';  rp[p_, _FULL] = 'East-Southeast'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SEbE'; rp[p_, _FULL] = 'Southeast by East'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SE';   rp[p_, _FULL] = 'Southeast'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SEbS'; rp[p_, _FULL] = 'Southeast by South'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SSE';  rp[p_, _FULL] = 'South-Southeast'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SbE';  rp[p_, _FULL] = 'South by East'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'S';    rp[p_, _FULL] = 'South'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SbW';  rp[p_, _FULL] = 'South by West'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SSW';  rp[p_, _FULL] = 'South-Southwest'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SWbS'; rp[p_, _FULL] = 'Southwest by South'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SW';   rp[p_, _FULL] = 'Southwest'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'SWbW'; rp[p_, _FULL] = 'Southwest by West'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'WSW';  rp[p_, _FULL] = 'Southwest'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'WbS';  rp[p_, _FULL] = 'West by South'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'W';    rp[p_, _FULL] = 'West'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'WbN';  rp[p_, _FULL] = 'West by North'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'WNW';  rp[p_, _FULL] = 'West-Northwest'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NWbW'; rp[p_, _FULL] = 'Northwest by West'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NW';   rp[p_, _FULL] = 'Northwest'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NWbN'; rp[p_, _FULL] = 'Northwest by North'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NNW';  rp[p_, _FULL] = 'North-Northwest'
 p_ = p_ + 1; rp[0] = p_; rp[p_] = 'NbW';  rp[p_, _FULL] = 'North by West'
 return rp

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method makeHeadings() private returns Rexx

 hdg = 
 hdg[0] = 0
 points = 32
 loop i_ = 0 to points
   heading = i_ * 360 / points
   select case i_ // 3
     when 1 then heading_h = heading + 5.62
     when 2 then heading_h = heading - 5.62
     otherwise   heading_h = heading
     end
   ix = hdg[0] + 1; hdg[0] = ix; hdg[ix] = heading_h
   end i_
 return hdg

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ method getCompassPoints() public returns Rexx

 r_ = 0
 table = 
 r_ = r_ + 1; table[0] = r_; table[r_] = 'Idx' -
                                         'Abbr' -
                                         'Compass Point'.left(20) -
                                         'Low (Deg.)'.right(10) -
                                         'Mid (Deg.)'.right(10) -
                                         'Hi (Deg.)'.right(10)
 -- one point of the compass is 360 / 32 (11.25) degrees
 -- using functions to calculate this just for fun
 one_pt = 360 / 32
 parse getDegreesMinutesSeconds(one_pt / 2) ad am as .
 points = 32
 loop h_ = 0 to points - 1
   heading = h_ * 360 / points
   hmin = heading - getDecimalAngle(ad, am, as)
   hmax = heading + getDecimalAngle(ad, am, as)
   if hmin < 0 then do
     hmin = hmin + 360
     end
   if hmax >= 360 then do
     hmax = hmax - 360
     end
   index = getRosepointIndex(heading)
   parse getRosepoint(index) p_abbrev p_full
   r_ = r_ + 1; table[0] = r_; table[r_] = index.right(3) -
                                           p_abbrev.left(4) -
                                           p_full.left(20) -
                                           hmin.format(6, 3).right(10) -
                                           heading.format(6, 3).right(10) -
                                           hmax.format(6, 3).right(10)
   end h_
 return table

</lang>

Output
Idx Abbr Compass Point        Low (Deg.) Mid (Deg.)  Hi (Deg.)
  1 N    North                   354.375      0.000      5.625
  2 NbE  North by East             5.625     11.250     16.875
  3 NNE  North-Northeast          16.875     22.500     28.125
  4 NEbn Northeast by North       28.125     33.750     39.375
  5 NE   Northeast                39.375     45.000     50.625
  6 NEbE Northeast by East        50.625     56.250     61.875
  7 ENE  East-Northeast           61.875     67.500     73.125
  8 EbN  East by North            73.125     78.750     84.375
  9 E    East                     84.375     90.000     95.625
 10 EbS  East by South            95.625    101.250    106.875
 11 ESE  East-Southeast          106.875    112.500    118.125
 12 SEbE Southeast by East       118.125    123.750    129.375
 13 SE   Southeast               129.375    135.000    140.625
 14 SEbS Southeast by South      140.625    146.250    151.875
 15 SSE  South-Southeast         151.875    157.500    163.125
 16 SbE  South by East           163.125    168.750    174.375
 17 S    South                   174.375    180.000    185.625
 18 SbW  South by West           185.625    191.250    196.875
 19 SSW  South-Southwest         196.875    202.500    208.125
 20 SWbS Southwest by South      208.125    213.750    219.375
 21 SW   Southwest               219.375    225.000    230.625
 22 SWbW Southwest by West       230.625    236.250    241.875
 23 WSW  Southwest               241.875    247.500    253.125
 24 WbS  West by South           253.125    258.750    264.375
 25 W    West                    264.375    270.000    275.625
 26 WbN  West by North           275.625    281.250    286.875
 27 WNW  West-Northwest          286.875    292.500    298.125
 28 NWbW Northwest by West       298.125    303.750    309.375
 29 NW   Northwest               309.375    315.000    320.625
 30 NWbN Northwest by North      320.625    326.250    331.875
 31 NNW  North-Northwest         331.875    337.500    343.125
 32 NbW  North by West           343.125    348.750    354.375

Idx Abbr Compass Point           Degrees
  1 N    North                     0.000
  2 NbE  North by East            16.870
  3 NNE  North-Northeast          16.880
  4 NEbn Northeast by North       33.750
  5 NE   Northeast                50.620
  6 NEbE Northeast by East        50.630
  7 ENE  East-Northeast           67.500
  8 EbN  East by North            84.370
  9 E    East                     84.380
 10 EbS  East by South           101.250
 11 ESE  East-Southeast          118.120
 12 SEbE Southeast by East       118.130
 13 SE   Southeast               135.000
 14 SEbS Southeast by South      151.870
 15 SSE  South-Southeast         151.880
 16 SbE  South by East           168.750
 17 S    South                   185.620
 18 SbW  South by West           185.630
 19 SSW  South-Southwest         202.500
 20 SWbS Southwest by South      219.370
 21 SW   Southwest               219.380
 22 SWbW Southwest by West       236.250
 23 WSW  Southwest               253.120
 24 WbS  West by South           253.130
 25 W    West                    270.000
 26 WbN  West by North           286.870
 27 WNW  West-Northwest          286.880
 28 NWbW Northwest by West       303.750
 29 NW   Northwest               320.620
 30 NWbN Northwest by North      320.630
 31 NNW  North-Northwest         337.500
 32 NbW  North by West           354.370
  1 N    North                   354.380

PARI/GP

<lang parigp>box(x)={["North","North by east","North-northeast","Northeast by north","Northeast", "Northeast by east","East-northeast","East by north","East","East by south","East-southeast", "Southeast by east","Southeast","Southeast by south","South-southeast","South by east","South", "South by west","South-southwest","Southwest by south","Southwest","Southwest by west","West-southwest", "West by south","West","West by north","West-northwest","Northwest by west","Northwest", "Northwest by north","North-northwest","North by west"][round(x*4/45)%32+1]}; for(i=0,32,print(i%32+1" "box(x=i*11.25+if(i%3==1,5.62,if(i%3==2,-5.62)))" "x))</lang>

Output:

1 North 0
2 North by east 16.8700000
3 North-northeast 16.8800000
4 Northeast by north 33.7500000
5 Northeast 50.6200000
6 Northeast by east 50.6300000
7 East-northeast 67.5000000
8 East by north 84.3700000
9 East 84.3800000
10 East by south 101.250000
11 East-southeast 118.120000
12 Southeast by east 118.130000
13 Southeast 135.000000
14 Southeast by south 151.870000
15 South-southeast 151.880000
16 South by east 168.750000
17 South 185.620000
18 South by west 185.630000
19 South-southwest 202.500000
20 Southwest by south 219.370000
21 Southwest 219.380000
22 Southwest by west 236.250000
23 West-southwest 253.120000
24 West by south 253.130000
25 West 270.000000
26 West by north 286.870000
27 West-northwest 286.880000
28 Northwest by west 303.750000
29 Northwest 320.620000
30 Northwest by north 320.630000
31 North-northwest 337.500000
32 North by west 354.370000
1 North 354.380000

Pascal

Translation of: Fortran

<lang pascal>program BoxTheCompass(output);

function compasspoint(angle: real): string;

 const
   points: array [1..32] of string = 
     ('North             ', 'North by east     ', 'North-northeast   ', 'Northeast by north', 
      'Northeast         ', 'Northeast by east ', 'East-northeast    ', 'East by north     ', 
      'East              ', 'East by south     ', 'East-southeast    ', 'Southeast by east ', 
      'Southeast         ', 'Southeast by south', 'South-southeast   ', 'South by east     ', 
      'South             ', 'South by west     ', 'South-southwest   ', 'Southwest by south', 
      'Southwest         ', 'Southwest by west ', 'West-southwest    ', 'West by south     ', 
      'West              ', 'West by north     ', 'West-northwest    ', 'Northwest by west ', 
      'Northwest         ', 'Northwest by north', 'North-northwest   ', 'North by west     '
     );
 var
   index: integer;
 begin
   index := round (angle / 11.25);
   index := index mod 32 + 1;
   compasspoint := points[index];
 end;
 

var

 i:       integer;
 heading: real;

begin

 for i := 0 to 32 do
 begin
   heading := i * 11.25;
   case (i mod 3) of
     1: heading := heading + 5.62;
     2: heading := heading - 5.62;
   end;
   writeln((i mod 32) + 1:2, ' ', compasspoint(heading), ' ', heading:8:4);
 end;

end.</lang> Output:

:> ./BoxTheCompass
 1 North                0.0000
 2 North by east       16.8700
 3 North-northeast     16.8800
 4 Northeast by north  33.7500
 5 Northeast           50.6200
 6 Northeast by east   50.6300
 7 East-northeast      67.5000
 8 East by north       84.3700
 9 East                84.3800
10 East by south      101.2500
11 East-southeast     118.1200
12 Southeast by east  118.1300
13 Southeast          135.0000
14 Southeast by south 151.8700
15 South-southeast    151.8800
16 South by east      168.7500
17 South              185.6200
18 South by west      185.6300
19 South-southwest    202.5000
20 Southwest by south 219.3700
21 Southwest          219.3800
22 Southwest by west  236.2500
23 West-southwest     253.1200
24 West by south      253.1300
25 West               270.0000
26 West by north      286.8700
27 West-northwest     286.8800
28 Northwest by west  303.7500
29 Northwest          320.6200
30 Northwest by north 320.6300
31 North-northwest    337.5000
32 North by west      354.3700
 1 North              354.3800

Perl

Don't waste brain cells calculating names, not worth the effort. Code is probably shorter, faster, and easier to read this way. <lang Perl>use utf8;

my @names = ( "North", "North by east", "North-northeast", "Northeast by north", "Northeast", "Northeast by east", "East-northeast", "East by north", "East", "East by south", "East-southeast", "Southeast by east", "Southeast", "Southeast by south", "South-southeast", "South by east", "South", "South by west", "South-southwest", "Southwest by south", "Southwest", "Southwest by west", "West-southwest", "West by south", "West", "West by north", "West-northwest", "Northwest by west", "Northwest", "Northwest by north", "North-northwest", "North by west", ); my @angles = (0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5, 84.37, 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75, 185.62, 185.63, 202.5, 219.37, 219.38, 236.25, 253.12, 253.13, 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38);

for (@angles) { my $i = int(($_ * 32 / 360) + .5) % 32; printf "%3d %18s %6.2f°\n", $i + 1, $names[$i], $_; }</lang>output<lang> 1 North 0.00°

 2      North by east  16.87°
 3    North-northeast  16.88°
 4 Northeast by north  33.75°
 5          Northeast  50.62°
 6  Northeast by east  50.63°
 7     East-northeast  67.50°
 8      East by north  84.37°
 9               East  84.38°
10      East by south 101.25°
11     East-southeast 118.12°
12  Southeast by east 118.13°
13          Southeast 135.00°
14 Southeast by south 151.87°
15    South-southeast 151.88°
16      South by east 168.75°
17              South 185.62°
18      South by west 185.63°
19    South-southwest 202.50°
20 Southwest by south 219.37°
21          Southwest 219.38°
22  Southwest by west 236.25°
23     West-southwest 253.12°
24      West by south 253.13°
25               West 270.00°
26      West by north 286.87°
27     West-northwest 286.88°
28  Northwest by west 303.75°
29          Northwest 320.62°
30 Northwest by north 320.63°
31    North-northwest 337.50°
32      North by west 354.37°
 1              North 354.38°</lang>

Perl 6

Translation of: Perl

<lang perl6>sub point (Int $index) {

   my $ix = $index % 32;
   if $ix +& 1
       { "&point(($ix + 1) +& 28) by &point(((2 - ($ix +& 2)) * 4) + $ix +& 24)" }
   elsif $ix +& 2
       { "&point(($ix + 2) +& 24)-&point(($ix +| 4) +& 28)" }
   elsif $ix +& 4
       { "&point(($ix + 8) +& 16)&point(($ix +| 8) +& 24)" }
   else
       { <north east south west>[$ix div 8]; }

}

sub test-angle ($ix) { $ix * 11.25 + (0, 5.62, -5.62)[ $ix % 3 ] } sub angle-to-point($𝜽) { floor $𝜽 / 360 * 32 + 0.5 }

for 0 .. 32 -> $ix {

   my $𝜽 = test-angle($ix);
   printf "  %2d %6.2f%s %s\n",
             $ix % 32 + 1,
                 $𝜽, '°',
                         ucfirst point angle-to-point $𝜽;

}</lang>

Output:

   1   0.00° North
   2  16.87° North by east
   3  16.88° North-northeast
   4  33.75° Northeast by north
   5  50.62° Northeast
   6  50.63° Northeast by east
   7  67.50° East-northeast
   8  84.37° East by north
   9  84.38° East
  10 101.25° East by south
  11 118.12° East-southeast
  12 118.13° Southeast by east
  13 135.00° Southeast
  14 151.87° Southeast by south
  15 151.88° South-southeast
  16 168.75° South by east
  17 185.62° South
  18 185.63° South by west
  19 202.50° South-southwest
  20 219.37° Southwest by south
  21 219.38° Southwest
  22 236.25° Southwest by west
  23 253.12° West-southwest
  24 253.13° West by south
  25 270.00° West
  26 286.87° West by north
  27 286.88° West-northwest
  28 303.75° Northwest by west
  29 320.62° Northwest
  30 320.63° Northwest by north
  31 337.50° North-northwest
  32 354.37° North by west
   1 354.38° North

PicoLisp

<lang PicoLisp>(scl 3)

(setq *Compass # Build lookup table

  (let H -16.875
     (mapcar
        '((Str)
           (cons
              (inc 'H 11.25)       # Heading in degrees
              (pack                # Compass point
                 (replace (chop Str)
                    "N" "north"
                    "E" "east"
                    "S" "south"
                    "W" "west"
                    "b" " by " ) ) ) )
        '("N" "NbE" "N-NE" "NEbN" "NE" "NEbE" "E-NE" "EbN"
           "E" "EbS" "E-SE" "SEbE" "SE" "SEbS" "S-SE" "SbE"
           "S" "SbW" "S-SW" "SWbS" "SW" "SWbW" "W-SW" "WbS"
           "W" "WbN" "W-NW" "NWbW" "NW" "NWbN" "N-NW" "NbW"
           "N" ) ) ) )

(de heading (Deg)

  (rank (% Deg 360.00) *Compass) )

(for I (range 0 32)

  (let H (* I 11.25)
     (case (% I 3)
        (1 (inc 'H 5.62))
        (2 (dec 'H 5.62)) )
     (tab (3 1 -18 8)
        (inc (% I 32))
        NIL
        (cdr (heading H))
        (round H 2) ) ) )</lang>

Output:

  1 north                 0.00
  2 north by east        16.87
  3 north-northeast      16.88
  4 northeast by north   33.75
  5 northeast            50.62
  6 northeast by east    50.63
  7 east-northeast       67.50
  8 east by north        84.37
  9 east                 84.38
 10 east by south       101.25
 11 east-southeast      118.12
 12 southeast by east   118.13
 13 southeast           135.00
 14 southeast by south  151.87
 15 south-southeast     151.88
 16 south by east       168.75
 17 south               185.62
 18 south by west       185.63
 19 south-southwest     202.50
 20 southwest by south  219.37
 21 southwest           219.38
 22 southwest by west   236.25
 23 west-southwest      253.12
 24 west by south       253.13
 25 west                270.00
 26 west by north       286.87
 27 west-northwest      286.88
 28 northwest by west   303.75
 29 northwest           320.62
 30 northwest by north  320.63
 31 north-northwest     337.50
 32 north by west       354.37
  1 north               354.38

PureBasic

<lang PureBasic>DataSection

 Data.s "N", "north", "E", "east", "W", "west", "S", "south", "b", " by "   ;abbreviations, expansions
 Data.s "N NbE N-NE NEbN NE NEbE E-NE EbN E EbS E-SE SEbE SE SEbS S-SE SbE" ;dirs
 Data.s "S SbW S-SW SWbS SW SWbW W-SW WbS W WbN W-NW NWbW NW NWbN N-NW NbW"

EndDataSection

initialize data

NewMap dirSubst.s() Define i, abbr.s, expansion.s For i = 1 To 5

 Read.s abbr
 Read.s expansion
 dirSubst(abbr) = expansion

Next

Dim dirs.s(32) Define j, s.s For j = 0 To 1

 Read.s s.s
 For i = 0 To 15
   abbr.s = StringField(s, i + 1, " ")
   dirs(j * 16 + i) = abbr
 Next

Next

expand abbreviated compass point and capitalize

Procedure.s abbr2compassPoint(abbr.s)

 Shared dirSubst()
 Protected i, compassPoint.s, key.s
 
 For i = 1 To Len(abbr)
   key.s = Mid(abbr, i, 1)
   If FindMapElement(dirSubst(), key)
     compassPoint + dirSubst(key)
   Else
     compassPoint + key
   EndIf
 Next
 ProcedureReturn UCase(Left(compassPoint, 1)) + Mid(compassPoint, 2)

EndProcedure

Procedure.s angle2compass(angle.f)

 Shared dirs()
 Static segment.f = 360.0 / 32 ;width of each compass segment
 Protected dir
 
 ;work out which segment contains the compass angle
 dir = Int((Mod(angle, 360) / segment) + 0.5)
 
 ;convert to a named direction
 ProcedureReturn abbr2compassPoint(dirs(dir))

EndProcedure

box the compass

If OpenConsole()

 Define i, heading.f, index 
 For i = 0 To 32
   heading = i * 11.25
   If i % 3 = 1
     heading + 5.62
   EndIf 
   If i % 3 = 2
     heading - 5.62
   EndIf 
   index = i % 32 + 1
   
   PrintN(RSet(Str(index), 2) + " " + LSet(angle2compass(heading), 18) + RSet(StrF(heading, 2), 7))
 Next 
 
 Print(#CRLF$ + #CRLF$ + "Press ENTER to exit"): Input()
 CloseConsole()

EndIf</lang> Sample output:

 1 North                0.00
 2 North by east       16.87
 3 North-northeast     16.88
 4 Northeast by north  33.75
 5 Northeast           50.62
 6 Northeast by east   50.63
 7 East-northeast      67.50
 8 East by north       84.37
 9 East                84.38
10 East by south      101.25
11 East-southeast     118.12
12 Southeast by east  118.13
13 Southeast          135.00
14 Southeast by south 151.87
15 South-southeast    151.88
16 South by east      168.75
17 South              185.62
18 South by west      185.63
19 South-southwest    202.50
20 Southwest by south 219.37
21 Southwest          219.38
22 Southwest by west  236.25
23 West-southwest     253.12
24 West by south      253.13
25 West               270.00
26 West by north      286.87
27 West-northwest     286.88
28 Northwest by west  303.75
29 Northwest          320.62
30 Northwest by north 320.63
31 North-northwest    337.50
32 North by west      354.37
 1                    354.38

Prolog

Part 1 : The following knowledge base takes a heading in degrees and returns the correct 32-point compass heading. It can also go in the other direction. <lang prolog> compassangle(1, 'North',n, 0.00). compassangle(2, 'North by east', nbe, 11.25). compassangle(3, 'North-northeast', nne,22.50). compassangle(4, 'Northeast by north', nebn,33.75). compassangle(5, 'Northeast', ne,45.00). compassangle(6, 'Norteast by east', nebe,56.25). compassangle(7, 'East-northeast', ene,67.50). compassangle(8, 'East by North', ebn,78.75). compassangle(9, 'East', e,90.00). compassangle(10, 'East by south', ebs, 101.25). compassangle(11, 'East-southeast', ese,112.50). compassangle(12, 'Southeast by east', sebe, 123.75). compassangle(13, 'Southeast', se, 135.00). compassangle(14, 'Southeast by south', sebs, 146.25). compassangle(15, 'South-southeast',sse, 157.50). compassangle(16, 'South by east', sbe, 168.75). compassangle(17, 'South', s, 180.00). compassangle(18, 'South by west', sbw, 191.25). compassangle(19, 'South-southwest', ssw, 202.50). compassangle(20, 'Southwest by south', swbs, 213.75). compassangle(21, 'Southwest', sw, 225.00). compassangle(22, 'Southwest by west', swbw, 236.25). compassangle(23, 'West-southwest', wsw, 247.50). compassangle(24, 'West by south', wbs, 258.75). compassangle(25, 'West', w, 270.00). compassangle(26, 'West by north', wbn, 281.25). compassangle(27, 'West-northwest', wnw, 292.50). compassangle(28, 'Northwest by west', nwbw, 303.75). compassangle(29, 'Northwest', nw, 315.00). compassangle(30, 'Northwest by north', nwbn, 326.25). compassangle(31, 'North-northwest', nnw, 337.50). compassangle(32, 'North by west', nbw, 348.75). compassangle(1, 'North', n, 360.00). compassangle(Index , Name, Heading, Angle) :- nonvar(Angle), resolveindex(Angle, Index),

                                              compassangle(Index,Name, Heading, _).

resolveindex(Angle, Index) :- N is Angle / 11.25 + 0.5, I is floor(N),Index is (I mod 32) + 1. </lang> Part 2 : The following rules print a table of indexes. <lang prolog> printTableRow(Angle) :- compassangle(Index, Name, _, Angle),

                       write(Index), write('    '),
                       write(Name), write('   '),
                       write(Angle).

printTable([X|Xs]) :- printTableRow(X), nl, printTable(Xs),!. printTable([]). </lang> The following query prints the required table. <lang prolog> ?- printTable([0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5, 84.37, 84.38, 101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75, 185.62,

                      185.63, 202.5, 219.37, 219.38, 236.25, 253.12, 253.13, 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38]).

1 North 0.0 2 North by east 16.87 3 North-northeast 16.88 4 Northeast by north 33.75 5 Northeast 50.62 6 Norteast by east 50.63 7 East-northeast 67.5 8 East by North 84.37 9 East 84.38 10 East by south 101.25 11 East-southeast 118.12 12 Southeast by east 118.13 13 Southeast 135.0 14 Southeast by south 151.87 15 South-southeast 151.88 16 South by east 168.75 17 South 185.62 18 South by west 185.63 19 South-southwest 202.5 20 Southwest by south 219.37 21 Southwest 219.38 22 Southwest by west 236.25 23 West-southwest 253.12 24 West by south 253.13 25 West 270.0 26 West by north 286.87 27 West-northwest 286.88 28 Northwest by west 303.75 29 Northwest 320.62 30 Northwest by north 320.63 31 North-northwest 337.5 32 North by west 354.37 1 North 354.38 true. </lang>

Python

<lang python>majors = 'north east south west'.split() majors *= 2 # no need for modulo later quarter1 = 'N,N by E,N-NE,NE by N,NE,NE by E,E-NE,E by N'.split(',') quarter2 = [p.replace('NE','EN') for p in quarter1]

def degrees2compasspoint(d):

   d = (d % 360) + 360/64
   majorindex, minor = divmod(d, 90.)
   majorindex = int(majorindex)
   minorindex  = int( (minor*4) // 45 )
   p1, p2 = majors[majorindex: majorindex+2]
   if p1 in {'north', 'south'}:
       q = quarter1
   else:
       q = quarter2
   return q[minorindex].replace('N', p1).replace('E', p2).capitalize()

if __name__ == '__main__':

   for i in range(33):
       d = i * 11.25
       m = i % 3
       if   m == 1: d += 5.62
       elif m == 2: d -= 5.62
       n = i % 32 + 1
       print( '%2i %-18s %7.2f°' % (n, degrees2compasspoint(d), d) )</lang>
Output
 1 North                 0.00°
 2 North by east        16.87°
 3 North-northeast      16.88°
 4 Northeast by north   33.75°
 5 Northeast            50.62°
 6 Northeast by east    50.63°
 7 East-northeast       67.50°
 8 East by north        84.37°
 9 East                 84.38°
10 East by south       101.25°
11 East-southeast      118.12°
12 Southeast by east   118.13°
13 Southeast           135.00°
14 Southeast by south  151.87°
15 South-southeast     151.88°
16 South by east       168.75°
17 South               185.62°
18 South by west       185.63°
19 South-southwest     202.50°
20 Southwest by south  219.37°
21 Southwest           219.38°
22 Southwest by west   236.25°
23 West-southwest      253.12°
24 West by south       253.13°
25 West                270.00°
26 West by north       286.87°
27 West-northwest      286.88°
28 Northwest by west   303.75°
29 Northwest           320.62°
30 Northwest by north  320.63°
31 North-northwest     337.50°
32 North by west       354.37°
 1 North               354.38°

REXX

This example is written in ooRexx <lang REXX>/* Rexx */

Do

 globs = '!DEG !MIN !SEC !FULL'
 Drop !DEG !MIN !SEC !FULL
 sign. = 
 sign.!DEG = 'c2b0'x     -- degree sign  : U+00B0
 sign.!MIN = 'e280b2'x   -- prime        : U+2032
 sign.!SEC = 'e280b3'x   -- double prime : U+2033
 points. = 
 Call display_compass_points
 Call display_sample
 Say
 headings. = 
 headings.0 = 0
 Call make_headings
 Call flush_queue
 Do h_ = 1 to headings.0
   Queue headings.h_
   End h_
 Call display_sample
 Say
 Return

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ flush_queue: Procedure Do

 Do q_ = 1 to queued()
   Parse pull .
   End q_
 Return

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ display_sample: Procedure Expose points. sign. (globs) Do

 Do q_ = 1 to queued()
   Parse pull heading
   index = get_index(heading)
   Parse Value get_point(index) with p_abbrev p_full
   Say index~right(3),
       p_abbrev~left(4) p_full~left(20),
       heading~format(5, 3) || sign.!DEG '('format_degrees_minutes_seconds(heading)')',
       
   End q_
 Return

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ display_compass_points: Procedure Expose points. sign. (globs) Do

 points = 32
 one_pt = 360 / points
 Do h_ = 0 to points - 1
   heading = h_ * 360 / points
   hmin = heading - one_pt / 2
   hmax = heading + one_pt / 2
   If hmin < 0 then Do
     hmin = hmin + 360
     End
   If hmax >= 360 then Do
     hmax = hmax - 360
     End
   index = (h_ // points) + 1
   Parse Value get_point(index) with p_abbrev p_full
   Say index~right(3),
       p_abbrev~left(4) p_full~left(20),
       hmin~format(5, 3)    || sign.!DEG '('format_degrees_minutes_seconds(hmin)')',
       heading~format(5, 3) || sign.!DEG '('format_degrees_minutes_seconds(heading)')',
       hmax~format(5, 3)    || sign.!DEG '('format_degrees_minutes_seconds(hmax)')',
       
   End h_
 Say
 Return

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ make_headings: Procedure Expose headings. Do

 points = 32
 Do i_ = 0 to points
   heading = i_ * 360 / 32
   it = i_ // 3
   Select
     When it = 1 then Do
       heading_h = heading + 5.62
       End
     When it = 2 then Do
       heading_h = heading - 5.62
       End
     Otherwise Do
       heading_h = heading
       End
     End
   index = (i_ // points) + 1
   ix = headings.0 + 1; headings.0 = ix; headings.ix = heading_h
   End i_
 Return

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ get_index: Procedure Do

 Parse Arg heading .
 one_pt = 360 / 32
 hn = heading // 360
 hi = hn % one_pt
 If hn > hi * one_pt + one_pt / 2 then Do
   hi = hi + 1 -- greater than max range for this point; bump to next point
   End
 idx = hi // 32 + 1 -- add one to get index into points. stem
 Return idx

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ get_point: Procedure Expose points. sign. (globs) Do

 Parse arg index .
 Call get_points
 Return points.index points.index.!FULL

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ get_points: Procedure Expose points. sign. (globs) Do

 Drop !FULL
 points. = 
 p_ = 0
 p_ = p_ + 1; points.0 = p_; points.p_ = 'N';    points.p_.!FULL = 'North'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NbE';  points.p_.!FULL = 'North by East'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NNE';  points.p_.!FULL = 'North-Northeast'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NEbn'; points.p_.!FULL = 'Northeast by North'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NE';   points.p_.!FULL = 'Northeast'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NEbE'; points.p_.!FULL = 'Northeast by East'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'ENE';  points.p_.!FULL = 'East-Northeast'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'EbN';  points.p_.!FULL = 'East by North'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'E';    points.p_.!FULL = 'East'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'EbS';  points.p_.!FULL = 'East by South'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'ESE';  points.p_.!FULL = 'East-Southeast'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SEbE'; points.p_.!FULL = 'Southeast by East'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SE';   points.p_.!FULL = 'Southeast'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SEbS'; points.p_.!FULL = 'Southeast by South'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SSE';  points.p_.!FULL = 'South-Southeast'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SbE';  points.p_.!FULL = 'South by East'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'S';    points.p_.!FULL = 'South'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SbW';  points.p_.!FULL = 'South by West'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SSW';  points.p_.!FULL = 'South-Southwest'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SWbS'; points.p_.!FULL = 'Southwest by South'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SW';   points.p_.!FULL = 'Southwest'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'SWbW'; points.p_.!FULL = 'Southwest by West'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'WSW';  points.p_.!FULL = 'Southwest'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'WbS';  points.p_.!FULL = 'West by South'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'W';    points.p_.!FULL = 'West'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'WbN';  points.p_.!FULL = 'West by North'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'WNW';  points.p_.!FULL = 'West-Northwest'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NWbW'; points.p_.!FULL = 'Northwest by West'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NW';   points.p_.!FULL = 'Northwest'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NWbN'; points.p_.!FULL = 'Northwest by North'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NNW';  points.p_.!FULL = 'North-Northwest'
 p_ = p_ + 1; points.0 = p_; points.p_ = 'NbW';  points.p_.!FULL = 'North by West'
 Return

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ get_decimal_angle: Procedure Expose sign. (globs) Do

 Parse Arg degrees ., minutes ., seconds .
 degrees = degrees * 10 % 10
 minutes = minutes * 10 % 10
 angle = degrees + minutes / 60 + seconds / 60 / 60
 Return angle

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ format_decimal_angle: Procedure Expose sign. (globs) Do

 Parse Arg degrees ., minutes ., seconds .
 Return get_decimal_angle(degrees, minutes, seconds)~format(5, 3) || sign.!DEG

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ get_degrees_minutes_seconds: Procedure Expose sign. (globs) Do

 Parse arg angle .
 degrees = angle * 100 % 100
 minutes = ((angle - degrees) * 60) * 100 % 100
 seconds = ((((angle - degrees) * 60) - minutes) * 60) * 100 % 100
 Return degrees minutes seconds

End Exit

/* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ */ format_degrees_minutes_seconds: Procedure Expose sign. (globs) Do

 Parse arg angle .
 Parse Value get_degrees_minutes_seconds(angle) with degrees minutes seconds .
 formatted = degrees~right(3) || sign.!DEG || minutes~right(2, 0) || sign.!MIN || seconds~right(2, 0) || sign.!SEC
 Return formatted

End Exit </lang>

Output
  1 N    North                  354.375° (354°22′30″)     0.000° (  0°00′00″)     5.625° (  5°37′30″) 
  2 NbE  North by East            5.625° (  5°37′30″)    11.250° ( 11°15′00″)    16.875° ( 16°52′30″) 
  3 NNE  North-Northeast         16.875° ( 16°52′30″)    22.500° ( 22°30′00″)    28.125° ( 28°07′30″) 
  4 NEbn Northeast by North      28.125° ( 28°07′30″)    33.750° ( 33°45′00″)    39.375° ( 39°22′30″) 
  5 NE   Northeast               39.375° ( 39°22′30″)    45.000° ( 45°00′00″)    50.625° ( 50°37′30″) 
  6 NEbE Northeast by East       50.625° ( 50°37′30″)    56.250° ( 56°15′00″)    61.875° ( 61°52′30″) 
  7 ENE  East-Northeast          61.875° ( 61°52′30″)    67.500° ( 67°30′00″)    73.125° ( 73°07′30″) 
  8 EbN  East by North           73.125° ( 73°07′30″)    78.750° ( 78°45′00″)    84.375° ( 84°22′30″) 
  9 E    East                    84.375° ( 84°22′30″)    90.000° ( 90°00′00″)    95.625° ( 95°37′30″) 
 10 EbS  East by South           95.625° ( 95°37′30″)   101.250° (101°15′00″)   106.875° (106°52′30″) 
 11 ESE  East-Southeast         106.875° (106°52′30″)   112.500° (112°30′00″)   118.125° (118°07′30″) 
 12 SEbE Southeast by East      118.125° (118°07′30″)   123.750° (123°45′00″)   129.375° (129°22′30″) 
 13 SE   Southeast              129.375° (129°22′30″)   135.000° (135°00′00″)   140.625° (140°37′30″) 
 14 SEbS Southeast by South     140.625° (140°37′30″)   146.250° (146°15′00″)   151.875° (151°52′30″) 
 15 SSE  South-Southeast        151.875° (151°52′30″)   157.500° (157°30′00″)   163.125° (163°07′30″) 
 16 SbE  South by East          163.125° (163°07′30″)   168.750° (168°45′00″)   174.375° (174°22′30″) 
 17 S    South                  174.375° (174°22′30″)   180.000° (180°00′00″)   185.625° (185°37′30″) 
 18 SbW  South by West          185.625° (185°37′30″)   191.250° (191°15′00″)   196.875° (196°52′30″) 
 19 SSW  South-Southwest        196.875° (196°52′30″)   202.500° (202°30′00″)   208.125° (208°07′30″) 
 20 SWbS Southwest by South     208.125° (208°07′30″)   213.750° (213°45′00″)   219.375° (219°22′30″) 
 21 SW   Southwest              219.375° (219°22′30″)   225.000° (225°00′00″)   230.625° (230°37′30″) 
 22 SWbW Southwest by West      230.625° (230°37′30″)   236.250° (236°15′00″)   241.875° (241°52′30″) 
 23 WSW  Southwest              241.875° (241°52′30″)   247.500° (247°30′00″)   253.125° (253°07′30″) 
 24 WbS  West by South          253.125° (253°07′30″)   258.750° (258°45′00″)   264.375° (264°22′30″) 
 25 W    West                   264.375° (264°22′30″)   270.000° (270°00′00″)   275.625° (275°37′30″) 
 26 WbN  West by North          275.625° (275°37′30″)   281.250° (281°15′00″)   286.875° (286°52′30″) 
 27 WNW  West-Northwest         286.875° (286°52′30″)   292.500° (292°30′00″)   298.125° (298°07′30″) 
 28 NWbW Northwest by West      298.125° (298°07′30″)   303.750° (303°45′00″)   309.375° (309°22′30″) 
 29 NW   Northwest              309.375° (309°22′30″)   315.000° (315°00′00″)   320.625° (320°37′30″) 
 30 NWbN Northwest by North     320.625° (320°37′30″)   326.250° (326°15′00″)   331.875° (331°52′30″) 
 31 NNW  North-Northwest        331.875° (331°52′30″)   337.500° (337°30′00″)   343.125° (343°07′30″) 
 32 NbW  North by West          343.125° (343°07′30″)   348.750° (348°45′00″)   354.375° (354°22′30″) 


  1 N    North                    0.000° (  0°00′00″) 
  2 NbE  North by East           16.870° ( 16°52′12″) 
  3 NNE  North-Northeast         16.880° ( 16°52′48″) 
  4 NEbn Northeast by North      33.750° ( 33°45′00″) 
  5 NE   Northeast               50.620° ( 50°37′12″) 
  6 NEbE Northeast by East       50.630° ( 50°37′48″) 
  7 ENE  East-Northeast          67.500° ( 67°30′00″) 
  8 EbN  East by North           84.370° ( 84°22′12″) 
  9 E    East                    84.380° ( 84°22′48″) 
 10 EbS  East by South          101.250° (101°15′00″) 
 11 ESE  East-Southeast         118.120° (118°07′12″) 
 12 SEbE Southeast by East      118.130° (118°07′48″) 
 13 SE   Southeast              135.000° (135°00′00″) 
 14 SEbS Southeast by South     151.870° (151°52′12″) 
 15 SSE  South-Southeast        151.880° (151°52′48″) 
 16 SbE  South by East          168.750° (168°45′00″) 
 17 S    South                  185.620° (185°37′12″) 
 18 SbW  South by West          185.630° (185°37′48″) 
 19 SSW  South-Southwest        202.500° (202°30′00″) 
 20 SWbS Southwest by South     219.370° (219°22′12″) 
 21 SW   Southwest              219.380° (219°22′48″) 
 22 SWbW Southwest by West      236.250° (236°15′00″) 
 23 WSW  Southwest              253.120° (253°07′12″) 
 24 WbS  West by South          253.130° (253°07′48″) 
 25 W    West                   270.000° (270°00′00″) 
 26 WbN  West by North          286.870° (286°52′12″) 
 27 WNW  West-Northwest         286.880° (286°52′48″) 
 28 NWbW Northwest by West      303.750° (303°45′00″) 
 29 NW   Northwest              320.620° (320°37′12″) 
 30 NWbN Northwest by North     320.630° (320°37′48″) 
 31 NNW  North-Northwest        337.500° (337°30′00″) 
 32 NbW  North by West          354.370° (354°22′12″) 
  1 N    North                  354.380° (354°22′48″) 

Ruby

First I want a hash Headings = {1 => "north", 2 => "north by east", ...}. This program outputs the hash so that I can skip typing all 32 pairs.

<lang ruby>h = [] ["north", "east", "south", "west", "north"].each_cons(2) do |a, b|

 c = if ["north", "south"].include? a then "#{a}#{b}" else "#{b}#{a}" end
 h << a
 h << "#{a} by #{b}"
 h << "#{a}-#{c}"
 h << "#{c} by #{a}"
 h << "#{c}"
 h << "#{c} by #{b}"
 h << "#{b}-#{c}"
 h << "#{b} by #{a}"

end

puts "Headings = {" h.each_with_index { |n, i| puts " #{i+1} => #{n.inspect}," } puts "}"</lang>

I paste the output from the first program into a second program, then add a method to find a compass heading from degrees, and some code to output the table.

<lang ruby>Headings = {

 1 => "north",
 2 => "north by east",
 3 => "north-northeast",
 4 => "northeast by north",
 5 => "northeast",
 6 => "northeast by east",
 7 => "east-northeast",
 8 => "east by north",
 9 => "east",
 10 => "east by south",
 11 => "east-southeast",
 12 => "southeast by east",
 13 => "southeast",
 14 => "southeast by south",
 15 => "south-southeast",
 16 => "south by east",
 17 => "south",
 18 => "south by west",
 19 => "south-southwest",
 20 => "southwest by south",
 21 => "southwest",
 22 => "southwest by west",
 23 => "west-southwest",
 24 => "west by south",
 25 => "west",
 26 => "west by north",
 27 => "west-northwest",
 28 => "northwest by west",
 29 => "northwest",
 30 => "northwest by north",
 31 => "north-northwest",
 32 => "north by west",

}

  1. Finds the 32-point compass heading nearest _degrees_, and
  2. returns an array of the index and name.
  3. p heading(60)
  4. # => [6, "northeast by east"]

def heading(degrees)

 i = degrees.quo(360).*(32).round.%(32).+(1)
 [i, Headings[i]]

end

  1. an array of angles, in degrees

angles = (0..32).map { |i| i * 11.25 + [0, 5.62, -5.62][i % 3] }

angles.each do |degrees|

 index, name = heading degrees
 printf "%2d %20s %6.2f\n", index, name.center(20), degrees

end</lang>

The second program outputs this table:

 1        north           0.00
 2    north by east      16.87
 3   north-northeast     16.88
 4  northeast by north   33.75
 5      northeast        50.62
 6  northeast by east    50.63
 7    east-northeast     67.50
 8    east by north      84.37
 9         east          84.38
10    east by south     101.25
11    east-southeast    118.12
12  southeast by east   118.13
13      southeast       135.00
14  southeast by south  151.87
15   south-southeast    151.88
16    south by east     168.75
17        south         185.62
18    south by west     185.63
19   south-southwest    202.50
20  southwest by south  219.37
21      southwest       219.38
22  southwest by west   236.25
23    west-southwest    253.12
24    west by south     253.13
25         west         270.00
26    west by north     286.87
27    west-northwest    286.88
28  northwest by west   303.75
29      northwest       320.62
30  northwest by north  320.63
31   north-northwest    337.50
32    north by west     354.37
 1        north         354.38

Scala

Inspired by Java version <lang Scala>object BoxingTheCompass extends App {

 val cardinal = List("north", "east", "south", "west")
 val pointDesc = List("1", "1 by 2", "1-C", "C by 1", "C", "C by 2", "2-C", "2 by 1")
 val pointDeg: Int => Double = i => {

val fswitch: Int => Int = i => i match {case 1 => 1; case 2 => -1; case _ => 0} i*11.25+fswitch(i%3)*5.62

 }
 val deg2ind: Double => Int = deg => (deg*32/360+.5).toInt%32+1
 
 val pointName: Int => String = ind => {
   val i = ind - 1
   val str1 = cardinal(i%32/8)
   val str2 = cardinal((i%32/8+1)%4)
   val strC = if ((str1 == "north") || (str1 == "south")) str1+str2 else str2+str1
   pointDesc(i%32%8).replace("1", str1).replace("2", str2).replace("C", strC).capitalize
 }
 (0 to 32).map(i=>Triple(pointDeg(i),deg2ind(pointDeg(i)),pointName(deg2ind(pointDeg(i)))))
     .map{t=>(printf("%s\t%18s\t%s°\n",t._2,t._3,t._1))}

}</lang>

Output:

1	             North	0.0°
2	     North by east	16.87°
3	   North-northeast	16.88°
4	Northeast by north	33.75°
5	         Northeast	50.62°
6	 Northeast by east	50.63°
7	    East-northeast	67.5°
8	     East by north	84.37°
9	              East	84.38°
10	     East by south	101.25°
11	    East-southeast	118.12°
12	 Southeast by east	118.13°
13	         Southeast	135.0°
14	Southeast by south	151.87°
15	   South-southeast	151.88°
16	     South by east	168.75°
17	             South	185.62°
18	     South by west	185.63°
19	   South-southwest	202.5°
20	Southwest by south	219.37°
21	         Southwest	219.38°
22	 Southwest by west	236.25°
23	    West-southwest	253.12°
24	     West by south	253.13°
25	              West	270.0°
26	     West by north	286.87°
27	    West-northwest	286.88°
28	 Northwest by west	303.75°
29	         Northwest	320.62°
30	Northwest by north	320.63°
31	   North-northwest	337.5°
32	     North by west	354.37°
1	             North	354.38°

Seed7

<lang seed7>$ include "seed7_05.s7i";

 include "float.s7i";

const array string: names is [] ("North", "North by east", "North-northeast", "Northeast by north",

  "Northeast", "Northeast by east", "East-northeast", "East by north", "East", "East by south",
  "East-southeast", "Southeast by east", "Southeast", "Southeast by south", "South-southeast",
  "South by east", "South", "South by west", "South-southwest", "Southwest by south", "Southwest",
  "Southwest by west", "West-southwest", "West by south", "West", "West by north", "West-northwest",
  "Northwest by west", "Northwest", "Northwest by north", "North-northwest", "North by west", "North");

const proc: main is func

 local
   const array float: degrees is [] (0.0, 16.87, 16.88, 33.75, 50.62, 50.63, 67.5, 84.37, 84.38,
       101.25, 118.12, 118.13, 135.0, 151.87, 151.88, 168.75, 185.62, 185.63, 202.5, 219.37, 219.38,
       236.25, 253.12, 253.13, 270.0, 286.87, 286.88, 303.75, 320.62, 320.63, 337.5, 354.37, 354.38);
   var integer: index is 0;
   var integer: nameIndex is 0;
 begin
   for key index range degrees do
     nameIndex := round(degrees[index] * 32.0 / 360.0);
     writeln(succ(pred(index) rem 32) lpad 2 <& "  " <& names[succ(nameIndex rem 32)] rpad 22 <&
         degrees[index] digits 2 lpad 6);
   end for;
 end func;</lang>

Output:

 1  North                   0.00
 2  North by east          16.87
 3  North-northeast        16.88
 4  Northeast by north     33.75
 5  Northeast              50.62
 6  Northeast by east      50.63
 7  East-northeast         67.50
 8  East by north          84.37
 9  East                   84.38
10  East by south         101.25
11  East-southeast        118.12
12  Southeast by east     118.13
13  Southeast             135.00
14  Southeast by south    151.87
15  South-southeast       151.88
16  South by east         168.75
17  South                 185.62
18  South by west         185.63
19  South-southwest       202.50
20  Southwest by south    219.37
21  Southwest             219.38
22  Southwest by west     236.25
23  West-southwest        253.12
24  West by south         253.13
25  West                  270.00
26  West by north         286.87
27  West-northwest        286.88
28  Northwest by west     303.75
29  Northwest             320.62
30  Northwest by north    320.63
31  North-northwest       337.50
32  North by west         354.37
 1  North                 354.38

Tcl

<lang tcl>proc angle2compass {angle} {

   set dirs {

N NbE N-NE NEbN NE NEbE E-NE EbN E EbS E-SE SEbE SE SEbS S-SE SbE S SbW S-SW SWbS SW SWbW W-SW WbS W WbN W-NW NWbW NW NWbN N-NW NbW

   }
   set unpack {N "north" E "east" W "west" S "south" b " by "}
   # Compute the width of each compass segment
   set sep [expr {360.0 / [llength $dirs]}]
   # Work out which segment contains the compass angle
   set dir [expr {round((fmod($angle + $sep/2, 360) - $sep/2) / $sep)}]
   # Convert to a named direction, capitalized as in the wikipedia article
   return [string totitle [string map $unpack [lindex $dirs $dir]]]

}

  1. Box the compass, using the variable generation algorithm described

for {set i 0} {$i < 33} {incr i} {

   set heading [expr {$i * 11.25}]
   if {$i % 3 == 1} {set heading [expr {$heading + 5.62}]}
   if {$i % 3 == 2} {set heading [expr {$heading - 5.62}]}
   set index [expr {$i % 32 + 1}]
   # Pretty-print the results of converting an angle to a compass heading
   puts [format "%2i %-18s %7.2f°" $index [angle2compass $heading] $heading]

}</lang> Output:

 1 North                 0.00°
 2 North by east        16.87°
 3 North-northeast      16.88°
 4 Northeast by north   33.75°
 5 Northeast            50.62°
 6 Northeast by east    50.63°
 7 East-northeast       67.50°
 8 East by north        84.37°
 9 East                 84.38°
10 East by south       101.25°
11 East-southeast      118.12°
12 Southeast by east   118.13°
13 Southeast           135.00°
14 Southeast by south  151.87°
15 South-southeast     151.88°
16 South by east       168.75°
17 South               185.62°
18 South by west       185.63°
19 South-southwest     202.50°
20 Southwest by south  219.37°
21 Southwest           219.38°
22 Southwest by west   236.25°
23 West-southwest      253.12°
24 West by south       253.13°
25 West                270.00°
26 West by north       286.87°
27 West-northwest      286.88°
28 Northwest by west   303.75°
29 Northwest           320.62°
30 Northwest by north  320.63°
31 North-northwest     337.50°
32 North by west       354.37°
 1 North               354.38°

UNIX Shell

Works with: Bourne Again SHell
Translation of: Logo

Requires the standard POSIX bc(1) and sed(1) commands to function.

<lang sh># List of abbreviated compass point labels compass_points=( N NbE N-NE NEbN NE NEbE E-NE EbN

                E EbS E-SE SEbE SE SEbS S-SE SbE 
                S SbW S-SW SWbS SW SWbW W-SW WbS 
                W WbN W-NW NWbW NW NWbN N-NW NbW )
  1. List of angles to test

test_angles=( 0.00 16.87 16.88 33.75 50.62 50.63 67.50

             84.37  84.38 101.25 118.12 118.13 135.00 151.87 
            151.88 168.75 185.62 185.63 202.50 219.37 219.38
            236.25 253.12 253.13 270.00 286.87 286.88 303.75 
            320.62 320.63 337.50 354.37 354.38 )


  1. capitalize a string

function capitalize {

 echo "$1" | sed 's/^./\U&/'

}

  1. convert compass point abbreviation to full text of label

function expand_point {

 local label="$1"
 set -- N north E east S south W west b " by "
 while (( $# )); do
   label="${label//$1/$2}"
   shift 2
 done
 capitalize "$label"

}

  1. modulus function that returns 1..N instead of 0..N-1

function amod {

 echo $(( ($1 - 1) % $2 + 1 ))

}

  1. convert a compass angle from degrees into a box index (1..32)

function compass_point {

 #amod $(dc <<<"$1 5.625 + 11.25 / 1 + p") 32
 amod $(bc <<<"($1 + 5.625) / 11.25 + 1") 32

}

  1. Now output the table of test data

header_format="%-7s | %-18s | %s\n" row_format="%7.2f | %-18s | %2d\n" printf "$header_format" "Degrees" "Closest Point" "Index" for angle in ${test_angles[@]}; do

 let index=$(compass_point $angle)
 abbr=${compass_points[index-1]}
 label="$(expand_point $abbr)"
 printf "$row_format" $angle "$label" $index

done</lang>

Output:

Degrees | Closest Point      | Index
   0.00 | North              |  1
  16.87 | North by east      |  2
  16.88 | North-northeast    |  3
  33.75 | Northeast by north |  4
  50.62 | Northeast          |  5
  50.63 | Northeast by east  |  6
  67.50 | East-northeast     |  7
  84.37 | East by north      |  8
  84.38 | East               |  9
 101.25 | East by south      | 10
 118.12 | East-southeast     | 11
 118.13 | Southeast by east  | 12
 135.00 | Southeast          | 13
 151.87 | Southeast by south | 14
 151.88 | South-southeast    | 15
 168.75 | South by east      | 16
 185.62 | South              | 17
 185.63 | South by west      | 18
 202.50 | South-southwest    | 19
 219.37 | Southwest by south | 20
 219.38 | Southwest          | 21
 236.25 | Southwest by west  | 22
 253.12 | West-southwest     | 23
 253.13 | West by south      | 24
 270.00 | West               | 25
 286.87 | West by north      | 26
 286.88 | West-northwest     | 27
 303.75 | Northwest by west  | 28
 320.62 | Northwest          | 29
 320.63 | Northwest by north | 30
 337.50 | North-northwest    | 31
 354.37 | North by west      | 32
 354.38 | North              |  1

Visual Basic .NET

<lang vbnet>Module BoxingTheCompass

   Dim _points(32) As String
   Sub Main()
       BuildPoints()
       Dim heading As Double = 0D
       For i As Integer = 0 To 32
           heading = i * 11.25
           Select Case i Mod 3
               Case 1
                   heading += 5.62
               Case 2
                   heading -= 5.62
           End Select
           Console.WriteLine("{0,2}: {1,-18} {2,6:F2}°", (i Mod 32) + 1, InitialUpper(GetPoint(heading)), heading)
       Next
   End Sub
   Private Sub BuildPoints()
       Dim cardinal As String() = New String() {"north", "east", "south", "west"}
       Dim pointDesc As String() = New String() {"1", "1 by 2", "1-C", "C by 1", "C", "C by 2", "2-C", "2 by 1"}
       Dim str1, str2, strC As String
       For i As Integer = 0 To 3
           str1 = cardinal(i)
           str2 = cardinal((i + 1) Mod 4)
           strC = IIf(str1 = "north" Or str1 = "south", str1 & str2, str2 & str1)
           For j As Integer = 0 To 7
               _points(i * 8 + j) = pointDesc(j).Replace("1", str1).Replace("2", str2).Replace("C", strC)
           Next
       Next
   End Sub
   Private Function InitialUpper(ByVal s As String) As String
       Return s.Substring(0, 1).ToUpper() & s.Substring(1)
   End Function
   Private Function GetPoint(ByVal Degrees As Double) As String
       Dim testD As Double = (Degrees / 11.25) + 0.5
       Return _points(CInt(Math.Floor(testD Mod 32)))
   End Function

End Module </lang> Output:

 1: North                0.00°
 2: North by east       16.87°
 3: North-northeast     16.88°
 4: Northeast by north  33.75°
 5: Northeast           50.62°
 6: Northeast by east   50.63°
 7: East-northeast      67.50°
 8: East by north       84.37°
 9: East                84.38°
10: East by south      101.25°
11: East-southeast     118.12°
12: Southeast by east  118.13°
13: Southeast          135.00°
14: Southeast by south 151.87°
15: South-southeast    151.88°
16: South by east      168.75°
17: South              185.62°
18: South by west      185.63°
19: South-southwest    202.50°
20: Southwest by south 219.37°
21: Southwest          219.38°
22: Southwest by west  236.25°
23: West-southwest     253.12°
24: West by south      253.13°
25: West               270.00°
26: West by north      286.87°
27: West-northwest     286.88°
28: Northwest by west  303.75°
29: Northwest          320.62°
30: Northwest by north 320.63°
31: North-northwest    337.50°
32: North by west      354.37°
 1: North              354.38°