Numbers divisible by their individual digits, but not by the product of their digits.

From Rosetta Code
Numbers divisible by their individual digits, but not by the product of their digits. 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

Find and show positive decimal integers divisible by their individual digits,   but not divisible by the product of their digits,
where   n   <   1,000

11l

Translation of: Python
F p(n)
   ‘True if n is divisible by each of its digits,
    but not divisible by the product of those digits.
   ’
   V digits = String(n).map(c -> Int(c))
   R !(0 C digits) & (0 != (n % product(digits))) & all(digits.map(d -> 0 == @n % d))

F chunksOf(n)
   ‘A series of lists of length n, subdividing the
    contents of xs. Where the length of xs is not evenly
    divible, the final list will be shorter than n.
   ’
   F go(xs)
      R ((0 .< xs.len).step(@=n).map(i -> @xs[i .< @=n + i]))
   R go

V xs = (1..999).filter(n -> p(n)).map(String)
V w = xs.last.len
print(xs.len" matching numbers:\n")
print(chunksOf(10)(xs).map(row -> row.map(cell -> cell.rjust(:w, ‘ ’)).join(‘ ’)).join("\n"))
Output:
45 matching numbers:

 22  33  44  48  55  66  77  88  99 122
124 126 155 162 168 184 222 244 248 264
288 324 333 336 366 396 412 424 444 448
488 515 555 636 648 666 728 777 784 824
848 864 888 936 999

8086 Assembly

	cpu	8086
	org	100h
section	.text
	mov	si,1		; Current number
number:	mov	bp,1		; BP holds product
	mov	di,si		; DI holds number
digit:	mov	ax,di		; Get digit
	xor	dx,dx
	mov	cx,10
	div	cx
	mov	di,ax		; Store remaining digits in DI
	test	dx,dx		; Is the digit zero?
	jz	next		; Then this number is not valid
	mov	cx,dx		; Is the number divisible by the digit?
	xor	dx,dx
	mov	ax,si
	div	cx 
	test	dx,dx
	jnz	next		; If not, this number is not valid
	mov	ax,bp		; Otherwise, multiply digit into product
	mul	cx
	mov	bp,ax
	test	di,di		; More digits?
	jnz	digit		; If so, do next digit
	mov	ax,si		; Is the number divisible by the product?
	xor	dx,dx
	div	bp
	test	dx,dx
	jz	next		; If so, this number is not valid
	mov	ax,si		; Otherwise, print the number
	call	prnum
next:	inc	si		; Next number
	cmp 	si,1000		; Are we there yet?
	jne	number		; If not, do the next number
	ret 			; But if so, stop
	;;;	Print number in AX
prnum:	mov	bx,dbuf		; Start of buffer
	mov	cx,10		; Divisor
.dgt:	xor	dx,dx		; Divide by 10
	div	cx
	add	dl,'0'		; Make ASCII digit
	dec	bx
	mov	[bx],dl		; Store digit
	test	ax,ax		; Any more digits remaining?
	jnz	.dgt		; If so, next digits
	mov	dx,bx		; Print string using MS-DOS
	mov	ah,9
	int	21h
	ret
section	.data
	db	'*****'
dbuf:	db	13,10,'$'
Output:
22
33
44
48
55
66
77
88
99
122
124
126
155
162
168
184
222
244
248
264
288
324
333
336
366
396
412
424
444
448
488
515
555
636
648
666
728
777
784
824
848
864
888
936
999

Action!

BYTE FUNC Check(INT x)
  BYTE d
  INT tmp,prod

  prod=1 tmp=x
  WHILE tmp#0
  DO
    d=tmp MOD 10
    IF x MOD d#0 THEN
      RETURN (0)
    FI
    tmp==/10
    prod==*d
  OD
  IF x MOD prod=0 THEN
    RETURN (0)
  FI
RETURN (1)

PROC Main()
  INT i

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

Screenshot from Atari 8-bit computer

22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336
366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

Ada

with Ada.Text_Io;
with Ada.Integer_Text_Io;

procedure Numbers_Divisible is

   function Is_Divisible (N : Natural) return Boolean is

      function To_Decimal (C : Character) return Natural
      is ( Character'Pos (C) - Character'Pos ('0'));

      Image : constant String := N'Image;
      Digit : Natural;
      Prod  : Natural := 1;
   begin
      for A in Image'First + 1 .. Image'Last loop
         Digit := To_Decimal (Image (A));
         if Digit = 0 then
            return False;
         end if;
         if N mod Digit /= 0 then
            return False;
         end if;
         Prod := Prod * Digit;
      end loop;
      return N mod Prod /= 0;
   end Is_Divisible;

   Count : Natural := 0;
begin
   for N in 1 .. 999 loop
      if Is_Divisible (N) then
         Count := Count + 1;
         Ada.Integer_Text_Io.Put (N, Width => 5);
         if Count mod 15 = 0 then
            Ada.Text_Io.New_Line;
         end if;
      end if;
   end loop;
end Numbers_Divisible;
Output:
   22   33   44   48   55   66   77   88   99  122  124  126  155  162  168
  184  222  244  248  264  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824  848  864  888  936  999

ALGOL 68

BEGIN # find numbers divisible by their digits but not the product of their digits #
    INT max number    = 999;
    INT number count := 0;
    FOR n TO max number DO
        INT digit product        := 1;
        INT v                    := n;
        BOOL divisible by digits := n /= 0;
        WHILE v > 0 AND divisible by digits DO
            INT digit = v MOD 10;
            divisible by digits := IF digit = 0
                                   THEN FALSE
                                   ELSE n MOD digit = 0
                                   FI;
            digit product *:= digit;
            v OVERAB 10
        OD;
        IF divisible by digits THEN
            IF n MOD digit product /= 0 THEN
                # have a number divisible by its digits but not the product of the digits #
                print( ( " ", whole( n, -3 ) ) );
                IF ( number count +:= 1 ) MOD 15 = 0 THEN print( ( newline ) ) FI
            FI
        FI
    OD
END
Output:
  22  33  44  48  55  66  77  88  99 122 124 126 155 162 168
 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448
 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

ALGOL-M

begin
    integer function mod(a, b);
    integer a, b;
    mod := a-a/b*b;
    
    integer function divisible(n);
    integer n;
    begin
        integer r, p, c, d;
        p := 1;
        c := n;
        r := 0;
        while c <> 0 do
        begin
            d := mod(c, 10);
            if d = 0 then go to stop;
            if mod(n, d) <> 0 then go to stop;
            p := p * d;
            c := c / 10;
        end;
        if mod(n, p) <> 0 then r := 1;
    stop:
        divisible := r;
    end;
    
    integer c, n;
    c := 0;
    for n := 1 step 1 until 1000 do
    begin
        if divisible(n) <> 0 then
        begin
            if (c-1)/10 <> c/10 then
                write(n)
            else
                writeon(n);
            c := c + 1;
        end;
    end;
    write("");
end
Output:
    22    33    44    48    55    66    77    88    99   122
   124   126   155   162   168   184   222   244   248   264
   288   324   333   336   366   396   412   424   444   448
   488   515   555   636   648   666   728   777   784   824
   848   864   888   936   999

ALGOL W

begin % find numbers divisible by their digits but not the product of their digits %
    % returns true if n is divisible by its digits but not the product of its      %
    %         digits, false otherwise                                              %
    logical procedure divisibleByDigitsButNotDigitProduct ( integer value n ) ;
    begin
        integer v, p;
        logical matches;
        v       := n;
        p       := 1;
        matches := v not = 0;
        while matches and v > 0 do begin
            integer d;
            d       := v rem 10;
            v       := v div 10;
            if d = 0 then matches := false else matches := n rem d = 0;
            p       := p * d
        end while_matches_and_v_gt_0 ;
        if matches then begin
            if p = 0 then matches := false else matches := n rem p not = 0
        end if_matche ;
        matches
    end divisibleByDigitsButNotDigitProduct ;
    integer count;
    % show the members of the seuence up to 1000 %
    write( "Numbers below 1000 that are divisible by their digits but not the product of their digits:" );
    write();
    count := 0;
    for i := 0 until 999 do begin
        if divisibleByDigitsButNotDigitProduct( i ) then begin
            writeon( i_w := 3, s_w := 0, " ", i );
            count := count + 1;
            if count rem 15 = 0 then write()
        end if_divisibleByDigitsButNotDigitProduct__i
    end for_i
end.
Output:
Numbers below 1000 that are divisible by their digits but not the product of their digits:
  22  33  44  48  55  66  77  88  99 122 124 126 155 162 168
 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448
 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

APL

Works with: Dyalog APL
((/⍨)((¨∘)((/0=|)0(×/)|⊢))¨)999
Output:
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555
      636 648 666 728 777 784 824 848 864 888 936 999

Arturo

valid?: function [n][
    digs: digits n
    facts: factors n
    and? [not? in? product digs facts]
         [every? digs 'd -> in? d facts]
]

print select 1..999 => valid?
Output:
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

AutoHotkey

main:
while n < 1000
{
    n := A_Index
    prod = 1
    for i, v in StrSplit(n)
    {
        if (v = 0) || (n/v <> floor(n/v))
            continue, main
        prod *= v
    }
    if (n/prod = floor(n/prod))
        continue
    result .= n "`t"
}
MsgBox % result
Output:
22	33	44	48	55	66	77	88	99	122	124	126
155	162	168	184	222	244	248	264	288	324	333	336	
366	396	412	424	444	448	488	515	555	636	648	666	
728	777	784	824	848	864	888	936	999	

AWK

# syntax: GAWK -f NUMBERS_DIVISIBLE_BY_THEIR_INDIVIDUAL_DIGITS_BUT_NOT_BY_THE_PRODUCT_OF_THEIR_DIGITS.AWK
# converted from C
BEGIN {
    start = 1
    stop = 999
    for (i=start; i<=stop; i++) {
      if (divisible(i)) {
        printf("%4d%1s",i,++count%10?"":"\n")
      }
    }
    printf("\nNumbers divisible by their individual digits but not by the product of their digits %d-%d: %d\n",start,stop,count)
    exit(0)
}
function divisible(n,  c,d,p) {
    p = 1
    for (c=n; c; c=int(c/10)) {
      d = c % 10
      if (!d || n % d) { return(0) }
      p *= d
    }
    return(n % p)
}
Output:
  22   33   44   48   55   66   77   88   99  122
 124  126  155  162  168  184  222  244  248  264
 288  324  333  336  366  396  412  424  444  448
 488  515  555  636  648  666  728  777  784  824
 848  864  888  936  999
Numbers divisible by their individual digits but not by the product of their digits 1-999: 45

BASIC

10 DEFINT A-Z
20 FOR I=1 TO 999
30 N=I: P=1
40 D=N MOD 10
50 IF D=0 THEN 110
60 P=P*D
70 IF I MOD D THEN 110
80 N=N\10
90 IF N THEN 40
100 IF I MOD P <> 0 THEN PRINT I,
110 NEXT I
Output:
 22            33            44            48            55
 66            77            88            99            122
 124           126           155           162           168
 184           222           244           248           264
 288           324           333           336           366
 396           412           424           444           448
 488           515           555           636           648
 666           728           777           784           824
 848           864           888           936           999

BCPL

get "libhdr"

let divisible(n) = valof
$(  let p = 1
    let c = n
    until c = 0 do
    $(  let d = c rem 10
        if d=0 resultis false
        unless n rem d=0 resultis false
        p := p * d
        c := c / 10
    $)
    resultis n rem p ~= 0
$)

let start() be
$(  let c = 0
    for n = 1 to 1000 do
        if divisible(n) do
        $(  writef("%I5",n)
            c := c + 1
            if c rem 10=0 then wrch('*N')
        $)
    wrch('*N')
$)
Output:
   22   33   44   48   55   66   77   88   99  122
  124  126  155  162  168  184  222  244  248  264
  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824
  848  864  888  936  999

C

#include <stdio.h>

int divisible(int n) {
    int p = 1;
    int c, d;
    
    for (c=n; c; c /= 10) {
        d = c % 10;
        if (!d || n % d) return 0;
        p *= d;
    }
    
    return n % p;
}

int main() {
    int n, c=0;
    
    for (n=1; n<1000; n++) {
        if (divisible(n)) {
            printf("%5d", n);
            if (!(++c % 10)) printf("\n");
        }
    }
    printf("\n");
    
    return 0;
}
Output:
   22   33   44   48   55   66   77   88   99  122
  124  126  155  162  168  184  222  244  248  264
  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824
  848  864  888  936  999

CLU

divisible = proc (n: int) returns (bool)
    prod: int := 1
    dgts: int := n
    while dgts > 0 do
        dgt: int := dgts // 10
        if dgt=0 cor n//dgt~=0 then 
            return(false) 
        end
        prod := prod * dgt
        dgts := dgts / 10
    end
    return(n//prod~=0)
end divisible

start_up = proc ()
    po: stream := stream$primary_output()
    col: int := 0
    for n: int in int$from_to(1,1000) do
        if divisible(n) then
            stream$putright(po, int$unparse(n), 5)
            col := col + 1
            if col//10=0 then stream$putc(po,'\n') end
        end
    end
end start_up
Output:
   22   33   44   48   55   66   77   88   99  122
  124  126  155  162  168  184  222  244  248  264
  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824
  848  864  888  936  999

COBOL

        IDENTIFICATION DIVISION.
        PROGRAM-ID. DIV-BY-DGTS-BUT-NOT-PROD.
        
        DATA DIVISION.
        WORKING-STORAGE SECTION.
        01 CALCULATION.
           02 N             PIC 9(4).
           02 DGT-PROD      PIC 9(3).
           02 NSTART        PIC 9.
           02 D             PIC 9.
           02 N-INDEXING    REDEFINES N.
              03 DIGIT      PIC 9 OCCURS 4 TIMES.
           02 NDIV          PIC 9(4).
           02 OK            PIC 9.
        01 OUTPUT-FORMAT.
           02 DISP-N        PIC Z(4).
           
        PROCEDURE DIVISION.
        BEGIN.
            PERFORM CHECK VARYING N FROM 1 BY 1 
                    UNTIL N IS EQUAL TO 1000.
            STOP RUN.
            
        CHECK SECTION.
        BEGIN.
            SET NSTART TO 1.
            INSPECT N TALLYING NSTART FOR LEADING '0'.
            
            SET DGT-PROD TO 1.
            PERFORM MUL-DIGIT VARYING D FROM NSTART BY 1
                    UNTIL D IS GREATER THAN 4.
            IF DGT-PROD = 0 GO TO NOPE.
            SET OK TO 1.
            PERFORM CHECK-DIGIT VARYING D FROM NSTART BY 1
                    UNTIL D IS GREATER THAN 4.
            IF OK = 0 GO TO NOPE.
            DIVIDE N BY DGT-PROD GIVING NDIV.
            MULTIPLY DGT-PROD BY NDIV.
            IF NDIV IS EQUAL TO N GO TO NOPE.
            MOVE N TO DISP-N.
            DISPLAY DISP-N.
        MUL-DIGIT.
            IF D IS GREATER THAN 4 GO TO NOPE.
            MULTIPLY DIGIT(D) BY DGT-PROD.
        CHECK-DIGIT.
            IF D IS GREATER THAN 4 GO TO NOPE.
            DIVIDE N BY DIGIT(D) GIVING NDIV.
            MULTIPLY DIGIT(D) BY NDIV.
            IF NDIV IS NOT EQUAL TO N SET OK TO 0.
        NOPE. EXIT.
Output:
  22
  33
  44
  48
  55
  66
  77
  88
  99
 122
 124
 126
 155
 162
 168
 184
 222
 244
 248
 264
 288
 324
 333
 336
 366
 396
 412
 424
 444
 448
 488
 515
 555
 636
 648
 666
 728
 777
 784
 824
 848
 864
 888
 936
 999

Cowgol

include "cowgol.coh";

sub divisible(n: uint16): (r: uint8) is
    var product: uint16 := 1;
    var c := n;
    r := 1;
    
    while c != 0 loop
        var digit := c % 10;
        if digit == 0 or n % digit != 0 then
            r := 0;
            return;
        end if;
        product := product * digit;
        c := c / 10;
    end loop;
    
    if n % product == 0 then
        r := 0;
    end if;
end sub;

var n: uint16 := 1;
var c: uint8 := 1;
while n < 1000 loop
    if divisible(n) != 0 then
        print_i16(n);
        c := c + 1;
        if c % 10 == 1 then
            print_nl();
        else
            print_char('\t');
        end if;
    end if;
    n := n + 1;
end loop;
print_nl();
Output:
22      33      44      48      55      66      77      88      99      122
124     126     155     162     168     184     222     244     248     264
288     324     333     336     366     396     412     424     444     448
488     515     555     636     648     666     728     777     784     824
848     864     888     936     999

Draco

proc nonrec divisible(word n) bool:
    word dprod, c, dgt;
    bool div;
    
    c := n;
    div := true;
    dprod := 1;
    while div and c /= 0 do
        dgt := c % 10;
        c := c / 10;
        if dgt = 0 or n % dgt /= 0
            then div := false
            else dprod := dprod * dgt
        fi
    od;
    
    div and n % dprod /= 0
corp

proc nonrec main() void:
    word n, c;
    c := 0;
    
    for n from 1 upto 999 do
        if divisible(n) then
            write(n:5);
            c := c+1;
            if c % 10 = 0 then writeln() fi
        fi
    od
corp
Output:
   22   33   44   48   55   66   77   88   99  122
  124  126  155  162  168  184  222  244  248  264
  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824
  848  864  888  936  999

Delphi

Works with: Delphi version 6.0


function IsDivisible(N: integer): boolean;
{Returns true if N is divisible by each of its digits}
{And not divisible by the product of all the digits}
var I: integer;
var S: string;
var B: byte;
var P: integer;
begin
Result:=False;
{Test if digits divide into N}
S:=IntToStr(N);
for I:=1 to Length(S) do
	begin
	B:=Byte(S[I])-$30;
	if B=0 then exit;
 	if (N mod B)<>0 then exit;
 	end;
{Test if product of digits doesn't divide into N}
P:=1;
for I:=1 to Length(S) do
	begin
	B:=Byte(S[I])-$30;
	P:=P * B;
	end;
Result:=(N mod P)<>0;
end;


procedure ShowDivisibleDigits(Memo: TMemo);
{Show numbers that are even divisible by each of its digits}
{But not divisible by the product of all its digits}
var I,Cnt: integer;
var S: string;
begin
Cnt:=0;
S:='';
for I:=1 to 999 do
 if IsDivisible(I) then
	begin
	Inc(Cnt);
	S:=S+Format('%4D',[I]);
	If (Cnt mod 10)=0 then S:=S+#$0D#$0A;
	end;
Memo.Lines.Add('Count='+IntToStr(Cnt));
Memo.Lines.Add(S);
end;
Output:
Count=45
  22  33  44  48  55  66  77  88  99 122
 124 126 155 162 168 184 222 244 248 264
 288 324 333 336 366 396 412 424 444 448
 488 515 555 636 648 666 728 777 784 824
 848 864 888 936 999


F#

// Nigel Galloway. April 9th., 2021
let rec fN i g e l=match g%10,g/10 with (0,_)->false |(n,_) when i%n>0->false |(n,0)->i%(l*n)>0 |(n,g)->fN i g (e+n) (l*n)
seq{1..999}|>Seq.filter(fun n->fN n n 0 1)|>Seq.iter(printf "%d "); printfn ""
Output:
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

Factor

Works with: Factor version 0.99 2021-02-05
USING: combinators.short-circuit grouping kernel math
math.functions math.ranges math.text.utils prettyprint sequences ;

: needle? ( n -- ? )
    dup 1 digit-groups dup product
    {
        [ 2nip zero? not ]
        [ nip divisor? not ]
        [ drop [ divisor? ] with all? ]
    } 3&& ;

1000 [1..b] [ needle? ] filter 9 group simple-table.
Output:
22  33  44  48  55  66  77  88  99
122 124 126 155 162 168 184 222 244
248 264 288 324 333 336 366 396 412
424 444 448 488 515 555 636 648 666
728 777 784 824 848 864 888 936 999

FOCAL

01.10 F I=1,999;D 2
01.20 Q

02.10 S N=I
02.15 S P=1
02.20 S Z=FITR(N/10)
02.25 S D=N-Z*10
02.30 S N=Z
02.35 S P=P*D
02.40 I (-D)2.45,2.65
02.45 S Z=I/D
02.60 I (FITR(Z)-Z)2.65,2.7
02.65 R
02.70 I (-N)2.2
02.75 S Z=I/P
02.80 I (FITR(Z)-Z)2.85,2.65
02.85 T %4,I,!
Output:
=   22
=   33
=   44
=   48
=   55
=   66
=   77
=   88
=   99
=  122
=  124
=  126
=  155
=  162
=  168
=  184
=  222
=  244
=  248
=  264
=  288
=  324
=  333
=  336
=  366
=  396
=  412
=  424
=  444
=  448
=  488
=  515
=  555
=  636
=  648
=  666
=  728
=  777
=  784
=  824
=  848
=  864
=  888
=  936
=  999

Forth

Works with: Gforth
: divisible? { n -- ? }
  1 { p }
  n
  begin
    dup 0 >
  while
    10 /mod swap
    dup 0= if
      2drop false exit
    then
    dup n swap mod 0<> if
      2drop false exit
    then
    p * to p
  repeat
  drop n p mod 0<> ;

: main
  0 { count }
  1000 1 do
    i divisible? if
      i 4 .r
      count 1+ to count
      count 10 mod 0= if cr else space then
    then
  loop cr ;

main
bye
Output:
  22   33   44   48   55   66   77   88   99  122
 124  126  155  162  168  184  222  244  248  264
 288  324  333  336  366  396  412  424  444  448
 488  515  555  636  648  666  728  777  784  824
 848  864  888  936  999 

FreeBASIC

This function does a bit more than the task asks for, just to make things interesting.

function divdignp( n as const integer ) as ubyte
    'returns 1 if the number is divisible by its digits
    '        2 if it is NOT divisible by the product of its digits
    '        3 if both are true
    '        0 if neither are true
    dim as integer m = n, p = 1, r = 1, d
    while m>0
        d = m mod 10
        m \= 10
        p *= d
        if d<>0 andalso n mod d <> 0 then r = 0
    wend
    if p<>0 andalso n mod p <> 0 then r += 2
    return r
end function

for i as uinteger = 1 to 999
    if divdignp(i) = 3 then print i;" ";
next i : print
Output:
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

Go

Translation of: Wren
Library: Go-rcu
package main

import (
    "fmt"
    "rcu"
)

func main() {
    var res []int
    for n := 1; n < 1000; n++ {
        digits := rcu.Digits(n, 10)
        var all = true
        for _, d := range digits {
            if d == 0 || n%d != 0 {
                all = false
                break
            }
        }
        if all {
            prod := 1
            for _, d := range digits {
                prod *= d
            }
            if prod > 0 && n%prod != 0 {
                res = append(res, n)
            }
        }
    }
    fmt.Println("Numbers < 1000 divisible by their digits, but not by the product thereof:")
    for i, n := range res {
        fmt.Printf("%4d", n)
        if (i+1)%9 == 0 {
            fmt.Println()
        }
    }
    fmt.Printf("\n%d such numbers found\n", len(res))
}
Output:
Numbers < 1000 divisible by their digits, but not by the product thereof:
  22  33  44  48  55  66  77  88  99
 122 124 126 155 162 168 184 222 244
 248 264 288 324 333 336 366 396 412
 424 444 448 488 515 555 636 648 666
 728 777 784 824 848 864 888 936 999

45 such numbers found

Haskell

import Data.List.Split (chunksOf)
import Text.Printf

divisible :: Int -> Bool
divisible = divdgt <*> dgt
  where
    dgt = map (read . pure) . show
    divdgt x d =
      notElem 0 d
        && 0 /= x `mod` product d
        && all ((0 ==) . mod x) d

numbers :: [Int]
numbers = filter divisible [1 ..]

main :: IO ()
main = putStr $ unlines $ map (concatMap $ printf "%5d") split
  where
    n = takeWhile (< 1000) numbers
    split = chunksOf 10 n
Output:
   22   33   44   48   55   66   77   88   99  122
  124  126  155  162  168  184  222  244  248  264
  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824
  848  864  888  936  999

and another approach might be to obtain (unordered) digit lists numerically, rather than by string conversion.

import Data.Bool (bool)
import Data.List (unfoldr)
import Data.List.Split (chunksOf)
import Data.Tuple (swap)

-- DIVISIBLE BY ALL DIGITS, BUT NOT BY PRODUCT OF ALL DIGITS

p :: Int -> Bool
p n =
  ( ( (&&)
        . all
          ( (&&) . (0 /=)
              <*> (0 ==) . rem n
          )
    )
      <*> (0 /=) . rem n . product
  )
    $ digits n

digits :: Int -> [Int]
digits =
  unfoldr $
    (bool Nothing . Just . swap . flip quotRem 10) <*> (0 <)

--------------------------- TEST -------------------------
main :: IO ()
main =
  let xs = [1 .. 1000] >>= (\n -> [show n | p n])
      w = length $ last xs
   in (putStrLn . unlines) $
        unwords
          <$> chunksOf
            10
            (fmap (justifyRight w ' ') xs)

justifyRight :: Int -> Char -> String -> String
justifyRight n c = (drop . length) <*> (replicate n c <>)
Output:
 22  33  44  48  55  66  77  88  99 122
124 126 155 162 168 184 222 244 248 264
288 324 333 336 366 396 412 424 444 448
488 515 555 636 648 666 728 777 784 824
848 864 888 936 999

J

   ([ #~ ((10 #.inv]) ((0~:*/@[|]) * */@(0=|)) ])"0) >:i.999
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

([ #~ ... ) >:i.999 filters the numbers based on the predicate (shown as '...' here).

((10 #.inv]) ... ])"0 extracts a predicate value for each number, with the number's digits as the left argument and the number itself as the right argument.

((0~:*/@[|]) * */@(0=|)) is true if the product of the digits does not evenly divide the number ((0~:*/@[|])) AND all of the digits individually evenly divide the number (*/@(0=|)).

jq

Works with: jq

Works with gojq, the Go implementation of jq

def digits:
  tostring | explode | map( [.] | implode | tonumber);

def prod:
  reduce .[] as $i (1; .*$i);
  
def is_divisible_by_digits_but_not_product:
  . as $n
  | tostring 
  | select( null == index("0"))
  | digits
  | all( unique[]; $n % . == 0)
    and ($n % prod != 0);

The Task

"Numbers < 1000 divisible by their digits, but not by the product thereof:",
 (range(1; 1000)
  | select(is_divisible_by_digits_but_not_product))
Output:
Numbers < 1000 divisible by their digits, but not by the product thereof:
22
33
44
48
55
66
77
88
99
122
124
126
155
162
168
184
222
244
248
264
288
324
333
336
366
396
412
424
444
448
488
515
555
636
648
666
728
777
784
824
848
864
888
936
999


Julia

isonlydigdivisible(n) = (d = digits(n); !(0 in d) && all(x -> n % x == 0, d) && n % prod(d) != 0)

foreach(p -> print(rpad(p[2], 5), p[1] % 15 == 0 ? "\n" : ""), enumerate(filter(isonlydigdivisible, 1:1000)))
Output:
22   33   44   48   55   66   77   88   99   122  124  126  155  162  168  
184  222  244  248  264  288  324  333  336  366  396  412  424  444  448
488  515  555  636  648  666  728  777  784  824  848  864  888  936  999

Ksh

#!/bin/ksh

# Numbers divisible by their digits, but not by the product of their digits

#	# Variables:
#
integer MAXN=1000

#	# Functions:
#
#	# Function _isdivisible(n) - return 1 if:
#	#  - is divisible by individual digits, and
#	#  - not divisible by product of digits
#
function _isdivisible {
	typeset _n ; integer _n=$1
	typeset _i _digit _product ; integer _i _digit _product=1

	for ((_i=0; _i<${#_n}; _i++)); do
		_digit=${_n:_i:1}
		(( ! _digit )) || (( _n % _digit )) && return 0
		(( _product*=_digit ))
	done
	return $(( _n % _product ))
}

 ######
# main #
 ######

for ((i=10; i<MAXN; i++)); do
	(( ! i % 10 )) || _isdivisible ${i} || printf "%d " ${i}
done
Output:

22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999 

MAD

            NORMAL MODE IS INTEGER
            PRINT COMMENT $ $
            
            INTERNAL FUNCTION(N)
            ENTRY TO DVDGT.
            P=1            
            C=N
DGT         WHENEVER C.NE.0
                Z = C/10
                D = C-Z*10
                WHENEVER D.E.0 .OR. N/D*D.NE.N, FUNCTION RETURN 0B
                P = P*D
                C = Z
                TRANSFER TO DGT
            END OF CONDITIONAL
            FUNCTION RETURN N/P*P.NE.N
            END OF FUNCTION
            
            THROUGH TEST, FOR I=1, 1, I.E.1000
TEST        WHENEVER DVDGT.(I), PRINT FORMAT FMT, I

            VECTOR VALUES FMT = $I4*$
            END OF PROGRAM
Output:
  22
  33
  44
  48
  55
  66
  77
  88
  99
 122
 124
 126
 155
 162
 168
 184
 222
 244
 248
 264
 288
 324
 333
 336
 366
 396
 412
 424
 444
 448
 488
 515
 555
 636
 648
 666
 728
 777
 784
 824
 848
 864
 888
 936
 999

Mathematica/Wolfram Language

ClearAll[SaveDivisible,DivisibleDigits]
SaveDivisible[n_,0] := False
SaveDivisible[n_,m_] := Divisible[n,m]
DivisibleDigits[n_Integer] := AllTrue[IntegerDigits[n],SaveDivisible[n,#]&]
Select[Range[999],DivisibleDigits[#]\[And]!SaveDivisible[#,Times@@IntegerDigits[#]]&]
Length[%]
Output:
{22, 33, 44, 48, 55, 66, 77, 88, 99, 122, 124, 126, 155, 162, 168, 184, 222, 244, 248, 264, 288, 324, 333, 336, 366, 396, 412, 424, 444, 448, 488, 515, 555, 636, 648, 666, 728, 777, 784, 824, 848, 864, 888, 936, 999}
45

Miranda

main :: [sys_message]
main = [Stdout (table 12 5 numbers)]

table :: num->num->[num]->[char]
table cols cw = lay . map concat . split . map fmt
                where split [] = []
                      split ls = take cols ls : split (drop cols ls)
                      fmt   n  = reverse (take cw ((reverse (shownum n)) ++ repeat ' '))

numbers :: [num]
numbers = [n | n<-[1..1000]; divisible n]

divisible :: num->bool
divisible n = False, if digprod = 0 \/ n mod digprod = 0
            = and [n mod d = 0 | d <- digits n], otherwise
              where digprod = product (digits n)

digits :: num->[num]
digits = map (mod 10) . takewhile (>0) . iterate (div 10)
Output:
   22   33   44   48   55   66   77   88   99  122  124  126
  155  162  168  184  222  244  248  264  288  324  333  336
  366  396  412  424  444  448  488  515  555  636  648  666
  728  777  784  824  848  864  888  936  999

Nim

import strutils

iterator digits(n: Positive): int =
  var n = n.int
  while n != 0:
    yield n mod 10
    n = n div 10

var result: seq[int]
for n in 1..1000:
  block check:
    var m = 1
    for d in n.digits:
      if d == 0 or n mod d != 0: break check
      m *= d
    if n mod m != 0: result.add n

echo "Found ", result.len, " matching numbers."
for i, n in result:
  stdout.write ($n).align(3), if (i + 1) mod 9 == 0: '\n' else: ' '
Output:
Found 45 matching numbers.
 22  33  44  48  55  66  77  88  99
122 124 126 155 162 168 184 222 244
248 264 288 324 333 336 366 396 412
424 444 448 488 515 555 636 648 666
728 777 784 824 848 864 888 936 999

OCaml

let test b x =
  let rec loop m n =
    if n < b
    then x mod n = 0 && x mod (m * n) > 0
    else let d = n mod b in d > 0 && x mod d = 0 && loop (m * d) (n / b)
  in loop 1 x

let () =
  Seq.ints 1 |> Seq.take 999 |> Seq.filter (test 10)
  |> Seq.iter (Printf.printf " %u") |> print_newline
Output:
 22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

Pascal

Free Pascal

program DivByDgtsNotByProdOfDgts;

function ProdDigits(n:cardinal):cardinal;
// returns product of Digits if n is divisible by digits
var
  p,q,r,dgt : cardinal;
begin
  q := n;
  p := 1;
  repeat
    r := q DIV 10;
    dgt := q-10*r;
    if (dgt= 0)OR(n mod dgt <> 0) then
      EXIT(0);
    p := p*dgt;
    q := r;
  until q = 0;
  Exit(p)
end;

const
  LimitLow  =    1;
  LimitHigh = 1000;
var
  i,mul,cnt : Cardinal;
BEGIN
  cnt := 0;
  writeln('Limits ',LimitLow,'..',LimitHigh);
  For i := LimitLow to LimitHigh do
  begin
    mul := ProdDigits(i);
    if (mul <> 0)  AND (i MOD MUL<>0) then
    Begin
      write(i:4);
      inc(cnt);
      if cnt AND 15= 0 then
        writeln;
    end;
  end;
  if cnt AND 15 <> 0 then
    writeln;
  writeln(' count : ',cnt);
END.
Output:
Limits 1..1000
  22  33  44  48  55  66  77  88  99 122 124 126 155 162 168 184
 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515
 555 636 648 666 728 777 784 824 848 864 888 936 999
 count : 45

Perl

#!/usr/bin/perl

use strict;
use warnings;

my @numbers = grep
  {
  my $n = $_;
  ! /0/ and $_ % eval s/\B/*/gr and 0 == grep $n % $_, split //
  } 1 .. 999;

print @numbers . " numbers found\n\n@numbers\n" =~ s/.{25}\K /\n/gr;
Output:
45 numbers found

22 33 44 48 55 66 77 88 99
122 124 126 155 162 168 184
222 244 248 264 288 324 333
336 366 396 412 424 444 448
488 515 555 636 648 666 728
777 784 824 848 864 888 936
999

Phix

function didbntp(integer n)
    integer w = n, p = 1
    while w do
        integer d = remainder(w,10)
        if d=0 or remainder(n,d) then return false end if
        p *= d
        w = floor(w/10)
    end while
    return remainder(n,p)!=0
end function
sequence res = apply(filter(tagset(1000),didbntp),sprint)
printf(1,"found %d didbntp thingies less than one thousand: %s\n",{length(res),join(shorten(res,"",5),",")})
Output:
found 45 didbntp thingies less than one thousand: 22,33,44,48,55,...,848,864,888,936,999

PL/M

100H:

/* CHECK NUMBER */
DIVISIBLE: PROCEDURE (N) BYTE;
    DECLARE (N, I, PROD) ADDRESS;
    DECLARE D BYTE;
    PROD = 1;
    I = N;
    DO WHILE N > 0;
        D = N MOD 10;
        N = N / 10;
        IF D = 0 THEN RETURN 0;
        IF I MOD D <> 0 THEN RETURN 0;
        PROD = PROD * D;
    END;
    RETURN I MOD PROD <> 0;
END DIVISIBLE;

/* CP/M BDOS CALL - PL/M DOESN'T ACTUALLY COME WITH OUTPUT ROUTINES */
BDOS: PROCEDURE (FN, ARG);
    DECLARE FN BYTE, ARG ADDRESS;
    GO TO 5;
END BDOS;

/* PRINT DECIMAL NUMBER */
PRINT$NUMBER: PROCEDURE (N);
    DECLARE S (8) BYTE INITIAL ('.....',13,10,'$');
    DECLARE (N, P) ADDRESS, C BASED P BYTE;
    P = .S(5);
DIGIT:
    P = P - 1;
    C = N MOD 10 + '0';
    N = N / 10;
    IF N > 0 THEN GO TO DIGIT;
    CALL BDOS(9, P);
END PRINT$NUMBER;

/* TEST THE NUMBERS 1..1000 */
DECLARE N ADDRESS;
DO N=1 TO 999;
    IF DIVISIBLE(N) THEN 
        CALL PRINT$NUMBER(N);
END;

CALL BDOS(0,0);
EOF
Output:
22
33
44
48
55
66
77
88
99
122
124
126
155
162
168
184
222
244
248
264
288
324
333
336
366
396
412
424
444
448
488
515
555
636
648
666
728
777
784
824
848
864
888
936
999

Plain English

To run:
Start up.
Loop.
If a counter is past 999, break.
If the counter is digit-divisible but non-digit-product-divisible, write the counter then " " on the console without advancing.
Repeat.
Wait for the escape key.
Shut down.

To decide if a number is digit-divisible but non-digit-product-divisible:
If the number is 0, say no.
Put the number into a shrinking number.
Put 1 into a digit product number.
Loop.
If the shrinking number is 0, break.
Divide the shrinking number by 10 giving a quotient and a remainder.
Multiply the digit product by the remainder.
If the number is not evenly divisible by the remainder, say no.
Put the quotient into the shrinking number.
Repeat.
If the number is evenly divisible by the digit product, say no.
Say yes.
Output:
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

Python

'''Numbers matching a function of their digits'''

from functools import reduce
from operator import mul


# p :: Int -> Bool
def p(n):
    '''True if n is divisible by each of its digits,
       but not divisible by the product of those digits.
    '''
    digits = [int(c) for c in str(n)]
    return not 0 in digits and (
        0 != (n % reduce(mul, digits, 1))
    ) and all(0 == n % d for d in digits)


# ------------------------- TEST -------------------------
# main :: IO ()
def main():
    '''Numbers below 1000 which satisfy p
    '''
    xs = [
        str(n) for n in range(1, 1000)
        if p(n)
    ]
    w = len(xs[-1])
    print(f'{len(xs)} matching numbers:\n')
    print('\n'.join(
        ' '.join(cell.rjust(w, ' ') for cell in row)
        for row in chunksOf(10)(xs)
    ))


# ----------------------- GENERIC ------------------------

# chunksOf :: Int -> [a] -> [[a]]
def chunksOf(n):
    '''A series of lists of length n, subdividing the
       contents of xs. Where the length of xs is not evenly
       divible, the final list will be shorter than n.
    '''
    def go(xs):
        return (
            xs[i:n + i] for i in range(0, len(xs), n)
        ) if 0 < n else None
    return go


# MAIN ---
if __name__ == '__main__':
    main()
Output:
45 matching numbers:

 22  33  44  48  55  66  77  88  99 122
124 126 155 162 168 184 222 244 248 264
288 324 333 336 366 396 412 424 444 448
488 515 555 636 648 666 728 777 784 824
848 864 888 936 999

Quackery

  [ dup 0 = iff 
     [ 2drop false ] done
    mod 0 = ]                      is divisible     ( n n --> b )

  [ [] swap 
    [ 10 /mod 
      rot join swap
      dup 0 = until ]
    drop ]                         is digits        (   n --> [ )

  [ 1 swap witheach * ]            is product       (   [ --> n )

  [ dup digits
    dup product
    dip over divisible 
    iff [ 2drop false ] done
    true unrot 
    witheach 
      [ dip dup divisible not if 
          [ dip not conclude ] ]
    drop ]                         is meetscriteria ( n n --> b )

  1000 times [ i^ meetscriteria if [ i^ echo sp ] ]
Output:
22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999

Raku

say "{+$_} matching numbers:\n{.batch(10)».fmt('%3d').join: "\n"}" given
   (^1000).grep: -> $n { $n.contains(0) ?? False !! all |($n.comb).map($n %% *), $n % [*] $n.comb };
Output:
45 matching numbers:
 22  33  44  48  55  66  77  88  99 122
124 126 155 162 168 184 222 244 248 264
288 324 333 336 366 396 412 424 444 448
488 515 555 636 648 666 728 777 784 824
848 864 888 936 999

REXX

/*REXX pgm finds integers divisible by its individual digits, but not by product of digs*/
parse arg hi cols .                              /*obtain optional argument from the CL.*/
if   hi=='' |   hi==","  then   hi= 1000         /*Not specified?  Then use the default.*/
if cols=='' | cols==","  then cols=   10         /* "      "         "   "   "     "    */
w= 10                                            /*width of a number in any column.     */
                    title= ' base ten integers  < '   commas(hi)   " that are divisible" ,
                           'by its digits, but not by the product of its digits'
if cols>0 then say ' index │'center(title,   1 + cols*(w+1)     )
if cols>0 then say '───────┼'center(""   ,   1 + cols*(w+1), '─')
finds= 0;                 idx= 1                 /*initialize # of found numbers & index*/
$=                                               /*a list of integers found  (so far).  */
     do j=1  for hi-1;    L= length(j);    != 1  /*search for integers within the range.*/
     if pos(0, j)>0  then iterate                /*Does J have a zero?  Yes, then skip. */      /* ◄■■■■■■■■ a filter. */
            do k=1  for L;    x= substr(j, k, 1) /*extract a single decimal digit from J*/
            if j//x\==0   then iterate j         /*J ÷ by this digit?  No, then skip it.*/      /* ◄■■■■■■■■ a filter. */
            != ! * x                             /*compute the running product of digits*/
            end   /*k*/
     if j//!==0           then iterate           /*J ÷ by its digit product?  Yes, skip.*/      /* ◄■■■■■■■■ a filter. */
     finds= finds + 1                            /*bump the number of  found  integers. */
     if cols<0            then iterate           /*Build the list  (to be shown later)? */
     $= $ right( commas(j), w)                   /*add the number found to the  $  list.*/
     if finds//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 '       commas(finds)       title
exit 0                                           /*stick a fork in it,  we're all done. */
/*──────────────────────────────────────────────────────────────────────────────────────*/
commas: parse arg ?;  do jc=length(?)-3  to 1  by -3; ?=insert(',', ?, jc); end;  return ?
output   when using the default inputs:
 index │      base ten integers  <  1,000  that are divisible by its digits, but not by the product of its digits
───────┼───────────────────────────────────────────────────────────────────────────────────────────────────────────────
   1   │         22         33         44         48         55         66         77         88         99        122
  11   │        124        126        155        162        168        184        222        244        248        264
  21   │        288        324        333        336        366        396        412        424        444        448
  31   │        488        515        555        636        648        666        728        777        784        824
  41   │        848        864        888        936        999
───────┴───────────────────────────────────────────────────────────────────────────────────────────────────────────────

Found  45  base ten integers  <  1,000  that are divisible by its digits, but not by the product of its digits

Ring

load "stdlib.ring"
 
decimals(0)
see "working..." + nl
see "Numbers divisible by their individual digits, but not by the product of their digits are:" + nl

row = 0
limit = 1000
 
for n = 1 to limit
    flag = 1
    pro = 1
    strn = string(n)
    for m = 1 to len(strn)
        temp = strn[m]
        if temp != 0
           pro = pro * number(temp)
        ok
        if n%temp = 0
           flag = 1
        else
           flag = 0
           exit
        ok
     next
     bool = ((n%pro) != 0)
     if flag = 1 and bool
        row = row + 1
        see "" + n + " "
        if row%10 = 0
           see nl
        ok
     ok
next

see nl + "Found " + row + " numbers" + nl
see "done..." + nl
Output:
working...
Numbers divisible by their individual digits, but not by the product of their digits are:
22 33 44 48 55 66 77 88 99 122 
124 126 155 162 168 184 222 244 248 264 
288 324 333 336 366 396 412 424 444 448 
488 515 555 636 648 666 728 777 784 824 
848 864 888 936 999 
Found 45 numbers
done...

RPL

Works with: HP version 48
≪ DUP →STR → n
   ≪ CASE
        DUP 9 ≤ n "0" POS OR THEN DROP 0 END
        ≪ n j DUP SUB STR→ ≫ 'j' 1 n SIZE 1 SEQ     @ make list of digits
        DUP2 MOD ∑LIST THEN DROP2 0 END
        ΠLIST MOD SIGN
     END
≫ 'GOOD?' STO
≪ 1 999 FOR j IF j GOOD? THEN j + END NEXT ≫ EVAL
Output:
1: { 22 33 44 48 55 66 77 88 99 122 124 126 155 162 168 184 222 244 248 264 288 324 333 336 366 396 412 424 444 448 488 515 555 636 648 666 728 777 784 824 848 864 888 936 999 }

Rust

fn to_digits( n : i32 ) -> Vec<i32> {
   let mut i : i32 = n ;
   let mut digits : Vec<i32> = Vec::new( ) ;
   while i != 0 {
      digits.push( i % 10 ) ;
      i /= 10 ;
   }
   digits
}

fn my_condition( num : i32 ) -> bool {
   let digits : Vec<i32> = to_digits( num ) ;
   if ! digits.iter( ).any( | x | *x == 0 ) {
      let prod : i32 = digits.iter( ).product( ) ;
      return digits.iter( ).all( | x | num % x == 0 ) && 
         num % prod != 0 ;
   }
   else {
      false 
   }
}

fn main() {
let mut count : i32 = 0 ;
   for n in 10 .. 1000 {
      if my_condition( n ) {
         print!("{:5}" , n) ;
         count += 1 ;
         if count % 10 == 0 {
            println!( ) ;
         }
      }
   }
   println!();
}
Output:
   22   33   44   48   55   66   77   88   99  122
  124  126  155  162  168  184  222  244  248  264
  288  324  333  336  366  396  412  424  444  448
  488  515  555  636  648  666  728  777  784  824
  848  864  888  936  999 

Ruby

res =(1..1000).select do |n|
  digits = n.digits
  next if digits.include? 0
  digits.uniq.all?{|d| n%d == 0} &! (n % digits.inject(:*) == 0)
end

p res
Output:
[22, 33, 44, 48, 55, 66, 77, 88, 99, 122, 124, 126, 155, 162, 168, 184, 222, 244, 248, 264, 288, 324, 333, 336, 366, 396, 412, 424, 444, 448, 488, 515, 555, 636, 648, 666, 728, 777, 784, 824, 848, 864, 888, 936, 999]

Sidef

^1000 -> grep {|n|
    n.digits.all {|d| d `divides` n } && !(n.digits.prod `divides` n)
}.say
Output:
[22, 33, 44, 48, 55, 66, 77, 88, 99, 122, 124, 126, 155, 162, 168, 184, 222, 244, 248, 264, 288, 324, 333, 336, 366, 396, 412, 424, 444, 448, 488, 515, 555, 636, 648, 666, 728, 777, 784, 824, 848, 864, 888, 936, 999]

Snobol

        define('divis(n)i,d,p')             :(divis_end)
divis   p = 1
        i = n
digit   d = remdr(i,10)
        p = ne(d,0) eq(remdr(n,d),0) p * d  :f(freturn)
        i = gt(i,9) i / 10                  :s(digit)
        ne(remdr(n,p))                      :s(return)f(freturn)
divis_end

        n = 1
loop    output = divis(n) n
        n = lt(n,1000) n + 1                :s(loop)
end
Output:
22
33
44
48
55
66
77
88
99
122
124
126
155
162
168
184
222
244
248
264
288
324
333
336
366
396
412
424
444
448
488
515
555
636
648
666
728
777
784
824
848
864
888
936
999

Wren

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

var res = []
for (n in 1..999) {
    var digits = Int.digits(n)
    if (digits.all { |d| n % d == 0 }) {
        var prod = Nums.prod(digits)
        if (prod > 0 && n % prod != 0) res.add(n)
    }
}
System.print("Numbers < 1000 divisible by their digits, but not by the product thereof:")
Fmt.tprint("$4d", res, 9)
System.print("\n%(res.count) such numbers found")
Output:
Numbers < 1000 divisible by their digits, but not by the product thereof:
  22   33   44   48   55   66   77   88   99
 122  124  126  155  162  168  184  222  244
 248  264  288  324  333  336  366  396  412
 424  444  448  488  515  555  636  648  666
 728  777  784  824  848  864  888  936  999

45 such numbers found

XPL0

func Check(N);
\Return 'true' if N is divisible by its digits and not by the product of its digits
int  N, M, Digit, Product;
[Product:= 1;
M:= N;
repeat  M:= M/10;
        Digit:= rem(0);
        if Digit = 0 then return false;
        if rem(N/Digit) then return false;
        Product:= Product * Digit;
until   M=0;
return rem(N/Product) # 0;
];

int Count, N;
[Count:= 0;
for N:= 1 to 1000-1 do
    if Check(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 integers found below 1000.
");
]
Output:
22      33      44      48      55      66      77      88      99      122
124     126     155     162     168     184     222     244     248     264
288     324     333     336     366     396     412     424     444     448
488     515     555     636     648     666     728     777     784     824
848     864     888     936     999     
45 such integers found below 1000.