Special divisors

From Rosetta Code
Special divisors is a draft programming task. It is not yet considered ready to be promoted as a complete task, for reasons that should be found in its talk page.
Task

Numbers   n   such that   reverse(d)   divides   reverse(n)   for all divisors   d   of   n,   where   n  <  200

Action!

PROC CalcDivisors(INT x INT ARRAY div INT POINTER count)
  INT i

  count^=0
  FOR i=1 TO x/2
  DO
    IF x MOD i=0 THEN
      div(count^)=i
      count^==+1
    FI
  OD
RETURN

INT FUNC Reverse(INT x)
  INT res

  res=0
  WHILE x#0
  DO
    res==*10
    res==+x MOD 10
    x==/10
  OD
RETURN (res)

BYTE FUNC IsSpecial(INT x)
  INT ARRAY divisors(100)
  INT count,i,rev,revd

  CalcDivisors(x,divisors,@count)
  rev=Reverse(x)
  FOR i=0 TO count-1
  DO
    revd=Reverse(divisors(i))
    IF rev MOD revd#0 THEN
      RETURN (0)
    FI
  OD
RETURN (1)

PROC Main()
  INT i

  FOR i=1 TO 199
  DO
    IF IsSpecial(i) THEN
      PrintI(i) Put(32)
    FI
  OD
RETURN
Output:

Screenshot from Atari 8-bit computer

1 2 3 4 5 6 7 8 9 11 13 17 19 22 23 26 27 29 31 33 37 39 41 43 44 46 47 53 55
59 61 62 66 67 69 71 73 77 79 82 83 86 88 89 93 97 99 101 103 107 109 113 121
127 131 137 139 143 149 151 157 163 167 169 173 179 181 187 191 193 197 199

ALGOL 68

BEGIN # find numbers where reverse(d) divides reverse(n) for all divisors d #
      # of n                                                                #
    # returns n with the digits reversed                                    #
    OP REVERSE = ( INT n )INT:
       BEGIN
            INT reverse := 0;
            INT v       := ABS n;
            WHILE v > 0 DO
                reverse *:= 10 +:= v MOD 10;
                v OVERAB 10
            OD;
            reverse * SIGN n
       END # REVERSE # ;
    # find the numbers up to 200                                            #
    INT rd count := 0;
    FOR n TO 199 DO
        INT  reverse n        = REVERSE n;
        BOOL reverse divisor := TRUE;
        FOR d FROM 2 TO n OVER 2 WHILE reverse divisor DO
            IF n MOD d = 0 THEN
                # have a divisor of n                                       #
                reverse divisor := reverse n MOD REVERSE d = 0
            FI
        OD;
        IF reverse divisor THEN
            # all the divisors of n reversed divide n reversed              #
            print( ( " ", whole( n, -3 ) ) );
            IF ( rd count +:= 1 ) MOD 10 = 0 THEN print( ( newline ) ) FI
        FI
    OD;
    print( ( newline, "Found ", whole( rd count, 0 ), " ""special divisors"" below 200", newline ) )
END
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199
Found 72 "special divisors" below 200

ALGOL W

Translation of: ALGOL 68
begin % find numbers where reverse(d) divides reverse(n) for all divisors d %
      % of n                                                                %
    % returns n with the digits reversed                                    %
    integer procedure reverse ( integer value n ) ;
    begin
        integer r, v;
        r := 0;
        v := abs n;
        while v > 0 do begin
            r := ( r * 10 ) + ( v rem 10 );
            v := v div 10
        end while_v_gt_0 ;
        if n < 0 then - r else r
    end reverse ;
    % find the numbers up to 200                                            %
    integer rdCount;
    rdCount := 0;
    for n := 1 until 199 do begin
        integer reverseN, d, maxD;
        logical reverseDivisor;
        reverseN       := reverse( n );
        reverseDivisor := true;
        d              := 1;
        maxD           := n div 2;
        while begin
                  d := d + 1;
                  d <= maxD and reverseDivisor
              end
        do begin
            if n rem d = 0 then begin
                % have a divisor of n                                       %
                reverseDivisor := reverseN rem reverse( d ) = 0
            end if_n_rem_d_eq_0
        end while_d_le_maxD_and_reverseDivisor ;
        if reverseDivisor then begin
            % all the divisors of n reversed divide n reversed              %
            writeon( i_w := 3, s_w := 0, " ", n );
            rdCount := rdCount + 1;
            if rdCount rem 10 = 0 then write()
        end if_reverseDivisor
    end for_n ;
    write( i_w := 1, s_w := 0, "Found ", rdCount, " ""special divisors"" below 200" )
end.
Output:

Same as the Algol 68 sample.

APL

Works with: Dyalog APL
((/⍨)(0.=(⍎⌽)¨∘(0=⍳|⊢)|(⍎⌽))¨) 200
Output:
1 2 3 4 5 6 7 8 9 11 13 17 19 22 23 26 27 29 31 33 37 39 41 43 44 46 47
      53 55 59 61 62 66 67 69 71 73 77 79 82 83 86 88 89 93 97 99 101
      103 107 109 113 121 127 131 137 139 143 149 151 157 163 167 169
      173 179 181 187 191 193 197 199

AppleScript

on factors(n)
    set output to {}
    
    if (n > 0) then
        set sqrt to n ^ 0.5
        set limit to sqrt div 1
        if (limit = sqrt) then
            set end of output to limit
            set limit to limit - 1
        end if
        repeat with i from limit to 1 by -1
            if (n mod i is 0) then
                set beginning of output to i
                set end of output to n div i
            end if
        end repeat
    end if
    
    return output
end factors

on reversedIntVal(n, base)
    set r to n mod base as integer
    set n to n div base
    repeat until (n = 0)
        set r to r * base + n mod base
        set n to n div base
    end repeat
    
    return r
end reversedIntVal

on hasSpecialDivisors(n, base)
    set divisors to factors(n)
    if (divisors is {}) then return false
    set r to reversedIntVal(n, base)
    repeat with d in divisors
        if (r mod (reversedIntVal(d, base)) > 0) then return false
    end repeat
    
    return true
end hasSpecialDivisors

local output, base, n
set output to {}
set base to 10
repeat with n from 1 to 199
    if (hasSpecialDivisors(n, base)) then set end of output to n
end repeat
return {|count|:(count output), finds:output}
Output:
{|count|:72, finds:{1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 13, 17, 19, 22, 23, 26, 27, 29, 31, 33, 37, 39, 41, 43, 44, 46, 47, 53, 55, 59, 61, 62, 66, 67, 69, 71, 73, 77, 79, 82, 83, 86, 88, 89, 93, 97, 99, 101, 103, 107, 109, 113, 121, 127, 131, 137, 139, 143, 149, 151, 157, 163, 167, 169, 173, 179, 181, 187, 191, 193, 197, 199}}

Arturo

reversed: function [x]->
    to :integer join to [:string] reverse digits x

specialDivisors: select 1..200 'n ->
    every? factors n 'd ->
        zero? (reversed n) % reversed d

loop split.every: 9 specialDivisors 'x ->
    print map x 's -> pad to :string s 4
Output:
   1    2    3    4    5    6    7    8    9 
  11   13   17   19   22   23   26   27   29 
  31   33   37   39   41   43   44   46   47 
  53   55   59   61   62   66   67   69   71 
  73   77   79   82   83   86   88   89   93 
  97   99  101  103  107  109  113  121  127 
 131  137  139  143  149  151  157  163  167 
 169  173  179  181  187  191  193  197  199

BASIC

10 DEFINT A-Z
20 FOR I=1 TO 199
30 J=I: X=0
40 IF J>0 THEN X=X*10+J MOD 10: J=J\10: GOTO 40
50 FOR J=1 TO I\2
60 IF I MOD J GOTO 100
70 K=J: Y=0
80 IF K>0 THEN Y=Y*10+K MOD 10: K=K\10: GOTO 80
90 IF X MOD Y GOTO 120
100 NEXT J
110 PRINT I,
120 NEXT I
Output:
 1             2             3             4             5
 6             7             8             9             11
 13            17            19            22            23
 26            27            29            31            33
 37            39            41            43            44
 46            47            53            55            59
 61            62            66            67            69
 71            73            77            79            82
 83            86            88            89            93
 97            99            101           103           107
 109           113           121           127           131
 137           139           143           149           151
 157           163           167           169           173
 179           181           187           191           193
 197           199

BASIC256

c = 0
for n = 1 to 200
    u = reverse(n)
    s = true
    for d = 1 to n
        if n mod d = 0 then
            b = reverse(d)
            if u mod b <> 0 then s = false
        end if
    next d
    if s then c += 1 : print n; chr(9);
next n

print
print "Found "; c; " special divisors."
end

function reverse(n)
    u = 0
    while n
        u = u * 10 + n mod 10
        n = n \ 10
    end while
    return u
end function
Output:
1    2    3    4    5    6    7    8    9    11    13    17    19    22    23    26    27    29    31    33    37    39    41    43    44    46    47    53    55    59    61    62    66    67    69    71    73    77    79    82    83    86    88    89    93    97    99    101    103    107    109    113    121    127    131    137    139    143    149    151    157    163    167    169    173    179    181    187    191    193    197    199    
Found 72 special divisors.

BCPL

get "libhdr"

let reverse(n) = valof
$(  let r = 0
    while n > 0
    $(  r := r*10 + n rem 10
        n := n/10
    $)
    resultis r
$)

let special(n) = valof
$(  let r = reverse(n)
    for d = 1 to n/2
        if n rem d = 0 & r rem reverse(d) ~= 0 
            resultis false
    resultis true
$)

let start() be
$(  let c = 0
    for n = 1 to 199
        if special(n)
        $(  writed(n,4)
            c := c + 1
            if c = 10
            $(  wrch('*N')
                c := 0
            $)
        $)
    wrch('*N')
$)
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

C

Translation of: Delphi
#include <stdbool.h>
#include <stdio.h>

int reverse(int n) {
    int result = 0;
    while (n > 0) {
        result = 10 * result + n % 10;
        n /= 10;
    }
    return result;
}

int main() {
    const int limit1 = 200;

    int row = 0;
    int num = 0;
    int n;

    for (n = 1; n < limit1; n++) {
        bool flag = true;
        int revNum = reverse(n);
        int m;

        for (m = 1; m < n / 2; m++) {
            int revDiv = reverse(m);
            if (n % m == 0) {
                if (revNum % revDiv == 0) {
                    flag = true;
                } else {
                    flag = false;
                    break;
                }
            }
        }

        if (flag) {
            num++;
            row++;
            printf("%4d ", n);
            if (row % 10 == 0) {
                printf("\n");
            }
        }
    }

    printf("\n\nFound %d special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where N < 200\n", num);

    return 0;
}
Output:
   1    2    3    4    5    6    7    8    9   11
  13   17   19   22   23   26   27   29   31   33
  37   39   41   43   44   46   47   53   55   59
  61   62   66   67   69   71   73   77   79   82
  83   86   88   89   93   97   99  101  103  107
 109  113  121  127  131  137  139  143  149  151
 157  163  167  169  173  179  181  187  191  193
 197  199

Found 72 special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where N < 200

C++

#include <iostream>
#include <iomanip>
#include <vector>

using uint = unsigned int;

std::vector<uint> divisors(uint n) {
    std::vector<uint> divs;
    for (uint d=1; d<=n/2; d++) {
        if (n % d == 0) divs.push_back(d);
    }
    return divs;
}

uint reverse(uint n) {
    uint r;
    for (r = 0; n; n /= 10) r = (r*10) + (n%10);
    return r;
}

bool special(uint n) {
    for (uint d : divisors(n))
        if (reverse(n) % reverse(d) != 0) return false;
    return true;
}

int main() {
    for (uint n=1, c=0; n < 200; n++) {
        if (special(n)) {
            std::cout << std::setw(4) << n;
            if (++c == 10) {
                c = 0;
                std::cout << std::endl;
            }
        }
    }
    std::cout << std::endl;
    return 0;
}
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

C#

Translation of: C
using System;

namespace SpecialDivisors {
    class Program {
        static int Reverse(int n) {
            int result = 0;
            while (n > 0) {
                result = 10 * result + n % 10;
                n /= 10;
            }
            return result;
        }

        static void Main() {
            const int LIMIT = 200;

            int row = 0;
            int num = 0;

            for (int n = 1; n < LIMIT; n++) {
                bool flag = true;
                int revNum = Reverse(n);

                for (int m = 1; m < n / 2; m++) {
                    int revDiv = Reverse(m);
                    if (n % m == 0) {
                        if (revNum % revDiv == 0) {
                            flag = true;
                        } else {
                            flag = false;
                            break;
                        }
                    }
                }

                if (flag) {
                    num++;
                    row++;
                    Console.Write("{0,4}", n);
                    if (row % 10 == 0) {
                        Console.WriteLine();
                    }
                }
            }

            Console.WriteLine();
            Console.WriteLine();
            Console.WriteLine("Found {0} special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where N < 200", num);
        }
    }
}
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

Found 72 special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where N < 200

CLU

reverse = proc (n: int) returns (int)
    r: int := 0
    while n>0 do
        r := r*10 + n//10
        n := n/10
    end
    return(r)
end reverse

special = proc (n: int) returns (bool)
    r: int := reverse(n)
    for d: int in int$from_to(1,n/2) do
        if n//d=0 & r//reverse(d)~=0 then 
            return(false) 
        end
    end
    return(true)
end special

start_up = proc ()
    po: stream := stream$primary_output()
    c: int := 0
    for n: int in int$from_to(1,199) do
        if special(n) then
            stream$putright(po, int$unparse(n), 4)
            c := c+1
            if c=10 then
                stream$putl(po, "")
                c := 0
            end
        end
    end
end start_up
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

COBOL

        IDENTIFICATION DIVISION.
        PROGRAM-ID. SPECIAL-DIVISORS.
        
        DATA DIVISION.
        WORKING-STORAGE SECTION.
        01 VARIABLES.
           02 CANDIDATE         PIC 999.
           02 CAND-REV          PIC 999.
           02 REVERSE           PIC 999.
           02 REV-DIGITS        REDEFINES REVERSE PIC 9 OCCURS 3 TIMES.
           02 DIVMAX            PIC 999.
           02 DIVISOR           PIC 999.
           02 DIVRSLT           PIC 999V999.
           02 FILLER            REDEFINES DIVRSLT.
              03 FILLER         PIC 999.
              03 FILLER         PIC 999.
                 88 DIVISIBLE   VALUE 0.
           02 TEMP              PIC 9.
           02 RD                PIC 9 COMP.
           02 STATUS-FLAG       PIC X.
              88 OK             VALUE 'Y'.    
           02 SPECIAL-N         PIC ZZ9.           

        PROCEDURE DIVISION.
        BEGIN.
            PERFORM CHECK-SPECIAL-DIVISOR
                VARYING CANDIDATE FROM 1 BY 1
                UNTIL CANDIDATE IS EQUAL TO 200.
            STOP RUN.
        
        CHECK-SPECIAL-DIVISOR.
            MOVE CANDIDATE TO REVERSE.
            PERFORM REVERSE-NUMBER.
            MOVE REVERSE TO CAND-REV.
            DIVIDE CANDIDATE BY 2 GIVING DIVMAX.
            MOVE 'Y' TO STATUS-FLAG.
            PERFORM TRY-DIVISOR
                VARYING DIVISOR FROM 1 BY 1
                UNTIL DIVISOR IS GREATER THAN DIVMAX.
            IF OK
                MOVE CANDIDATE TO SPECIAL-N
                DISPLAY SPECIAL-N.
        
        TRY-DIVISOR.
            IF OK
                DIVIDE CANDIDATE BY DIVISOR GIVING DIVRSLT
                IF DIVISIBLE
                    MOVE DIVISOR TO REVERSE
                    PERFORM REVERSE-NUMBER
                    DIVIDE CAND-REV BY REVERSE GIVING DIVRSLT
                    IF NOT DIVISIBLE MOVE 'N' TO STATUS-FLAG.
        
        REVERSE-NUMBER.
            SET RD TO 1.
            INSPECT REVERSE TALLYING RD FOR LEADING '0'.
            MOVE REV-DIGITS(RD) TO TEMP.
            MOVE REV-DIGITS(3) TO REV-DIGITS(RD).
            MOVE TEMP TO REV-DIGITS(3).
Output:
  1
  2
  3
  4
  5
  6
  7
  8
  9
 11
 13
 17
 19
 22
 23
 26
 27
 29
 31
 33
 37
 39
 41
 43
 44
 46
 47
 53
 55
 59
 61
 62
 66
 67
 69
 71
 73
 77
 79
 82
 83
 86
 88
 89
 93
 97
 99
101
103
107
109
113
121
127
131
137
139
143
149
151
157
163
167
169
173
179
181
187
191
193
197
199

Cowgol

include "cowgol.coh";

const MAXIMUM := 200;
typedef N is int(0, MAXIMUM);

sub reverse(n: N): (r: N) is
    r := 0;
    while n != 0 loop
        r := r*10 + n%10;
        n := n/10;
    end loop;
end sub;

sub special(n: N): (r: uint8) is
    r := 0;
    var revn := reverse(n);
    var dsor: N := 1;
    while dsor <= n/2 loop
        if n % dsor == 0 and revn % reverse(dsor) != 0 then
            return;
        end if;
        dsor := dsor + 1;
    end loop;
    r := 1;
end sub; 

var n: N := 1;
while n < MAXIMUM loop
    if special(n) != 0 then
        print_i32(n as uint32);
        print_nl();
    end if;
    n := n + 1;
end loop;
Output:
1
2
3
4
5
6
7
8
9
11
13
17
19
22
23
26
27
29
31
33
37
39
41
43
44
46
47
53
55
59
61
62
66
67
69
71
73
77
79
82
83
86
88
89
93
97
99
101
103
107
109
113
121
127
131
137
139
149
151
157
163
167
173
179
181
191
193
197
199

Delphi

Translation of: Ring
program Special_Divisors;
{$IFDEF FPC}
  {$MODE DELPHI}
 uses
    SysUtils,
    StrUtils;
{$ELSE}
  {$APPTYPE CONSOLE}
 uses
    System.SysUtils,
    System.StrUtils;
{$ENDIF}

const
  limit1 = 200;

var
  row, num, revNum, revDiv: Integer;
  flag: boolean;

procedure Main();
var
  n,m: NativeUint;
begin
  writeln('Working...'#10);
  row := 0;
  num := 0;

  for n := 1 to limit1 do
  begin
    flag := True;
    revNum := reversestring(n.ToString).ToInteger;
    for m := 1 to n div 2 do
    begin
      revDiv := reversestring(m.ToString).ToInteger;
      if n mod m = 0 then
        if revNum mod revDiv = 0 then
          flag := True
        else
        begin
          flag := False;
          Break;
        end;
    end;

    if flag then
    begin
      inc(num);
      inc(row);
      write(n: 4);
      if row mod 10 = 0 then
        Writeln;
    end;
  end;

  writeln(#10#10'Found ', num,
    ' special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where  N  <  200');

  writeln('Done...');
end;

begin
  Main;
 {$IFNDEF UNIX} readln; {$ENDIF}
end.
Output:
Working...

   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

Found 72 special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where  N  <  200
Done...

Factor

Works with: Factor version 0.99 2021-02-05
USING: grouping kernel math.functions math.parser
math.primes.factors math.ranges prettyprint sequences ;

: reverse-number ( n -- reversed ) 10 >base reverse dec> ;

: special? ( n -- ? )
    [ reverse-number ] [ divisors ] bi
    [ reverse-number divisor? ] with all? ;

200 [1..b] [ special? ] filter 18 group simple-table.
Output:
1   2   3   4   5   6   7   8   9   11  13  17  19  22  23  26  27  29
31  33  37  39  41  43  44  46  47  53  55  59  61  62  66  67  69  71
73  77  79  82  83  86  88  89  93  97  99  101 103 107 109 113 121 127
131 137 139 143 149 151 157 163 167 169 173 179 181 187 191 193 197 199

Forth

Works with: Gforth
: reverse ( n -- n )
  0 >r
  begin
    dup 0 >
  while
    10 /mod swap
    r> 10 * + >r
  repeat
  drop r> ;

: special? ( n -- ? )
  dup reverse >r
  2
  begin
    2dup dup * >=
  while
    2dup mod 0= if
      dup reverse r@ swap mod 0 <> if
        rdrop 2drop false exit
      then
      2dup / dup 2 pick <> if
        reverse r@ swap mod 0 <> if
          rdrop 2drop false exit
        then
      else
        drop
      then
    then
    1+
  repeat
  rdrop 2drop true ;

: main
  0
  200 1 do
    i special? if
      i 3 .r
      1+
      dup 10 mod 0= if cr else space then
    then
  loop cr
  . ." numbers found." cr ;

main
bye
Output:
  1   2   3   4   5   6   7   8   9  11
 13  17  19  22  23  26  27  29  31  33
 37  39  41  43  44  46  47  53  55  59
 61  62  66  67  69  71  73  77  79  82
 83  86  88  89  93  97  99 101 103 107
109 113 121 127 131 137 139 143 149 151
157 163 167 169 173 179 181 187 191 193
197 199 
72 numbers found.

FreeBASIC

function reverse(n as integer) as integer
    dim as integer u = 0
    while n
        u = 10*u + n mod 10
        n\=10
    wend
    return u
end function

dim as integer n, u, d, b
dim as boolean s

for n = 1 to 200
    u = reverse(n)
    s = true
    for d = 1 to n
        if n mod d = 0 then
            b = reverse(d)
            if u mod b <> 0 then s = false
        end if
    next d
    if s then print using "### ";n;
next n

Go

Translation of: Wren
Library: Go-rcu
package main

import (
    "fmt"
    "rcu"
)

func reversed(n int) int {
    rev := 0
    for n > 0 {
        rev = rev*10 + n%10
        n = n / 10
    }
    return rev
}

func main() {
    var special []int
    for n := 1; n < 200; n++ {
        divs := rcu.Divisors(n)
        revN := reversed(n)
        all := true
        for _, d := range divs {
            if revN%reversed(d) != 0 {
                all = false
                break
            }
        }
        if all {
            special = append(special, n)
        }
    }
    fmt.Println("Special divisors in the range 0..199:")
    for i, n := range special {
        fmt.Printf("%3d ", n)
        if (i+1)%12 == 0 {
            fmt.Println()
        }
    }
    fmt.Printf("\n%d special divisors found.\n", len(special))
}
Output:
Special divisors in the range 0..199:
  1   2   3   4   5   6   7   8   9  11  13  17 
 19  22  23  26  27  29  31  33  37  39  41  43 
 44  46  47  53  55  59  61  62  66  67  69  71 
 73  77  79  82  83  86  88  89  93  97  99 101 
103 107 109 113 121 127 131 137 139 143 149 151 
157 163 167 169 173 179 181 187 191 193 197 199 

72 special divisors found.

J

([#~([:*./0=|.&.":"0@>:@I.@(0=>:@i.|])||.&.":)"0)>:i.200
Output:
1 2 3 4 5 6 7 8 9 11 13 17 19 22 23 26 27 29 31 33 37 39 41 43 44 46 47 53 55 59 61 62 66 67 69 71 73 77 79 82 83 86 88 89 93 97 99 101 103 107 109 113 121 127 131 137 139 143 149 151 157 163 167 169 173 179 181 187 191 193 197 199

jq

Works with: jq

Works with gojq, the Go implementation of jq

# divisors as an unsorted stream
def divisors:
  if . == 1 then 1
  else . as $n
  | label $out
  | range(1; $n) as $i
  | ($i * $i) as $i2
  | if $i2 > $n then break $out
    else if $i2 == $n then $i
         elif ($n % $i) == 0 then $i, ($n/$i)
         else empty
	 end
    end
  end;

def is_special_divisor:
  def reverse_number: tostring|explode|reverse|implode|tonumber;
  reverse_number as $nreverse
  | all(divisors; $nreverse % reverse_number == 0);

range(1;200) | select(is_special_divisor)
Output:

A stream of numbers as shown elsewhere on this page.

Julia

using Primes

function divisors(n)
    f = [one(n)]
    for (p,e) in factor(n)
        f = reduce(vcat, [f*p^j for j in 1:e], init=f)
    end
    return f[1:end-1]
end

function isspecialdivisor(n)::Bool
    isprime(n) && return true
    nreverse = evalpoly(10, reverse(digits(n)))
    for d in divisors(n)
        dreverse = evalpoly(10, reverse(digits(d)))
        !(nreverse ÷ dreverse  nreverse / dreverse) && return false
    end
    return true
end

const specials = filter(isspecialdivisor, 1:200)
foreach(p -> print(rpad(p[2], 4), p[1] % 18 == 0 ? "\n" : ""), enumerate(specials))
Output:
1   2   3   4   5   6   7   8   9   11  13  17  19  22  23  26  27  29
31  33  37  39  41  43  44  46  47  53  55  59  61  62  66  67  69  71
73  77  79  82  83  86  88  89  93  97  99  101 103 107 109 113 121 127
131 137 139 143 149 151 157 163 167 169 173 179 181 187 191 193 197 199

MAD

            NORMAL MODE IS INTEGER
            
            INTERNAL FUNCTION(X)
            ENTRY TO RVRSE.
            XR = X
            RR = 0
LOOP        WHENEVER XR.E.0, FUNCTION RETURN RR
            XD = XR/10
            RR = RR*10 + XR-XD*10
            XR = XD
            TRANSFER TO LOOP
            END OF FUNCTION
            
            THROUGH CAND, FOR N=1, 1, N.GE.200
            RN = RVRSE.(N)
            THROUGH DIVS, FOR D=1, 1, D.G.N/2
            RD = RVRSE.(D)
DIVS        WHENEVER N/D*D.E.N .AND. RN/RD*RD.NE.RN, TRANSFER TO CAND
            PRINT FORMAT FMT,N
CAND        CONTINUE             
            VECTOR VALUES FMT = $I4*$
            END OF PROGRAM
Output:
   1
   2
   3
   4
   5
   6
   7
   8
   9
  11
  13
  17
  19
  22
  23
  26
  27
  29
  31
  33
  37
  39
  41
  43
  44
  46
  47
  53
  55
  59
  61
  62
  66
  67
  69
  71
  73
  77
  79
  82
  83
  86
  88
  89
  93
  97
  99
 101
 103
 107
 109
 113
 121
 127
 131
 137
 139
 143
 149
 151
 157
 163
 167
 169
 173
 179
 181
 187
 191
 193
 197
 199

Mathematica/Wolfram Language

SpecialDivisorQ[n_Integer] := AllTrue[Divisors[n], Divisible[IntegerReverse[n], IntegerReverse[#]] &]
Select[Range[199], SpecialDivisorQ]
Length[%]
Output:
{1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 13, 17, 19, 22, 23, 26, 27, 29, 31, 33, 37, 39, 41, 43, 44, 46, 47, 53, 55, 59, 61, 62, 66, 67, 69, 71, 73, 77, 79, 82, 83, 86, 88, 89, 93, 97, 99, 101, 103, 107, 109, 113, 121, 127, 131, 137, 139, 143, 149, 151, 157, 163, 167, 169, 173, 179, 181, 187, 191, 193, 197, 199}
72

Modula-2

MODULE SpecialDivisors;
FROM InOut IMPORT WriteCard, WriteLn;

CONST Max = 200;
VAR n, col: CARDINAL;

PROCEDURE Reverse(n: CARDINAL): CARDINAL;
VAR result: CARDINAL;
BEGIN
    result := 0;
    WHILE n > 0 DO
        result := result*10 + n MOD 10;
        n := n DIV 10;
    END;
    RETURN result;
END Reverse;

PROCEDURE Special(n: CARDINAL): BOOLEAN;
VAR reverse, divisor: CARDINAL;
BEGIN
    reverse := Reverse(n);
    FOR divisor := 1 TO n DIV 2 DO
        IF (n MOD divisor = 0) AND (reverse MOD Reverse(divisor) # 0) THEN
            RETURN FALSE;
        END;
    END;
    RETURN TRUE;
END Special;

BEGIN
    col := 0;
    FOR n := 1 TO Max DO
        IF Special(n) THEN
            WriteCard(n, 4);
            col := col + 1;
            IF col MOD 10 = 0 THEN
                WriteLn();
            END;
        END;
    END;
    WriteLn();
END SpecialDivisors.
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

Nim

import strutils

func reversed(n: Positive): int =
  var n = n.int
  while n != 0:
    result = 10 * result + n mod 10
    n = n div 10

func divisors(n: Positive): seq[int] =
  result = @[1, n]
  var d = 2
  while d * d <= n:
    if n mod d == 0:
      result.add d
      if d * d != n:
        result.add n div d
    inc d

var count = 0
for n in 1..<200:
  let revn = reversed(n)
  block check:
    for d in divisors(n):
      if revn mod reversed(d) != 0:
        break check
    inc count
    stdout.write ($n).align(3), if count mod 12 == 0: '\n' else: ' '
Output:
  1   2   3   4   5   6   7   8   9  11  13  17
 19  22  23  26  27  29  31  33  37  39  41  43
 44  46  47  53  55  59  61  62  66  67  69  71
 73  77  79  82  83  86  88  89  93  97  99 101
103 107 109 113 121 127 131 137 139 143 149 151
157 163 167 169 173 179 181 187 191 193 197 199

Pascal

see http://rosettacode.org/wiki/Special_Divisors#Delphi%7CDelphi

Perl

Library: ntheory
use strict;
use warnings;
use feature 'say';
use ntheory 'divisors';

my @sd;
for my $n (1..199) {
    map { next if $_ != int $_ } map { reverse($n) / reverse $_ } divisors $n;
    push @sd, $n;
}

say @sd . " matching numbers:\n" .
    (sprintf "@{['%4d' x @sd]}", @sd) =~ s/(.{40})/$1\n/gr;
Output:
72 matching numbers:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

Phix

function rev(integer n)
    integer r = 0
    while n do
        r = r*10+remainder(n,10)
        n = floor(n/10)
    end while
    return r
end function

function special_divisors(integer n)
    sequence fn = factors(n)
    if length(fn) then
        integer rn = rev(n)
        for i=1 to length(fn) do
            if remainder(rn,rev(fn[i])) then return false end if
        end for
    end if
    return true
end function

sequence res = apply(true,sprintf,{{"%3d"},filter(tagset(200),special_divisors)})
printf(1,"Found %d special divisors:\n%s\n",{length(res),join_by(res,1,18)})
Output:
Found 72 special divisors:
  1     2     3     4     5     6     7     8     9    11    13    17    19    22    23    26    27    29
 31    33    37    39    41    43    44    46    47    53    55    59    61    62    66    67    69    71
 73    77    79    82    83    86    88    89    93    97    99   101   103   107   109   113   121   127
131   137   139   143   149   151   157   163   167   169   173   179   181   187   191   193   197   199

PILOT

C :max=200
  :n=1
*num
C :x=n
U :*rev
C :rn=r
  :d=1
*div
J (d*(n/d)<>n):*nextdiv
C :x=d
U :*rev
J (r*(rn/r)<>rn):*next
*nextdiv
C :d=d+1
J (d<=n/2):*div
T :#n
*next
C :n=n+1
J (n<max):*num
E :
*rev
C :r=0
  :a=x
*revloop
C :b=a/10
  :r=r+(a-b*10)
  :a=b
J (a>0):*revloop
E :
Output:
1
2
3
4
5
6
7
8
9
11
13
17
19
22
23
26
27
29
31
33
37
39
41
43
44
46
47
53
55
59
61
62
66
67
69
71
73
77
79
81
82
83
86
88
89
93
97
99
101
103
107
109
113
121
127
131
137
139
143
149
151
157
163
167
169
173
179
181
187
191
193
197
199

PL/I

specialDivisors: procedure options(main);
    %replace MAX by 200;

    reverse: procedure(nn) returns(fixed);
        declare (r, n, nn) fixed;
        r = 0;
        do n=nn repeat(n/10) while(n > 0);
            r = r*10 + mod(n, 10);
        end;
        return(r);
    end reverse;
    
    isSpecial: procedure(n) returns(bit);
        declare (n, rev, div) fixed;
        rev = reverse(n);
        do div=1 to n/2;
            if mod(n, div)=0 & mod(rev, reverse(div))^=0 then
                return('0'b);
        end;
        return('1'b);
    end isSpecial;
    
    declare (cand, col) fixed;
    col = 0;
    do cand=1 to MAX;
        if isSpecial(cand) then do;
            put edit(cand) (F(4));
            col = col+1;
            if mod(col, 10)=0 then put skip;
        end;
    end;
end specialDivisors;
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199

See also #Polyglot:PL/I and PL/M

PL/M

Works with: 8080 PL/M Compiler
... under CP/M (or an emulator)
100H: /* FIND NUMBERS WHOSE REVERSED DIVISORS DIVIDE THE REVERSED NUMBER    */

   DECLARE TRUE    LITERALLY '0FFH';
   DECLARE FALSE   LITERALLY '0';

   BDOS: PROCEDURE( FN, ARG ); /* CP/M BDOS SYSTEM CALL */
      DECLARE FN BYTE, ARG ADDRESS;
      GOTO 5;
   END BDOS;
   PRINT$CHAR:   PROCEDURE( C ); DECLARE C BYTE;    CALL BDOS( 2, C ); END;
   PRINT$STRING: PROCEDURE( S ); DECLARE S ADDRESS; CALL BDOS( 9, S ); END;
   PRINT$NL:     PROCEDURE; CALL PRINT$STRING( .( 0DH, 0AH, '$' ) );   END;
   PRINT$NUMBER: PROCEDURE( N );
      DECLARE N ADDRESS;
      DECLARE V ADDRESS, N$STR( 6 ) BYTE, W BYTE;
      V = N;
      W = LAST( N$STR );
      N$STR( W ) = '$';
      N$STR( W := W - 1 ) = '0' + ( V MOD 10 );
      DO WHILE( ( V := V / 10 ) > 0 );
         N$STR( W := W - 1 ) = '0' + ( V MOD 10 );
      END;
      CALL PRINT$STRING( .N$STR( W ) );
   END PRINT$NUMBER;

   REVERSE: PROCEDURE( N )ADDRESS;  /* RETURNS THE REVERSED DIGITS OF N */
      DECLARE N ADDRESS;
      DECLARE ( R, V ) ADDRESS;
      V = N;
      R = V MOD 10;
      DO WHILE( ( V := V / 10 ) > 0 );
         R = ( R * 10 ) + ( V MOD 10 );
      END;
      RETURN R;
   END REVERSE ;

   /* FIND AND SHOW THE NUMBERS UP TO 200 */
   DECLARE MAX$SD LITERALLY '199';
   DECLARE ( N, RN, SD$COUNT, D, D$MAX ) ADDRESS;
   DECLARE IS$SD BYTE;
   SD$COUNT = 0;
   DO N = 1 TO MAX$SD;
      RN = REVERSE( N );
      IS$SD = TRUE;
      D = 2; D$MAX = N / 2;
      DO WHILE( IS$SD AND D < D$MAX );
         IF N MOD D = 0 THEN DO;
            /* HAVE A DIVISOR OF N */
            IS$SD = ( RN MOD REVERSE( D ) = 0 );
         END;
         D = D + 1;
      END;
      IF IS$SD THEN DO;
         /* ALL THE REVERSED DIVISORS OF N DIVIDE N REVERSED */
         CALL PRINT$CHAR( ' ' );
         IF N < 100 THEN DO;
            CALL PRINT$CHAR( ' ' );
            IF N < 10 THEN CALL PRINT$CHAR( ' ' );
         END;
         CALL PRINT$NUMBER( N );
         IF ( SD$COUNT := SD$COUNT + 1 ) MOD 10 = 0 THEN CALL PRINT$NL;
      END;
   END;
   CALL PRINT$NL;
   CALL PRINT$STRING( .'FOUND $' );
   CALL PRINT$NUMBER( SD$COUNT );
   CALL PRINT$STRING( .' ''''SPECIAL DIVISORS'''' BELOW $' );
   CALL PRINT$NUMBER( MAX$SD + 1 );
   CALL PRINT$NL;
EOF
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199
FOUND 72 ''SPECIAL DIVISORS'' BELOW 200

See also #Polyglot:PL/I and PL/M

Polyglot:PL/I and PL/M

Works with: 8080 PL/M Compiler
... under CP/M (or an emulator)

Should work with many PL/I implementations.
The PL/I include file "pg.inc" can be found on the Polyglot:PL/I and PL/M page. Note the use of text in column 81 onwards to hide the PL/I specifics from the PL/M compiler.

/* FIND NUMBERS WHOSE REVERSED DIVISORS DIVIDE THE REVERSED NUMBER    */
special_divisors_100H: procedure options                                        (main);

/* PL/I DEFINITIONS                                                             */
%include 'pg.inc';
/* PL/M DEFINITIONS: CP/M BDOS SYSTEM CALL AND CONSOLE I/O ROUTINES, ETC. */    /*
   DECLARE BINARY LITERALLY 'ADDRESS', CHARACTER LITERALLY 'BYTE';
   DECLARE SADDR  LITERALLY '.',       BIT       LITERALLY 'BYTE';
   DECLARE TRUE   LITERALLY '1',       FALSE     LITERALLY '0';
   BDOSF: PROCEDURE( FN, ARG )BYTE;
                               DECLARE FN BYTE, ARG ADDRESS; GOTO 5;   END; 
   BDOS: PROCEDURE( FN, ARG ); DECLARE FN BYTE, ARG ADDRESS; GOTO 5;   END;
   PRSTRING: PROCEDURE( S );   DECLARE S ADDRESS;   CALL BDOS( 9, S ); END;
   PRCHAR:   PROCEDURE( C );   DECLARE C CHARACTER; CALL BDOS( 2, C ); END;
   PRNL:     PROCEDURE;        CALL PRCHAR( 0DH ); CALL PRCHAR( 0AH ); END;
   PRNUMBER: PROCEDURE( N );
      DECLARE N ADDRESS;
      DECLARE V ADDRESS, N$STR( 6 ) BYTE, W BYTE;
      N$STR( W := LAST( N$STR ) ) = '$';
      N$STR( W := W - 1 ) = '0' + ( ( V := N ) MOD 10 );
      DO WHILE( ( V := V / 10 ) > 0 );
         N$STR( W := W - 1 ) = '0' + ( V MOD 10 );
      END; 
      CALL BDOS( 9, .N$STR( W ) );
   END PRNUMBER;
   MODF: PROCEDURE( A, B )ADDRESS;
      DECLARE ( A, B )ADDRESS;
      RETURN( A MOD B );
   END MODF;
/* END LANGUAGE DEFINITIONS */

   /* TASK */

   REVERSE: PROCEDURE( N )returns                                               (
                          BINARY                                                )
                          ;  /* RETURNS THE REVERSED DIGITS OF N */
      DECLARE N BINARY;
      DECLARE ( R, V ) BINARY;
      V = N;
      R = MODF( V, 10 );
      V = V / 10;
      DO WHILE( V > 0 );
         R = ( R * 10 ) + MODF( V, 10 );
         V = V / 10;
      END;
      RETURN ( R );
   END REVERSE ;

   /* FIND AND SHOW THE NUMBERS UP TO 200 */
   DECLARE ( N, RN, SDCOUNT, D, DMAX ) BINARY;
   DECLARE ISSD BIT;
   DECLARE MAXSD BINARY static INITIAL( 199 );
   SDCOUNT = 0;
   DO N = 1 TO MAXSD;
      RN = REVERSE( N );
      ISSD = TRUE;
      D = 2; DMAX = N / 2;
      DO WHILE( ISSD &                                                          /*
                AND /* */ D < DMAX );
         IF MODF( N, D ) = 0 THEN DO;
            /* HAVE A DIVISOR OF N */
            ISSD = ( MODF( RN, REVERSE( D ) ) = 0 );
         END;
         D = D + 1;
      END;
      IF ISSD THEN DO;
         /* ALL THE REVERSED DIVISORS OF N DIVIDE N REVERSED */
         CALL PRCHAR( ' ' );
         IF N < 100 THEN DO;
            CALL PRCHAR( ' ' );
            IF N < 10 THEN CALL PRCHAR( ' ' );
         END;
         CALL PRNUMBER( N );
         SDCOUNT = SDCOUNT + 1;
         IF MODF( SDCOUNT, 10 ) = 0 THEN CALL PRNL;
      END;
   END;
   CALL PRNL;
   CALL PRSTRING( SADDR( 'FOUND $' ) );
   CALL PRNUMBER( SDCOUNT );
   CALL PRSTRING( SADDR( ' ''''SPECIAL DIVISORS'''' BELOW $' ) );
   CALL PRNUMBER( MAXSD + 1 );
   CALL PRNL;

EOF: end special_divisors_100H;
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199
FOUND 72 ''SPECIAL DIVISORS'' BELOW 200

PureBasic

Procedure reverse(n.i)
  u.i = 0
  While n
    u = u * 10 + (n % 10)
    n = Int(n / 10)
  Wend
  ProcedureReturn u
EndProcedure

OpenConsole()
c.i = 0
For n.i = 1 To 200
  u.i = reverse(n)
  s.b = #True
  For d.i = 1 To n
    If n % d = 0
      b = reverse(d)
      If u % b <> 0
        s = #False
      EndIf
    EndIf
  Next d
  If s 
    Print(Str(n) + #TAB$)
    c + 1 
  EndIf
Next n

PrintN(#CRLF$ + "Found " + Str(c) + " special divisors.")
Input()
CloseConsole()
Output:
1       2       3       4       5       6       7       8       9       11      13      17      19      22      23
        26      27      29      31      33      37      39      41      43      44      46      47      53      55
        59      61      62      66      67      69      71      73      77      79      82      83      86      88
        89      93      97      99      101     103     107     109     113     121     127     131     137     139
        143     149     151     157     163     167     169     173     179     181     187     191     193     197
        199
Found 72 special divisors.

Python

#!/usr/bin/python

def reverse(n):
    u = 0
    while n:
        u = 10 * u + n % 10
        n = int(n / 10)
    return u

c = 0
for n in range(1, 200):
    u = reverse(n)
    s = True
    
    for d in range (1, n):
        if n % d == 0:
            b = reverse(d)
            if u % b != 0:
                s = False
    if s:
        c = c + 1
        print(n, end='\t')
                
print("\nEncontrados ", c, "divisores especiales.")
Output:
1	2	3	4	5	6	7	8	9	11	13	17	19	22	23	26	27	29	31	33	37	39	41	43	44	46	47	53	55	59	61	62	66	67	69	71	73	77	79	82	83	86	88	89	93	97	99	101	103	107	109	113	121	127	131	137	139	143	149	151	157	163	167	169	173	179	181	187	191	193	197	199	
Encontrados  72 divisores especiales.

Quackery

factors is defined at Factors of an integer#Quackery.

  [ 0
    [ swap 10 /mod
      rot 10 * +
      over 0 = until ]
    nip ]              is revnum ( n --> n )

  []
  [ 200 times
      [ true
        i^ revnum
        i^ factors
        witheach
          [ revnum
            dip dup mod
            0 != if
              [ dip not
                conclude ] ]
        drop
        if [ i^ join ] ]
    behead drop ]
  []
  swap witheach
    [ number$ nested join ]
  48 wrap$
Output:
1 2 3 4 5 6 7 8 9 11 13 17 19 22 23 26 27 29 31
33 37 39 41 43 44 46 47 53 55 59 61 62 66 67 69
71 73 77 79 82 83 86 88 89 93 97 99 101 103 107
109 113 121 127 131 137 139 143 149 151 157 163
167 169 173 179 181 187 191 193 197 199

Raku

use Prime::Factor:ver<0.3.0+>;

say "{+$_} matching numbers:\n{.batch(10)».fmt('%3d').join: "\n"}"
    given (1..^200).grep: { all .flip «%%« .&divisors».flip };
Output:
72 matching numbers:
  1   2   3   4   5   6   7   8   9  11
 13  17  19  22  23  26  27  29  31  33
 37  39  41  43  44  46  47  53  55  59
 61  62  66  67  69  71  73  77  79  82
 83  86  88  89  93  97  99 101 103 107
109 113 121 127 131 137 139 143 149 151
157 163 167 169 173 179 181 187 191 193
197 199

REXX

/*REXX program finds special divisors:   numbers  N  such that  reverse(D)  divides ··· */
/*────────────────────────── reverse(N)  for all divisors  D  of  N,  where  N  <  200. */
parse arg hi cols .                              /*obtain optional argument from the CL.*/
if   hi=='' |   hi==","  then   hi=  200         /* "      "         "   "   "     "    */
if cols=='' | cols==","  then cols=   10         /* "      "         "   "   "     "    */
w= 10                                            /*width of a number in any column.     */
title= ' special divisors  N  that reverse(D) divides reverse(N) for all divisors'  ,
       ' D  of  N,   where  N  < '    hi
if cols>0  then say ' index │'center(title,     1 + cols*(w+1)     )
if cols>0  then say '───────┼'center(""  ,      1 + cols*(w+1), '─')
found= 0;                   idx= 1               /*initialize # found numbers and index.*/
$=                                               /*a list of numbers found  (so far).   */
     do j=1  for  hi-1;     r= reverse(j)        /*search for special divisors.         */
                    do k=2  to j%2               /*skip the first divisor (unity) & last*/
                    if j//k==0  then if r//reverse(k)\==0  then iterate J /*Not OK? Skip*/
                    end   /*m*/
     found= found+1                              /*bump the number of special divisors. */
     if cols<0              then iterate         /*Build the list  (to be shown later)? */
     $= $ right(j, w)                            /*add a special divisor ──► the $ list.*/
     if found//cols\==0     then iterate         /*have we populated a line of output?  */
     say center(idx, 7)'│'  substr($, 2);    $=  /*display what we have so far  (cols). */
     idx= idx + cols                             /*bump the  index  count for the output*/
     end   /*j*/

if $\==''  then say center(idx, 7)"│"  substr($, 2)  /*possible display residual output.*/
if cols>0  then say '───────┴'center(""  ,      1 + cols*(w+1), '─')
say
say 'Found '      found         title
output   when using the default inputs:
 index │    special divisors  N  that reverse(D) divides reverse(N) for all divisors  D  of  N,   where  N  <  200
───────┼───────────────────────────────────────────────────────────────────────────────────────────────────────────────
   1   │          1          2          3          4          5          6          7          8          9         11
  11   │         13         17         19         22         23         26         27         29         31         33
  21   │         37         39         41         43         44         46         47         53         55         59
  31   │         61         62         66         67         69         71         73         77         79         82
  41   │         83         86         88         89         93         97         99        101        103        107
  51   │        109        113        121        127        131        137        139        143        149        151
  61   │        157        163        167        169        173        179        181        187        191        193
  71   │        197        199
───────┴───────────────────────────────────────────────────────────────────────────────────────────────────────────────

Found  72  special divisors  N  that reverse(D) divides reverse(N) for all divisors  D  of  N,   where  N  <  200

Ring

load "stdlib.ring"

see "working..." + nl

row = 0
num = 0
limit1 = 200

for n = 1 to limit1
    flag = 1
    revNum = rever(string(n))
    revNum = number(revNum)
    for m = 1 to n/2
        revDiv = rever(String(m))
        revDiv = number(revDiv)
        if n%m = 0
           if revNum % revDiv = 0
              flag = 1
           else
              flag = 0
              exit
           ok
        ok
    next 
    if flag = 1
       num = num + 1
       row = row + 1
       see "" + n + " "
       if row%10 = 0
          see nl
       ok
    ok
next

see nl + "Found " + num + " special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where  N  <  200" + nl
see "done..." + nl 

func rever(str)
     rev = ""
     for n = len(str) to 1 step -1
         rev = rev + str[n]
     next
     return rev
Output:
working...
1 2 3 4 5 6 7 8 9 11 
13 17 19 22 23 26 27 29 31 33 
37 39 41 43 44 46 47 53 55 59 
61 62 66 67 69 71 73 77 79 82 
83 86 88 89 93 97 99 101 103 107 
109 113 121 127 131 137 139 143 149 151 
157 163 167 169 173 179 181 187 191 193 
197 199 
Found 72 special divisors N that reverse(D) divides reverse(N) for all divisors D of N, where  N  <  200
done...

RPL

Works with: HP version 49
≪ →STR ""
   OVER SIZE 1 FOR j 
      OVER j DUP SUB +
  -1 STEP 
  STR→ NIP
≫ 'REVNUM' STO

≪ {1}
   2 200 FOR n
      1 SF
      n REVNUM n DIVIS
      2 OVER SIZE 1 - FOR d
         IF DUP2 d GET REVNUM MOD THEN
            1 CF DUP SIZE 'd' STO END
      NEXT DROP2
      IF 1 FS? THEN n + END
   NEXT
≫ 'TASK' STO
Output:
1: {1 2 3 4 5 6 7 8 9 11 13 17 19 22 23 26 27 29 31 33 37 39 41 43 44 46 47 53 55 59 61 62 66 67 69 71 73 77 79 82 83 86 88 89 93 97 99 101 103 107 109 113 121 127 131 137 139 143 149 151 157 163 167 169 173 179 181 187 191 193 197 199}

Runs in 62 seconds on a HP-50g.

Ruby

class Integer
  def reverse 
    to_s.reverse.to_i
  end
  def divisors
      res = []
      (1..Integer.sqrt(self)).each do |cand|
        div, mod = self.divmod(cand)
        res << cand << div if mod == 0
      end
      res.uniq.sort
  end
  def special_divisors?
    r = self.reverse
    divisors.all?{|d| r % d.reverse == 0}
  end
end

p (1..200).select(&:special_divisors?)
Output:
[1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 13, 17, 19, 22, 23, 26, 27, 29, 31, 33, 37, 39, 41, 43, 44, 46, 47, 53, 55, 59, 61, 62, 66, 67, 69, 71, 73, 77, 79, 82, 83, 86, 88, 89, 93, 97, 99, 101, 103, 107, 109, 113, 121, 127, 131, 137, 139, 143, 149, 151, 157, 163, 167, 169, 173, 179, 181, 187, 191, 193, 197, 199]

Sidef

1..200 -> grep {|n| n.divisors.all {|d| d.flip `divides` n.flip } }.say
Output:
[1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 13, 17, 19, 22, 23, 26, 27, 29, 31, 33, 37, 39, 41, 43, 44, 46, 47, 53, 55, 59, 61, 62, 66, 67, 69, 71, 73, 77, 79, 82, 83, 86, 88, 89, 93, 97, 99, 101, 103, 107, 109, 113, 121, 127, 131, 137, 139, 143, 149, 151, 157, 163, 167, 169, 173, 179, 181, 187, 191, 193, 197, 199]

Swift

import Foundation

func reverse(_ number: Int) -> Int {
    var rev = 0
    var n = number
    while n > 0 {
        rev = rev * 10 + n % 10
        n /= 10
    }
    return rev
}

func special(_ number: Int) -> Bool {
    var n = 2
    let rev = reverse(number)
    while n * n <= number {
        if number % n == 0 {
            if rev % reverse(n) != 0 {
                return false
            }
            let m = number / n
            if m != n && rev % reverse(m) != 0 {
                return false
            }
        }
        n += 1
    }
    return true
}

var count = 0
for n in 1..<200 {
    if special(n) {
        count += 1
        print(String(format: "%3d", n),
              terminator: count % 10 == 0 ? "\n" : " ")
    }
}
print("\n\(count) numbers found.")
Output:
  1   2   3   4   5   6   7   8   9  11
 13  17  19  22  23  26  27  29  31  33
 37  39  41  43  44  46  47  53  55  59
 61  62  66  67  69  71  73  77  79  82
 83  86  88  89  93  97  99 101 103 107
109 113 121 127 131 137 139 143 149 151
157 163 167 169 173 179 181 187 191 193
197 199 
72 numbers found.

Wren

Library: Wren-math
Library: Wren-fmt
import "./math" for Int
import "./fmt" for Fmt

var reversed = Fn.new { |n|
    var rev = 0
    while (n > 0) {
        rev = rev * 10 + n % 10
        n = (n/10).floor
    }
    return rev
}

var special = []
for (n in 1...200) {
    var divs = Int.divisors(n)
    var revN = reversed.call(n)
    if (divs.all { |d| revN % reversed.call(d) == 0 }) special.add(n)
}
System.print("Special divisors in the range 0..199:")
Fmt.tprint("$3d", special, 12)
System.print("\n%(special.count) special divisors found.")
Output:
Special divisors in the range 0..199:
  1   2   3   4   5   6   7   8   9  11  13  17
 19  22  23  26  27  29  31  33  37  39  41  43
 44  46  47  53  55  59  61  62  66  67  69  71
 73  77  79  82  83  86  88  89  93  97  99 101
103 107 109 113 121 127 131 137 139 143 149 151
157 163 167 169 173 179 181 187 191 193 197 199

72 special divisors found.

XPL0

func Reverse(N);        \Reverse the order of the digits
int  N, M;
[M:= 0;
repeat  N:= N/10;
        M:= M*10 + rem(0);
until   N = 0;
return M;
];

func Test(N);
\Return 'true' if reverse(D) divides reverse(N) for all divisors D of N
int  N, D, RevNum, RevDiv;
[RevNum:= Reverse(N);
for D:= 1 to N/2 do
    if rem(N/D) = 0 then
        [RevDiv:= Reverse(D);
        if rem(RevNum/RevDiv) then return false;
        ];
return true;
];

int Count, N;
[Count:= 0;
for N:= 1 to 199 do
    [if Test(N) then
        [IntOut(0, N);
        Count:= Count+1;
        if rem(Count/10) = 0 then CrLf(0) else ChOut(0, 9\tab\);
        ];
    ];
CrLf(0);
IntOut(0, Count);
Text(0, " such numbers found.");
]
Output:
1       2       3       4       5       6       7       8       9       11
13      17      19      22      23      26      27      29      31      33
37      39      41      43      44      46      47      53      55      59
61      62      66      67      69      71      73      77      79      82
83      86      88      89      93      97      99      101     103     107
109     113     121     127     131     137     139     143     149     151
157     163     167     169     173     179     181     187     191     193
197     199     
72 such numbers found.

Yabasic

Translation of: BASIC
// Rosetta Code problem: http://rosettacode.org/wiki/Special_divisors
// by Galileo, 04/2022

20 FOR I=1 TO 199
30 J=I: X=0
40 IF J>0 X=X*10+MOD(J, 10): J=INT(J/10): GOTO 40
50 FOR J=1 TO INT(I/2)
60 IF MOD(I, J) GOTO 100
70 K=J: Y=0
80 IF K>0 Y=Y*10+MOD(K, 10): K=INT(K/10): GOTO 80
90 IF MOD(X, Y) GOTO 120
100 NEXT J
110 PRINT I,
120 NEXT I
Output:
1       2       3       4       5       6       7       8       9       11      13      17      19      22      23      26      27      29      31      33      37      39      41      43      44      46      47      53      55      59      61      62      66      67      69      71      73      77      79      82      83      86      88      89      93      97      99      101     103     107     109     113     121     127     131     137     139     143     149     151     157     163     167     169     173     179     181     187     191     193     197     199     ---Program done, press RETURN---

Zig

const MAX = 200;  // max number to check
const N = u16;    // smallest integer type that fits

pub fn reverse(n: N) N {
    var r: N = 0;
    var nn = n;
    while (nn > 0) : (nn /= 10)
        r = r*10 + nn%10;
    return r;
}

pub fn special(n: N) bool {
    var r = reverse(n);
    var d: N = 1;
    while (d <= n/2) : (d += 1)
        if (n % d == 0 and r % reverse(d) != 0)
            return false;
    return true;
}

pub fn main() !void {
    const stdout = @import("std").io.getStdOut().writer();

    var c: N = 0;
    var n: N = 1;
    while (n <= MAX) : (n += 1) {
        if (special(n)) {
            try stdout.print("{d:4}", .{n});
            c += 1;
            if (c % 10 == 0) try stdout.print("\n", .{});
        }
    }
    try stdout.print("\n", .{});
}
Output:
   1   2   3   4   5   6   7   8   9  11
  13  17  19  22  23  26  27  29  31  33
  37  39  41  43  44  46  47  53  55  59
  61  62  66  67  69  71  73  77  79  82
  83  86  88  89  93  97  99 101 103 107
 109 113 121 127 131 137 139 143 149 151
 157 163 167 169 173 179 181 187 191 193
 197 199