Population count

From Rosetta Code


Task
Population count
You are encouraged to solve this task according to the task description, using any language you may know.

The   population count   is the number of   1s   (ones)   in the binary representation of a non-negative integer.

Population count   is also known as:

  •   pop count
  •   popcount
  •   sideways sum
  •   bit summation
  •   Hamming weight


For example,   5   (which is   101   in binary)   has a population count of   2.


Evil numbers   are non-negative integers that have an   even   population count.

Odious numbers     are  positive integers that have an    odd   population count.


Task
  • write a function (or routine) to return the population count of a non-negative integer.
  • all computation of the lists below should start with   0   (zero indexed).
  • display the   pop count   of the   1st   thirty powers of   3       (30,   31,   32,   33,   34,   ∙∙∙   329).
  • display the   1st   thirty     evil     numbers.
  • display the   1st   thirty   odious   numbers.
  • display each list of integers on one line   (which may or may not include a title),   each set of integers being shown should be properly identified.


See also



11l

Translation of: Python
print((0.<30).map(i -> bits:popcount(Int64(3) ^ i)))

[Int] evil, odious
V i = 0
L evil.len < 30 | odious.len < 30
   V p = bits:popcount(i)
   I (p % 2) != 0
      odious.append(i)
   E
      evil.append(i)
   i++

print(evil[0.<30])
print(odious[0.<30])
Output:
[1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
[0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]
[1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]

360 Assembly

Use of the old " Unnormalized Double Floating Point" feature, a bit forgotten, to have 56-bit integers. And also use of ICM (Insert Characters Under Mask) and TM (Test under Mask) to handle bits.
Let's note:

  • in Normalized Double Floating Point, one is implemented X'4110000000000000'
  • in Unnormalized Double Floating Point, one is implemented X'4E00000000000001'


*        Population count          09/05/2019
POPCNT   CSECT
         USING  POPCNT,R13         base register
         B      72(R15)            skip savearea
         DC     17F'0'             savearea
         SAVE   (14,12)            save previous context
         ST     R13,4(R15)         link backward
         ST     R15,8(R13)         link forward
         LR     R13,R15            set addressability
         LD     F0,UN              1
         STD    F0,BB              bb=1
         MVC    PG(7),=C'pow  3:'  init buffer
         L      R10,NN             nn
         BCTR   R10,0              nn-1
         LA     R9,PG+7            @pg 
         LA     R6,0               i=0 
       DO WHILE=(CR,R6,LE,R10)     do i=0 to nn-1
         LM     R0,R1,BB             r0r1=bb
         BAL    R14,POPCOUNT         call popcount(bb)
         LR     R1,R0                popcount(bb)
         XDECO  R1,XDEC              edit popcount(bb)
         MVC    0(3,R9),XDEC+9       output popcount(bb)
         LD     F0,BB                bb
         AW     F0,BB                bb*2
         AW     F0,BB                bb*3
         STD    F0,BB                bb=bb*3
         LA     R9,3(R9)             @pg
         LA     R6,1(R6)             i++ 
       ENDDO    ,                  enddo i
         XPRNT  PG,L'PG            print buffer
         SR     R7,R7              j=0 
       DO WHILE=(C,R7,LE,=F'1')    do j=0 to 1
         MVC    PG,=CL132' '         clear buffer
       IF   LTR,R7,Z,R7 THEN         if j=0 then
         MVC    PG(7),=C'evil:  '      init buffer
       ELSE     ,                    else
         MVC    PG(7),=C'odious:'      init buffer
       ENDIF    ,                    endif
         LA     R9,PG+7              @pg
         SR     R8,R8                n=0
         SR     R6,R6                i=0
       DO WHILE=(C,R8,LT,NN)         do i=0 by 1 while(n<nn)
         XR     R0,R0                  r0=0
         LR     R1,R6                  r1=i
         BAL    R14,POPCOUNT           r0=popcount(i)
         SRDA   R0,32                  ~
         D      R0,=F'2'               popcount(i)/2
       IF    CR,R0,EQ,R7 THEN          if popcount(i)//2=j then
         LA     R8,1(R8)                 n=n+1
         XDECO  R6,XDEC                  edit i
         MVC    0(3,R9),XDEC+9           output i
         LA     R9,3(R9)                 @pg
       ENDIF    ,                      endif
         LA     R6,1(R6)             i++ 
       ENDDO    ,                    enddo i
         XPRNT  PG,L'PG              print buffer
         LA     R7,1(R7)             j++
       ENDDO    ,                  enddo j
         L      R13,4(0,R13)       restore previous savearea pointer
         RETURN (14,12),RC=0       restore registers from calling sav
*------- ----   ------------------ 
POPCOUNT EQU    *                  popcount(x)
         ICM    R0,B'1000',=X'00'  zap exponant part
         XR     R3,R3              y=0
         LA     R4,56              mantissa size = 56
LOOP     STC    R1,CC              do i=1 to 56
         TM     CC,X'01'             if bit(x,i)=1
         BNO    NOTONE               then{
         LA     R3,1(R3)               y++}
NOTONE   SRDA   R0,1                 shift right double arithmetic 
         BCT    R4,LOOP            enddo i
         LR     R0,R3              return(y)
         BR     R14                return
*------- ----   ------------------ 
NN       DC     F'30'              nn=30
BB       DS     D                  bb
UN       DC     X'4E00000000000001'  un=1 (unnormalized)
PG       DC     CL132' '           buffer
XDEC     DS     CL12               temp for xdeco
CC       DS     C
         REGEQU
         END    POPCNT
Output:
pow  3:  1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil:    0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious:  1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

8080 Assembly

This program uses the parity flag to test whether a number is evil or odious, and is therefore not compatible with the Z80, which reused that flag as an overflow flag. It will only run correctly on a real 8080.

	org	100h
	mvi	e,30	; 3^0 to 3^29 inclusive
powers:	push	d	; Keep counter
	;;;	Calculate Hamming weight of pow3
	lxi	b,6	; C = 6 bytes, B = counter
	lxi	h,pow3
ham48:	mov	a,m	; Get byte
	ana	a	; Clear carry
hambt:	ral		; Rotate into carry
	jnc	$+4	; Increment counter if carry set
	inr	b
	ana	a	; Done yet?
	jnz	hambt	; If not, keep going
	dcr	c	; More bytes?
	inx	h
	jnz	ham48	; If not, keep going
	mov	a,b	; Print result
	call	outa
	;;;	Multiply pow3 by 3
	mvi	b,6	; Make copy
	lxi	h,pow3
	lxi	d,pow3c
copy:	mov	a,m
	stax	d
	inx	h
	inx	d
	dcr	b
	jnz	copy
	;;;	Multiply by 3 (add copy to it twice)
	lxi	h,pow3c	
	lxi	d,pow3
	call	add48
	call	add48
	pop	d	; Restore counter
	dcr	e	; Count down from 30
	jnz	powers
	call	outnl
	;;;	Print first 30 evil numbers
	;;;	An evil number has even parity
	lxi	b,-226	; B=current number (start -1), C=counter
evil:	inr	b	; Increment number
	jpo	evil	; If odious, try next number
	push	b	; Otherwise, output it,
	mov	a,b
	call	outa
	pop	b
	dcr	c	; Decrement counter
	jnz	evil	; If not zero, get more numbers
	call	outnl
	;;;	Print first 30 odious numbers
	;;;	An odious number has odd parity
	lxi	b,-226
odious:	inr	b
	jpe	odious	; If number is evil, try next number
	push	b
	mov 	a,b
	call	outa
	pop	b
	dcr	c
	jnz	odious
	;;;	Print newline
outnl:	lxi	d,nl
	mvi	c,9
	jmp	5
	;;;	Print 2-digit number in A
outa:	lxi	d,0A2Fh	; D=10, E=high digit
mkdgt:	inr	e
	sub	d
	jnc	mkdgt
	adi	'0'+10	; Low digit
	push	psw	; Save low digit
	mvi	c,2	; Print high digit
	call	5
	pop	psw	; Restore low digit
	mov	e,a	; Print low digit
	mvi	c,2
	call	5
	mvi	e,' '	; Print space
	mvi	c,2
	jmp	5
	;;;	Add 48-byte number at [HL] to [DE]
add48:	push	h	; Keep pointers
	push	d
	mvi	b,6	; 6 bytes
	ana	a	; Clear carry
a48l:	ldax	d	; Get byte at [DE]
	adc	m	; Add byte at [HL]
	stax	d	; Store result at [DE]
	inx	h	; Increment pointers
	inx	d
	dcr	b	; Any more bytes left?
	jnz	a48l	; If so, do next byte
	pop	d	; Restore pointers
	pop	h
	ret
nl:	db	13,10,'$'
pow3:	db	1,0,0,0,0,0	; pow3, starts at 1
pow3c:	equ	$		; room for copy
Output:
01 02 02 04 03 06 06 05 06 08 09 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
00 03 05 06 09 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
01 02 04 07 08 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59


8086 Assembly

	cpu	8086
	bits	16
	org	100h
section	.text
	;;;	Calculate hamming weights of 3^0 to 3^29.
	;;;	3^29 needs a 48-bit representation, which
	;;;	we'll put in BP:SI:DI.
	xor	bp,bp		; BP:SI:DI = 1
	xor	si,si
	xor	di,di
	inc	di
	mov	cx,30
	;;;	Calculate pop count of BP:SI:DI
pow3s:	push	bp		; Keep state
	push	si
	push	di
	xor	ax,ax		; AL = counter
ham48:	rcl	bp,1
	rcl	si,1
	rcl	di,1
	adc	al,ah
	mov	dx,bp
	or	dx,si
	or	dx,di
	jnz	ham48
	pop	di		; Restore state
	pop	si
	pop	bp
	call	outal		; Output
	;;;	Multiply by 3
	push	bp		; Keep state
	push	si
	push	di
	add	di,di 		; Mul by two (add to itself)
	adc	si,si
	adc	bp,bp
	pop	ax		; Add original (making x3)
	add	di,ax
	pop	ax
	adc	si,ax
	pop	ax
	adc	bp,ax
	loop	pow3s
	call	outnl
	;;;	Print first 30 evil numbers
	;;;	This is much easier, since they fit in a byte,
	;;;	and we only need to know whether the Hamming weight
	;;;	is odd or even, which is the same as the built-in
	;;;	parity check
	mov	cl,30
	xor	bx,bx
	dec	bx
evil:	inc	bx		; Increment number to test
	jpo	.next		; If parity is odd, number is not evil
	mov	al,bl		; Otherwise, output the number
	call	outal
	dec	cx		; One fewer left
.next:	test	cx,cx
	jnz	evil		; Next evil number
	call	outnl
	;;;	For the odious numbers it is the same
	mov	cl,30
	xor	bx,bx
	dec	bx
odious:	inc	bx
	jpe	.next 		; Except this time we skip the evil numbers
	mov	al,bl
	call	outal
	dec	cx
.next:	test	cx,cx
	jnz	odious
	;;;	Print newline
outnl:	mov	ah,2
	mov	dl,13
	int	21h
	mov	dl,10
	int	21h
	ret
	;;;	Print 2-digit number in AL
outal:	aam
	add 	ax,3030h
	xchg	dx,ax
	xchg	dl,dh
	mov	ah,2
	int	21h
	xchg	dl,dh
	int	21h
	mov 	dl,' '
	int	21h
	ret
Output:
01 02 02 04 03 06 06 05 06 08 09 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
00 03 05 06 09 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
01 02 04 07 08 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Ada

Specification and implementation of an auxiliary package "Population_Count". The same package is used for Pernicious numbers#Ada

with Interfaces;

package Population_Count is
   subtype Num is Interfaces.Unsigned_64;
   function Pop_Count(N: Num) return Natural;
end Population_Count;
package body Population_Count is
   
   function Pop_Count(N: Num) return Natural is
      use Interfaces;
      K5555:  constant Unsigned_64 := 16#5555555555555555#;
      K3333:  constant Unsigned_64 := 16#3333333333333333#;
      K0f0f:  constant Unsigned_64 := 16#0f0f0f0f0f0f0f0f#;
      K0101:  constant Unsigned_64 := 16#0101010101010101#;
      X: Unsigned_64 := N;
   begin
      X :=  X            - (Shift_Right(X, 1)   and k5555); 
      X := (X and k3333) + (Shift_Right(X, 2)   and k3333); 
      X := (X            +  (Shift_Right(X, 4)) and K0f0f); 
      X := Shift_Right((x * k0101), 56); 
      return Natural(X);
   end Pop_Count;
      
end Population_Count;

The main program:

with Ada.Text_IO, Population_Count; use Ada.Text_IO; use Population_Count;

procedure Test_Pop_Count is
   
   X: Num; use type Num;
   
begin
   Put("Pop_Cnt(3**i):"); -- print pop_counts of powers of three
   X := 1; -- X=3**0
   for I in 1 .. 30 loop
      Put(Natural'Image(Pop_Count(X)));
      X := X * 3; 
   end loop;
   New_Line;
   
   Put("Evil:         ");    -- print first thirty evil numbers
   X := 0;
   for I in 1 .. 30 loop
      while Pop_Count(X) mod 2 /= 0 loop -- X is not evil
         X := X + 1;
      end loop;
      Put(Num'Image(X));
      X := X + 1;
   end loop;
   New_Line;
   
   Put("Odious:       "); -- print thirty oudous numbers
   X := 1;
   for I in 1 .. 30 loop 
      while Pop_Count(X) mod 2 /= 1 loop -- X is not odious
         X := X + 1;
      end loop;
      Put(Num'Image(X));
      X := X + 1;
   end loop;
   New_Line;
end Test_Pop_Count;
Output:
Pop_Cnt(3**i): 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:          0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious:        1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

ALGOL 68

# returns the population count (number of bits on) of the non-negative       #
# integer n                                                                  #
PROC population count = ( LONG INT n )INT:
     BEGIN
        LONG INT number := n;
        INT      result := 0;
        WHILE number > 0 DO
            IF ODD number THEN result +:= 1 FI;
            number OVERAB 2
        OD;
        result
     END # population # ;

# population count of 3^0, 3^1, 3*2, ..., 3^29                               #
LONG INT  power of three := 1;
print( ( "3^x pop counts:" ) );
FOR power FROM 0 TO 29 DO
    print( ( " ", whole( population count( power of three ), 0 ) ) );
    power of three *:= 3
OD;
print( ( newline ) );
# print the first thirty evil numbers (even population count)                #
INT evil count := 0;
print( ( "evil numbers  :" ) );
FOR n FROM 0 WHILE evil count < 30 DO
    IF NOT ODD population count( n ) THEN
        print( ( " ", whole( n, 0 ) ) );
        evil count +:= 1
    FI
OD;
print( ( newline ) );
# print the first thirty odious numbers (odd population count)               #
INT odious count := 0;
print( ( "odious numbers:" ) );
FOR n WHILE odious count < 30 DO
    IF ODD population count( n ) THEN
        print( ( " ", whole( n, 0 ) ) );
        odious count +:= 1
    FI
OD;
print( ( newline ) )
Output:
3^x pop counts: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil numbers  : 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious numbers: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

ALGOL W

begin
    % returns the population count (number of bits on) of the non-negative integer n %
    integer procedure populationCount( integer value n ) ;
            begin
                integer v, count;
                v     := n;
                count := 0;
                while v > 0 do begin
                    if odd( v ) then count := count + 1;
                    v     := v div 2
                end while_v_gt_0 ;
                count
            end populationCount ;
    % returns the sum of population counts of the elements of the array n            %
    %         the bounds of n must be 1 :: length                                    %
    integer procedure arrayPopulationCount( integer array n ( * ); integer value length ) ;
            begin
                integer count;
                count := 0;
                for i := 1 until length do count := count + populationCount( n( i ) );
                count
            end arrayPopulationCount ;
    begin %task requirements %
        integer array power( 1 :: 8 );
        integer n, count, carry;
        % population counts of the first 30 powers of three %
        % Algol W integers are 32-bit, so we simulate 64-bit with an array of integers %
        % the only operation we need is multiplication by 3                            %
        % we use 8 bits of each number                                                 %
        % start with 3^0, which is 1 %
        for i := 1 until 8 do power( i ) := 0;
        power( 1 ) := 1;
        write( i_w := 1, s_w := 0, "3^x  population: ", arrayPopulationCount( power, 8 ) );
        for p := 1 until 29 do begin
            carry := 0;
            for b := 1 until 8 do begin
                integer bValue;
                bValue     := ( power( b ) * 3 ) + carry;
                carry      := bValue div 256;
                power( b ) := bValue rem 256
            end for_b ;
            writeon( i_w := 1, s_w := 0, " ", arrayPopulationCount( power, 8 ) )
        end for_p ;
   
        % evil numbers (even population count) %
        write( "evil    numbers:" );
        n     := 0;
        count := 0;
        while count < 30 do begin
            if not odd( populationCount( n ) ) then begin
                writeon( i_w := 1, s_w := 0, " ", n );
                count := count + 1
            end if_not_odd_populationCount ;
            n := n + 1
        end evil_numbers_loop ;

        % odious numbers (odd population count %
        write( "odious  numbers:" );
        n     := 0;
        count := 0;
        while count < 30 do begin
            if odd( populationCount( n ) ) then begin
                writeon( i_w := 1, s_w := 0, " ", n );
                count := count + 1
            end if_odd_populationCount ;
            n := n + 1
        end odious_numbers_loop
   end
end.
Output:
3^x  population: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil    numbers: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious  numbers: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

APL

 APL (DYALOG APL)
 popDemo{⎕IO0
     N
   ⍝ popCount: Does a popCount of integers (8-32 bits) or floats (64-bits) that can be represented as integers
     popCount{
         i2bits{∊+/2¯1}  ⍝ Use ⊥⍣¯1 (inverted decode) for ⊤ (encode) to automatically detect nubits needed
         +/i2bits            ⍝ Count the bits
     }¨

     act3popCount 3*⍳N

     MN×2
     actEvilN{/⍨0=2|popCount }M
     actOdiousN{/⍨1=2|popCount }M

     'powers 3'act3
     'evil    'actEvil
     'odious  'actOdious

   ⍝ Extra: Validate answers are correct
   ⍝    Actual answers
     ans31 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
     ansEvil0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
     ansOdious1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

     '***Passes' '***Fails'(ans3act3)(actEvilansEvil)(actOdiousansOdious)
 }
Output:
    popDemo 30
powers 3   1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil       0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious     1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 
***Passes

AppleScript

Functional

Translation of: JavaScript
--------------------- POPULATION COUNT ---------------------

-- populationCount :: Int -> Int
on populationCount(n)
    -- The number of non-zero bits in the binary
    -- representation of the integer n.
    
    script go
        on |λ|(x)
            if 0 < x then
                Just({x mod 2, x div 2})
            else
                Nothing()
            end if
        end |λ|
    end script
    
    integerSum(unfoldr(go, n))
end populationCount


--------------------------- TEST ---------------------------
on run
    set {evens, odds} to partition(compose(even, populationCount), ¬
        enumFromTo(0, 59))
    
    unlines({"Population counts of the first 30 powers of three:", ¬
        tab & showList(map(compose(populationCount, raise(3)), ¬
        enumFromTo(0, 29))), ¬
        "", ¬
        "First thirty 'evil' numbers:", ¬
        tab & showList(evens), ¬
        "", ¬
        "First thirty 'odious' numbers:", ¬
        tab & showList(odds)})
end run


------------------------- GENERIC --------------------------

-- Just :: a -> Maybe a
on Just(x)
    -- Constructor for an inhabited Maybe (option type) value.
    -- Wrapper containing the result of a computation.
    {type:"Maybe", Nothing:false, Just:x}
end Just


-- Nothing :: Maybe a
on Nothing()
    -- Constructor for an empty Maybe (option type) value.
    -- Empty wrapper returned where a computation is not possible.
    {type:"Maybe", Nothing:true}
end Nothing


-- compose (<<<) :: (b -> c) -> (a -> b) -> a -> c
on compose(f, g)
    script
        property mf : mReturn(f)
        property mg : mReturn(g)
        on |λ|(x)
            mf's |λ|(mg's |λ|(x))
        end |λ|
    end script
end compose


-- enumFromTo :: Int -> Int -> [Int]
on enumFromTo(m, n)
    if m  n then
        set lst to {}
        repeat with i from m to n
            set end of lst to i
        end repeat
        lst
    else
        {}
    end if
end enumFromTo


-- even :: Int -> Bool
on even(x)
    0 = x mod 2
end even


-- foldl :: (a -> b -> a) -> a -> [b] -> a
on foldl(f, startValue, xs)
    tell mReturn(f)
        set v to startValue
        set lng to length of xs
        repeat with i from 1 to lng
            set v to |λ|(v, item i of xs, i, xs)
        end repeat
        return v
    end tell
end foldl


-- map :: (a -> b) -> [a] -> [b]
on map(f, xs)
    -- The list obtained by applying f
    -- to each element of xs.
    tell mReturn(f)
        set lng to length of xs
        set lst to {}
        repeat with i from 1 to lng
            set end of lst to |λ|(item i of xs, i, xs)
        end repeat
        return lst
    end tell
end map


-- mReturn :: First-class m => (a -> b) -> m (a -> b)
on mReturn(f)
    -- 2nd class handler function lifted into 1st class script wrapper. 
    if script is class of f then
        f
    else
        script
            property |λ| : f
        end script
    end if
end mReturn

-- partition :: (a -> Bool) -> [a] -> ([a], [a])
on partition(f, xs)
    tell mReturn(f)
        set ys to {}
        set zs to {}
        repeat with x in xs
            set v to contents of x
            if |λ|(v) then
                set end of ys to v
            else
                set end of zs to v
            end if
        end repeat
    end tell
    {ys, zs}
end partition

-- raise :: Num -> Int -> Num
on raise(m)
    script
        on |λ|(n)
            m ^ n
        end |λ|
    end script
end raise


-- integerSum :: [Num] -> Num
on integerSum(xs)
    script addInt
        on |λ|(a, b)
            a + (b as integer)
        end |λ|
    end script
    
    foldl(addInt, 0, xs)
end integerSum


-- intercalate :: String -> [String] -> String
on intercalate(delim, xs)
    set {dlm, my text item delimiters} to ¬
        {my text item delimiters, delim}
    set s to xs as text
    set my text item delimiters to dlm
    s
end intercalate


-- showList :: [a] -> String
on showList(xs)
    "[" & intercalate(",", map(my str, xs)) & "]"
end showList


-- str :: a -> String
on str(x)
    x as string
end str


-- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
on unfoldr(f, v)
    -- A list derived from a simple value.
    -- Dual to foldr.
    -- unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
    -- -> [10,9,8,7,6,5,4,3,2,1] 
    set xr to {v, v} -- (value, remainder)
    set xs to {}
    tell mReturn(f)
        repeat -- Function applied to remainder.
            set mb to |λ|(item 2 of xr)
            if Nothing of mb then
                exit repeat
            else -- New (value, remainder) tuple,
                set xr to Just of mb
                -- and value appended to output list.
                set end of xs to item 1 of xr
            end if
        end repeat
    end tell
    return xs
end unfoldr


-- unlines :: [String] -> String
on unlines(xs)
    -- A single string formed by the intercalation
    -- of a list of strings with the newline character.
    set {dlm, my text item delimiters} to ¬
        {my text item delimiters, linefeed}
    set s to xs as text
    set my text item delimiters to dlm
    s
end unlines
Output:
Population counts of the first 30 powers of three:
    [1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]

First thirty 'evil' numbers:
    [0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]

First thirty 'odious' numbers:
    [1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]

Straightforward

on popCount(n)
    set counter to 0
    repeat until (n is 0)
        set counter to counter + n mod 2
        set n to n div 2
    end repeat
    
    return counter div 1
end popCount

-- Task code:
-- Get the popcounts of the first 30 powers of 3.
set list1 to {}
repeat with i from 0 to 29
    set end of list1 to popCount(3 ^ i)
end repeat

-- Collate the integers from 0 to 59 according to the evenness or oddness of their popcounts.
-- In any even number of consecutive integers, exactly half are "evil" and half "odious". Thus thirty of each here.
set lists2and3 to {{}, {}}
repeat with i from 0 to 59
    set end of item (popCount(i) mod 2 + 1) of lists2and3 to i
end repeat

-- Arrange the results for display.
set astid to AppleScript's text item delimiters
set AppleScript's text item delimiters to space
set {list1, list2, list3} to {list1 as text, beginning of lists2and3 as text, end of lists2and3 as text}
set AppleScript's text item delimiters to linefeed
set output to {"Popcounts of 1st thirty powers of 3:", list1, "1st thirty evil numbers:", list2, "1st thirty odious numbers:", list3} ¬
    as text
set AppleScript's text item delimiters to astid
return output
Output:
"Popcounts of 1st thirty powers of 3:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
1st thirty evil numbers:
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
1st thirty odious numbers:
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59"

Arturo

popCount: function [num][
    size select split to :string as.binary num 'x -> x="1"
]

print "population count for the first thirty powers of 3:"
print map 0..29 => [popCount 3^&]

print "first thirty evil numbers"
print take select 0..100 => [even? popCount &] 30

print "first thirty odious numbers"
print take select 0..100 => [odd? popCount &] 30
Output:
population count for the first thirty powers of 3:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
first thirty evil numbers
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
first thirty odious numbers
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

AutoHotkey

Loop, 30
	Out1 .= PopCount(3 ** (A_Index - 1)) " "
Loop, 60
	i := A_Index - 1
	, PopCount(i) & 0x1 ? Out3 .= i " " : Out2 .= i " "
MsgBox, % "3^x:`t" Out1 "`nEvil:`t" Out2 "`nOdious:`t" Out3

PopCount(x) {	;https://en.wikipedia.org/wiki/Hamming_weight#Efficient_implementation
	x -= (x >> 1) & 0x5555555555555555
	, x := (x & 0x3333333333333333) + ((x >> 2) & 0x3333333333333333)
	, x := (x + (x >> 4)) & 0x0f0f0f0f0f0f0f0f
	return (x * 0x0101010101010101) >> 56
}
Output:
3^x:	1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
Evil:	0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
Odious:	1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 

AWK

# syntax: GAWK -f POPULATION_COUNT.AWK
# converted from VBSCRIPT
BEGIN {
    nmax = 30
    b = 3
    n = 0
    bb = 1
    for (i=1; i<=nmax; i++) {
      list = list pop_count(bb) " "
      bb *= b
    }
    printf("%s^n: %s\n",b,list)
    for (j=0; j<=1; j++) {
      c = (j == 0) ? "evil" : "odious"
      i = n = 0
      list = ""
      while (n < nmax) {
        if (pop_count(i) % 2 == j) {
          n++
          list = list i " "
        }
        i++
      }
      printf("%s: %s\n",c,list)
    }
    exit(0)
}
function pop_count(xx,  xq,xr,y) {
    while (xx > 0) {
      xq = int(xx / 2)
      xr = xx - xq * 2
      if (xr == 1) { y++ }
      xx = xq
    }
    return(y)
}
Output:
3^n: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

BASIC

BASIC256

Translation of: Yabasic
print "Pop cont (3^x): ";
for i = 0 to 29
    print population(3^i); " "; #los últimos números no los muestra correctamente
next i

print : print
print "Evil numbers:   ";
call EvilOdious(30, 0)

print : print
print "Odious numbers: ";
call EvilOdious(30, 1)
end

subroutine EvilOdious(limit, type)
    i = 0 : cont = 0

    do
        eo = (population(i) mod 2)
        if (type and eo) or (not type and not eo) then
            cont += 1 : print i; " ";
        end if
        i += 1
    until (cont = limit)
end subroutine

function population(number)
    popul = 0

    binary$ = tobinary(number)
    for i = 1 to length(binary$)
        popul += int(mid(binary$, i, 1))
    next i
    return popul
end function

Run BASIC

function tobin$(num)
  bin$ = ""
  if num = 0 then bin$ = "0"
  
  while num >= 1
    num = num / 2
    X$ = str$(num)
    D$ = "": F$ = ""
    
    for i = 1 to len(X$)
      L$ = mid$(X$, i, 1)
      if L$ <> "." then
        D$ = D$ + L$
      else
        F$ = F$ + right$(X$, len(X$) - i)
        exit for
      end if
    next i
    
    if F$ = "" then B$ = "0" else B$ = "1"
    bin$ = bin$ + B$
    num = val(D$)
  wend
  B$ = ""
  for i = len(bin$) to 1 step -1
    B$ = B$ + mid$(bin$, i, 1)
  next i
  tobin$ = B$
end function

function population(number)
  popul = 0
  
  'digito$ = tobin$(number)
  'print tobin$(number)
  for i = 1 to len(tobin$(number))
    popul = popul + val(mid$(tobin$(number), i, 1))
  next i
  population = popul
end function

sub evilodious limit, tipo
  i = 0
  cont = 0
  
  while 1
    eo = (population(i) mod 2)
    if (tipo and eo = 1) or ((not(tipo) and not(eo)) = 1) then
      cont = cont + 1: print i; " ";
    end if
    i = i + 1
    if cont = limit then exit while
  wend
end sub

print "Pop cont (3^x): ";
for i = 0 to 14
  print population(3 ^ i); " ";
next i

print
print "Evil numbers:   "; 
call evilodious 15, 0

print
print "Odious numbers: ";
call evilodious 15, 1
end

BCPL

get "libhdr"

// Definitions
let popcount(n) = n=0 -> 0, (n&1) + popcount(n >> 1)
let evil(n)     = (popcount(n) & 1) = 0
let odious(n)   = (popcount(n) & 1) = 1

// The BCPL word size is implementation-dependent,
// but very unlikely to be big enough to store 3^29.
// This implements a 48-bit integer using byte strings.
let move48(dest, src) be
    for i=0 to 5 do dest%i := src%i

let set48(dest, n) be
    for i=5 to 0 by -1
    $(  dest%i := n & #XFF
        n := n >> 8
    $)
    
let add48(dest, src) be
$(  let temp = ? and carry = 0
    for i=5 to 0 by -1
    $(  temp := dest%i + src%i + carry
        carry := temp > #XFF -> 1, 0
        dest%i := temp & #XFF
    $)
$)

let mul3(n) be
$(  let temp = vec 2  // big enough even on a 16-bit machine
    move48(temp, n)
    add48(n, n)
    add48(n, temp)
$)

let popcount48(n) = valof
$(  let total = 0
    for i=0 to 5 do 
        total := total + popcount(n%i)
    resultis total
$)

// print the first N numbers 
let printFirst(amt, prec) be
$(  let seen = 0 and n = 0
    until seen >= amt
    $(  if prec(n)
        $(  writed(n, 3)
            seen := seen + 1
        $)
        n := n + 1
    $)
    wrch('*N')
$)

let start() be 
$(  let pow3 = vec 2
    
    // print 3^0 to 3^29
    set48(pow3, 1)
    for i = 0 to 29
    $(  writed(popcount48(pow3), 3)
        mul3(pow3)
    $)
    wrch('*N')
    
    // print the first 30 evil and odious numbers 
    printFirst(30, evil)
    printFirst(30, odious)
$)
Output:
  1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
  0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
  1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

BQN

PopCount  {(2|𝕩)+𝕊×⌊𝕩÷2}
Odious  2|PopCount
Evil  ¬Odious

_List  {𝕩↑𝔽¨/↕2×𝕩}
>PopCount¨ 330, 
  Evil _List 30, 
  Odious _List 30
Output:
┌─                                                                                      
╵ 1 2 2 4 3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25  
  0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58  
  1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59  
                                                                                       ┘

C

Works with: GCC
#include <stdio.h>

int main() {
  {
    unsigned long long n = 1;
    for (int i = 0; i < 30; i++) {
      // __builtin_popcount() for unsigned int
      // __builtin_popcountl() for unsigned long
      // __builtin_popcountll() for unsigned long long
      printf("%d ", __builtin_popcountll(n));
      n *= 3;
    }
    printf("\n");
  }

  int od[30];
  int ne = 0, no = 0;
  printf("evil  : ");
  for (int n = 0; ne+no < 60; n++) {
    if ((__builtin_popcount(n) & 1) == 0) {
      if (ne < 30) {
	printf("%d ", n);
	ne++;
      }
    } else {
      if (no < 30) {
	od[no++] = n;
      }
    }
  }
  printf("\n");
  printf("odious: ");
  for (int i = 0; i < 30; i++) {
    printf("%d ", od[i]);
  }
  printf("\n");

  return 0;
}
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil  : 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 


GCC's builtin doesn't exist prior to 3.4, and the LL version is broken in 3.4 to 4.1. In 4.2+, if the platform doesn't have a good popcount instruction or isn't enabled (e.g. not compiled with -march=native), it typically emits unoptimized code which is over 2x slower than the C below. Alternative:

#if defined(__POPCNT__) && defined(__GNUC__) && (__GNUC__> 4 || (__GNUC__== 4 && __GNUC_MINOR__> 1))
#define HAVE_BUILTIN_POPCOUNTLL
#endif
static uint64_t bitcount64(uint64_t b) {
  b -= (b >> 1) & 0x5555555555555555;
  b = (b & 0x3333333333333333) + ((b >> 2) & 0x3333333333333333);
  b = (b + (b >> 4)) & 0x0f0f0f0f0f0f0f0f;
  return (b * 0x0101010101010101) >> 56;
}
/* For 32-bit, an 8-bit table may or may not be a little faster */
static uint32_t bitcount32(uint32_t b) {
  b -= (b >> 1) & 0x55555555;
  b = (b & 0x33333333) + ((b >> 2) & 0x33333333);
  b = (b + (b >> 4)) & 0x0f0f0f0f;
  return (b * 0x01010101) >> 24;
}

C#

using System;
using System.Linq;

namespace PopulationCount
{
    class Program
    {
        private static int PopulationCount(long n)
        {
            string binaryn = Convert.ToString(n, 2);
            return binaryn.ToCharArray().Where(t => t == '1').Count();
        }

        static void Main(string[] args)
        {
            Console.WriteLine("Population Counts:");
            Console.Write("3^n :   ");

            int count = 0;

            while (count < 30)
            {
                double n = Math.Pow(3f, (double)count);
                int popCount = PopulationCount((long)n);
                Console.Write(string.Format("{0} ", popCount));
                count++;
            }

            Console.WriteLine();
            Console.Write("Evil:   ");

            count = 0;
            int i = 0;

            while (count < 30)
            {
                int popCount = PopulationCount(i);

                if (popCount % 2 == 0)
                {
                    count++;
                    Console.Write(string.Format("{0} ", i));
                }

                i++;
            }

            Console.WriteLine();
            Console.Write("Odious: ");

            count = 0;
            i = 0;

            while (count < 30)
            {
                int popCount = PopulationCount(i);

                if (popCount % 2 != 0)
                {
                    count++;
                    Console.Write(string.Format("{0} ", i));
                }

                i++;
            }

            Console.ReadKey();
        }
    }
}
Output:
Population Counts:
3^n :   1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

C++

Works with: C++11
#include <iostream>
#include <bitset>
#include <climits>

size_t popcount(unsigned long long n) {
  return std::bitset<CHAR_BIT * sizeof n>(n).count();
}

int main() {
  {
    unsigned long long n = 1;
    for (int i = 0; i < 30; i++) {
      std::cout << popcount(n) << " ";
      n *= 3;
    }
    std::cout << std::endl;
  }

  int od[30];
  int ne = 0, no = 0;
  std::cout << "evil  : ";
  for (int n = 0; ne+no < 60; n++) {
    if ((popcount(n) & 1) == 0) {
      if (ne < 30) {
	std::cout << n << " ";
	ne++;
      }
    } else {
      if (no < 30) {
	od[no++] = n;
      }
    }
  }
  std::cout << std::endl;
  std::cout << "odious: ";
  for (int i = 0; i < 30; i++) {
    std::cout << od[i] << " ";
  }
  std::cout << std::endl;

  return 0;
}
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil  : 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 


Clojure

(defn population-count [n]
  (Long/bitCount n))         ; use Java inter-op

(defn exp [n pow]
  (reduce * (repeat pow n)))

(defn evil? [n]
  (even? (population-count n)))

(defn odious? [n]
  (odd? (population-count n)))

;;
;; Clojure's support for generating "lazily-evaluated" infinite sequences can
;; be used to generate the requested output sets.  We'll create some infinite
;; sequences, and only as many items will be computed as are "pulled" by 'take'.
;;
(defn integers []
  (iterate inc 0))

(defn powers-of-n [n]
  (map #(exp n %) (integers)))

(defn evil-numbers []
  (filter evil? (integers)))

(defn odious-numbers []
  (filter odious? (integers)))
Output:
(take 5 (integers))       ; ==> (0 1 2 3 4)
(take 5 (powers-of-n 3))  ; ==> (1 3 9 27 81)
(take 5 (evil-numbers))   ; ==> (0 3 5 6 9)

;; Population Counts for first 30 powers of 3:
(take 30 (map population-count (powers-of-n 3)))
; ==> (1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25)

;; First 30 'evil' numbers:
(take 30 (evil-numbers))
; ==> (0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58)

;; First 30 'odious' numbers:
(take 30 (odious-numbers))
; ==> (1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59)

CLU

pop_count = proc (n: int) returns (int)
    p: int := 0
    while n>0 do
        p := p + n//2
        n := n/2
    end
    return(p)
end pop_count

evil = proc (n: int) returns (bool)
    return(pop_count(n)//2 = 0)
end evil

odious = proc (n: int) returns (bool)
    return(~evil(n))
end odious

first = iter (n: int, p: proctype (int) returns (bool)) yields (int)
    i: int := 0
    while n>0 do
        if p(i) then
            yield(i)
            n := n-1
        end
        i := i+1
    end
end first

start_up = proc ()
    po: stream := stream$primary_output()
    
    for i: int in int$from_to(0,29) do
        stream$putright(po, int$unparse(pop_count(3**i)), 3)
    end
    stream$putl(po, "")
    
    for i: int in first(30, evil) do
        stream$putright(po, int$unparse(i), 3)
    end
    stream$putl(po, "")
    
    for i: int in first(30, odious) do
        stream$putright(po, int$unparse(i), 3)
    end
    stream$putl(po, "")
end start_up
Output:
  1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
  0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
  1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

COBOL

       IDENTIFICATION DIVISION.
       PROGRAM-ID.  HAMMING.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 POPCOUNT-VARIABLES.
          03 POPCOUNT-IN       PIC 9(15)V9.
          03 FILLER            REDEFINES POPCOUNT-IN.
             05 POPCOUNT-REST  PIC 9(15).
             05 FILLER         PIC 9.
                88 BIT-IS-SET  VALUE 5.
          03 POPCOUNT-OUT      PIC 99.
          03 FILLER            REDEFINES POPCOUNT-OUT.
             05 FILLER         PIC 9.
             05 FILLER         PIC 9.
                88 EVIL        VALUES 0, 2, 4, 6, 8.
                88 ODIOUS      VALUES 1, 3, 5, 7, 9.

       01 STATE-VARIABLES.
          03 CUR-POWER-3       PIC 9(15) VALUE 1.
          03 CUR-EVIL-NUM      PIC 99 VALUE 0.
          03 CUR-ODIOUS-NUM    PIC 99 VALUE 0.
          03 LINE-INDEX        PIC 99 VALUE 1.

       01 OUTPUT-FORMAT.
          03 LINENO            PIC Z9.
          03 FILLER            PIC X VALUE '.'.
          03 FILLER            PIC XX VALUE SPACES.
          03 OUT-POW3          PIC Z9.
          03 FILLER            PIC X(4) VALUE SPACES.
          03 OUT-EVIL          PIC Z9.
          03 FILLER            PIC X(4) VALUE SPACES.
          03 OUT-ODIOUS        PIC Z9.

       PROCEDURE DIVISION.
       BEGIN.
           DISPLAY "     3^   EVIL   ODD"
           PERFORM MAKE-LINE 30 TIMES.
           STOP RUN.
      
       MAKE-LINE.
           MOVE LINE-INDEX TO LINENO.
           MOVE CUR-POWER-3 TO POPCOUNT-IN.
           PERFORM FIND-POPCOUNT.
           MOVE POPCOUNT-OUT TO OUT-POW3.
           PERFORM FIND-EVIL.
           MOVE CUR-EVIL-NUM TO OUT-EVIL.
           PERFORM FIND-ODIOUS.
           MOVE CUR-ODIOUS-NUM TO OUT-ODIOUS.
           DISPLAY OUTPUT-FORMAT.
           MULTIPLY 3 BY CUR-POWER-3.
           ADD 1 TO CUR-EVIL-NUM.
           ADD 1 TO CUR-ODIOUS-NUM.
           ADD 1 TO LINE-INDEX.
 
       FIND-EVIL.
           MOVE CUR-EVIL-NUM TO POPCOUNT-IN.
           PERFORM FIND-POPCOUNT.
           IF NOT EVIL, ADD 1 TO CUR-EVIL-NUM, GO TO FIND-EVIL.

       FIND-ODIOUS.
           MOVE CUR-ODIOUS-NUM TO POPCOUNT-IN.
           PERFORM FIND-POPCOUNT.
           IF NOT ODIOUS, ADD 1 TO CUR-ODIOUS-NUM, GO TO FIND-ODIOUS.
       
       FIND-POPCOUNT.
           MOVE 0 TO POPCOUNT-OUT.
           PERFORM PROCESS-BIT UNTIL POPCOUNT-IN IS EQUAL TO ZERO.

       PROCESS-BIT.
           DIVIDE 2 INTO POPCOUNT-IN.
           IF BIT-IS-SET, ADD 1 TO POPCOUNT-OUT.
           MOVE POPCOUNT-REST TO POPCOUNT-IN.
Output:
     3^   EVIL   ODD
 1.   1     0     1
 2.   2     3     2
 3.   2     5     4
 4.   4     6     7
 5.   3     9     8
 6.   6    10    11
 7.   6    12    13
 8.   5    15    14
 9.   6    17    16
10.   8    18    19
11.   9    20    21
12.  13    23    22
13.  10    24    25
14.  11    27    26
15.  14    29    28
16.  15    30    31
17.  11    33    32
18.  14    34    35
19.  14    36    37
20.  17    39    38
21.  17    40    41
22.  20    43    42
23.  19    45    44
24.  22    46    47
25.  16    48    49
26.  18    51    50
27.  24    53    52
28.  30    54    55
29.  25    57    56
30.  25    58    59

Common Lisp

(format T "3^x: ~{~a ~}~%" 
        (loop for i below 30 
              collect (logcount (expt 3 i))))

(multiple-value-bind 
  (evil odious)
  (loop for i below 60
        if (evenp (logcount i)) collect i into evil
        else collect i into odious
        finally (return (values evil odious)))
  (format T "evil: ~{~a ~}~%" evil)
  (format T "odious: ~{~a ~}~%" odious))
Output:
3^x: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Crystal

Translation of: Ruby

For Crystal select|reject are inherently lazy enumerators, and has popcount for upto unsigned 64-bit integers.

struct Int
  def evil?
    self >= 0 && popcount.even?
  end
end
 
puts "Powers of 3:", (0...30).map{|n| (3u64 ** n).popcount}.join(' ') # can also use &** (to prevent arithmetic overflow)
puts "Evil:"  , 0.step.select(&.evil?).first(30).join(' ')
puts "Odious:", 0.step.reject(&.evil?).first(30).join(' ')
Output:
Powers of 3:

1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 Evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

D

void main() {
    import std.stdio, std.algorithm, std.range, core.bitop;

    enum pCount = (ulong n) => popcnt(n & uint.max) + popcnt(n >> 32);
    writefln("%s\nEvil: %s\nOdious: %s",
             uint.max.iota.map!(i => pCount(3L ^^ i)).take(30),
             uint.max.iota.filter!(i => pCount(i) % 2 == 0).take(30),
             uint.max.iota.filter!(i => pCount(i) % 2).take(30));
}
Output:
[1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
Evil: [0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]
Odious: [1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]

Delphi

Translation of: C#
program Population_count;

{$APPTYPE CONSOLE}

{$R *.res}

uses
  System.SysUtils,
  Math;

function PopulationCount(AInt: UInt64): Integer;
begin
  Result := 0;
  repeat
    inc(Result, (AInt and 1));
    AInt := AInt div 2;
  until (AInt = 0);
end;

var
  i, count: Integer;
  n: Double;
  popCount: Integer;

begin
  Writeln('Population Counts:'#10);
  Write('3^n :   ');
  for i := 0 to 30 do
  begin
    n := Math.Power(3, i);
    popCount := PopulationCount(round(n));
    Write(Format('%d ', [popCount]));
  end;
  Writeln(#10#10'Evil:   ');

  count := 0;
  i := 0;
  while (count < 30) do
  begin
    popCount := PopulationCount(i);
    if not Odd(popCount) then
    begin
      inc(count);
      Write(Format('%d ', [i]));
    end;
    inc(i);
  end;
  Writeln(#10#10'Odious: ');

  count := 0;
  i := 0;
  while (count < 30) do
  begin
    popCount := PopulationCount(i);
    if Odd(popCount) then
    begin
      inc(count);
      Write(Format('%d ', [i]));
    end;
    inc(i);
  end;

  readln;
end.

EasyLang

func popcnt x .
   while x > 0
      r += x mod 2
      x = x div 2
   .
   return r
.
proc show3 . .
   write "3^n:"
   bb = 1
   for i = 1 to 30
      write " " & popcnt bb
      bb *= 3
   .
   print ""
.
proc show s$ x . .
   write s$
   while n < 30
      if popcnt i mod 2 = x
         n += 1
         write " " & i
      .
      i += 1
   .
   print ""
.
show3
show "evil:" 0
show "odious:" 1


Elixir

defmodule Population do

  def count(n), do: count(<<n :: integer>>, 0)

  defp count(<<>>, acc), do: acc

  defp count(<<bit :: integer-1, rest :: bitstring>>, sum), do: count(rest, sum + bit)
  
  def evil?(n), do: n >= 0 and rem(count(n),2) == 0
  
  def odious?(n), do: n >= 0 and rem(count(n),2) == 1

end

IO.puts "Population count of the first thirty powers of 3:"
IO.inspect Stream.iterate(1, &(&1*3)) |> Enum.take(30) |> Enum.map(&Population.count(&1))
IO.puts "first thirty evil numbers:"
IO.inspect Stream.iterate(0, &(&1+1)) |> Stream.filter(&Population.evil?(&1)) |> Enum.take(30)
IO.puts "first thirty odious numbers:"
IO.inspect Stream.iterate(0, &(&1+1)) |> Stream.filter(&Population.odious?(&1)) |> Enum.take(30)
Output:
Population count of the first thirty powers of 3:
[1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
first thirty evil numbers:
[0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]
first thirty odious numbers:
[1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]

Erlang

-module(population_count).
-export([popcount/1]).

-export([task/0]).

popcount(N) ->
    popcount(N,0).

popcount(0,Acc) ->
    Acc;
popcount(N,Acc) ->
    popcount(N div 2, Acc + N rem 2).

threes(_,0,Acc) ->
    lists:reverse(Acc);
threes(Threes,N,Acc) ->
    threes(Threes * 3, N-1, [popcount(Threes)|Acc]).

threes(N) ->
    threes(1,N,[]).

evil(_,0,Acc) ->
    lists:reverse(Acc);
evil(N,Count,Acc) ->
    case popcount(N) rem 2 of
        0 ->
            evil(N+1,Count-1,[N|Acc]);
        1 ->
            evil(N+1,Count,Acc)
    end.
evil(Count) ->
    evil(0,Count,[]).

odious(_,0,Acc) ->
    lists:reverse(Acc);
odious(N,Count,Acc) ->
    case popcount(N) rem 2 of
        1 ->
            odious(N+1,Count-1,[N|Acc]);
        0 ->
            odious(N+1,Count,Acc)
    end.
odious(Count) ->
    odious(1,Count,[]).


task() ->
    io:format("Powers of 3: ~p~n",[threes(30)]),
    io:format("Evil:~p~n",[evil(30)]),
    io:format("Odious:~p~n",[odious(30)]).
Output:
61> population_count:task().
Powers of 3: [1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,
 25]
Evil:[0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,
      51,53,54,57,58]
Odious:[1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,
        50,52,55,56,59]
ok

F#

// Population count. Nigel Galloway: February 18th., 2021
let pC n=Seq.unfold(fun n->match n/2L,n%2L with (0L,0L)->None |(n,g)->Some(g,n))n|>Seq.sum
printf "pow3  :"; [0..29]|>List.iter((pown 3L)>>pC>>(printf "%3d")); printfn ""
printf "evil  :"; Seq.initInfinite(int64)|>Seq.filter(fun n->(pC n) &&& 1L=0L)|>Seq.take 30|>Seq.iter(printf "%3d"); printfn ""
printf "odious:"; Seq.initInfinite(int64)|>Seq.filter(fun n->(pC n) &&& 1L=1L)|>Seq.take 30|>Seq.iter(printf "%3d"); printfn ""
Output:
pow3  :  1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil  :  0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious:  1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Factor

USING: formatting kernel lists lists.lazy math math.bitwise
math.functions namespaces prettyprint.config sequences ;

: 3^n ( obj -- obj' ) [ 3 swap ^ bit-count ] lmap-lazy ;
: evil ( obj -- obj' ) [ bit-count even? ] lfilter ;
: odious ( obj -- obj' ) [ bit-count odd? ] lfilter ;

100 margin set 0 lfrom [ 3^n ] [ evil ] [ odious ] tri
[ 30 swap ltake list>array ] tri@
"3^n:    %u\nEvil:   %u\nOdious: %u\n" printf
Output:
3^n:    { 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 }
Evil:   { 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 }
Odious: { 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 }

Fermat

Func Popcount(n) = if n = 0 then 0 else if 2*(n\2)=n then Popcount(n\2) else Popcount((n-1)\2)+1 fi fi.
Func Odiousness(n) = p:=Popcount(n);if 2*(p\2) = p then 0 else 1 fi.

for n=0 to 29 do !Popcount(3^n);!' ' od
e:=0
n:=0
while e<30 do if Odiousness(n)=0 then !n;!' ';e:=e+1 fi; n:=n+1 od
e:=0
n:=0
while e<30 do if Odiousness(n)=1 then !n;!' ';e:=e+1 fi; n:=n+1 od

Forth

Works with: Gforth version 0.7.3
: popcnt ( n -- u)  0 swap
   BEGIN dup WHILE tuck 1 AND +  swap 1 rshift REPEAT
   DROP ;
: odious? ( n -- t|f)  popcnt 1 AND ;
: evil? ( n -- t|f)  odious? 0= ;    

CREATE A 30 ,
: task1   1 0  ." 3**i popcnt: "
   BEGIN dup A @ < WHILE
     over popcnt .  1+ swap 3 * swap
   REPEAT  DROP DROP CR ;
: task2   0 0  ." evil       : "
   BEGIN dup A @ < WHILE
     over evil? IF over . 1+ THEN swap 1+ swap
   REPEAT  DROP DROP CR ;
: task3   0 0  ." odious     : "
   BEGIN dup A @ < WHILE
     over odious? IF over . 1+ THEN swap 1+ swap
   REPEAT  DROP DROP CR ;
task1 task2 task3 BYE
Output:
3**i popcnt: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil       : 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious     : 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Fortran

Works with: Fortran version 95 and later
program population_count
  implicit none

  integer, parameter :: i64 = selected_int_kind(18)
  integer(i64) :: x
  integer :: i, n
    
  x = 1
  write(*, "(a8)", advance = "no") "3**i :"
  do i = 1, 30
    write(*, "(i3)", advance = "no") popcnt(x)
    x = x * 3
  end do

  write(*,*)
  write(*, "(a8)", advance = "no") "Evil :"
  n = 0
  x = 0 
  do while(n < 30)
    if(mod(popcnt(x), 2) == 0) then
      n = n + 1
      write(*, "(i3)", advance = "no") x
    end if
    x = x + 1
  end do

  write(*,*)
  write(*, "(a8)", advance = "no") "Odious :"
  n = 0
  x = 0 
  do while(n < 30)
    if(mod(popcnt(x), 2) /= 0) then
      n = n + 1
      write(*, "(i3)", advance = "no") x
    end if
    x = x + 1
  end do

contains

integer function popcnt(x)
  integer(i64), intent(in) :: x
  integer :: i

  popcnt = 0
  do i = 0, 63
    if(btest(x, i)) popcnt = popcnt + 1
  end do

end function
end program
Output:
  3**i : 1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
  Evil : 0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious : 1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Free Pascal

The system unit in the RTL (run-time library) shipped with every FPC (Free Pascal compiler) distribution contains the function popCnt. It accepts one integer parameter and is defined for all unsigned integer types. Therefore its implementation is skipped.

program populationCount(input, output, stdErr);
var
	// general advice: iterator variables are _signed_
	iterator: int64;
	// the variable we’d like to count the set bits in
	number: qWord;
	// how many evil numbers we’ve already found
	evilCount: int64;
	// odious numbers
	odiousNumber: array[1..30] of qWord;
	odiousIterator: int64;
begin
	// population count for powers of three
	for iterator := 0 to 29 do
	begin
		number := round(exp(ln(3) * iterator));
		write(popCnt(number):3);
	end;
	writeLn();
	
	// evil numbers
	// (while preserving calculated odious numbers for next sub-task)
	evilCount := 0;
	odiousIterator := low(odiousNumber);
	
	// for-loop: because we (pretend to) don’t know,
	// when and where we’ve found the first 30 numbers of each
	for iterator := 0 to high(iterator) do
	begin
		// implicit typecast: popCnt only accepts _un_-signed integers
		number := iterator;
		if odd(popCnt(number)) then
		begin
			if odiousIterator <= high(odiousNumber) then
			begin
				odiousNumber[odiousIterator] := number;
				inc(odiousIterator);
			end;
		end
		else
		begin
			if evilCount < 30 then
			begin
				write(number:20);
				inc(evilCount);
			end;
		end;
		
		if evilCount + odiousIterator > 60 then
		begin
			break;
		end;
	end;
	writeLn();
	
	// odious numbers
	for number in odiousNumber do
	begin
		write(number:20);
	end;
	writeLn();
end.
Output:
  1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
                   0                   3                   5                   6                   9                  10                  12                  15                  17                  18                  20                  23                  24                  27                  29                  30                  33                  34                  36                  39                  40                  43                  45                  46                  48                  51                  53                  54                  57                  58
                   1                   2                   4                   7                   8                  11                  13                  14                  16                  19                  21                  22                  25                  26                  28                  31                  32                  35                  37                  38                  41                  42                  44                  47                  49                  50                  52                  55                  56                  59

Fōrmulæ

Fōrmulæ programs are not textual, visualization/edition of programs is done showing/manipulating structures but not text. Moreover, there can be multiple visual representations of the same program. Even though it is possible to have textual representation —i.e. XML, JSON— they are intended for storage and transfer purposes more than visualization and edition.

Programs in Fōrmulæ are created/edited online in its website.

In this page you can see and run the program(s) related to this task and their results. You can also change either the programs or the parameters they are called with, for experimentation, but remember that these programs were created with the main purpose of showing a clear solution of the task, and they generally lack any kind of validation.

Solution

Fōrmulæ has an integrated expression BitCount that counts the number of 1's of the binary representation of the number.

However, a function can also be written, as follows:

File:Fōrmulæ - Population count 01.png

Case 1. Display the pop count of the 1st thirty powers of 3

File:Fōrmulæ - Population count 02.png

File:Fōrmulæ - Population count 03.png

Case 2. Display the 1st thirty evil numbers

We need first a function to calculate the first numbers whose population count satisfies a given condition, passed as a lambda expression:

File:Fōrmulæ - Population count 04.png

File:Fōrmulæ - Population count 05.png

File:Fōrmulæ - Population count 06.png

Case 3. Display the 1st thirty odious numbers

File:Fōrmulæ - Population count 07.png

File:Fōrmulæ - Population count 08.png

FreeBASIC

#define NTERMS 30

function popcount( n as ulongint ) as uinteger
    if n = 0 then return 0
    if n = 1 then return 1
    if n mod 2 = 0 then return popcount(n/2)
    return 1 + popcount( (n - 1)/2 )
end function

dim as ulongint i=0, tp(0 to NTERMS-1), evil(0 to NTERMS-1),_
                     odious(0 to NTERMS-1), k, ne=0, no=0

while ne < NTERMS or no < NTERMS
    if i<NTERMS then tp(i) = popcount(3^i)
    k = popcount(i)
    if k mod 2 = 0 and ne < NTERMS then 
        evil(ne) = i
        ne += 1
    endif
    if k mod 2 = 1 and no < NTERMS then
        odious(no) = i
        no += 1
    end if
    i += 1
wend

dim as string s_tp = "", s_evil = "", s_odious = ""

for i = 0 to NTERMS-1
    s_tp += str(tp(i))+" "
    s_evil += str(evil(i))+" "
    s_odious += str(odious(i))+" "
next i

print s_tp
print s_evil
print s_odious
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59


FutureBasic

_limit = 30

local fn  Population( x as long ) as long
  long q, r, y = 0
  
  while ( x > 0 )
    q = int( x / 2 )
    r = x - q * 2
    if r == 1 then y++
    x = q
  wend
end fn = y

void local fn EvilOdious
  long   i = 0, k, ee = 0, eo = 0
  long   type(_limit - 1), evil(_limit - 1), odious(_limit - 1)
  Str255 typeStr, evilStr, odiousStr
  
  while ( ( ee < _limit ) or ( eo < _limit ) )
    if i < _limit then type(i) = fn Population(3^i)
    k = fn Population(i)
    if k mod 2 == 0 and ee < _limit then evil(ee)   = i : ee++
    if k mod 2 == 1 and eo < _limit then odious(eo) = i : eo++
    i++
  wend
  
  typeStr = "" : evilStr = "" : odiousStr = ""
  for i = 0 to _limit - 1
    typeStr   = typeStr   + str$( type(i) )   +  " "
    evilStr   = evilStr   + str$( evil(i) )   +  " "
    odiousStr = odiousStr + str$( odious(i) ) +  " "
  next
  print typeStr : print evilStr : print odiousStr
end fn

fn EvilOdious

HandleEvent
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59


Gambas

Click this link to run this code

Public Sub Main()
Dim sEvil, sOdious As String                         'To store the output for printing Evil and Odious 
Dim iCount, iEvil, iOdious As Integer                'Counters

Print "First 30 numbers ^3\t";                       'Print title

For iCount = 0 To 29                                 'Count 30 times
  Print Len(Replace(Bin(3 ^ iCount), "0", ""));;     'Get the Bin of the number, take out the '0's and the remaining
Next                                                 'length is the Population count e.g. 3^2=9, Bin=1001, remove '0's='11', length=2

iCount = 0                                           'Reset iCount

Repeat                                               'Repeat/Until loop
  If Even(Len(Replace(Bin(iCount), "0", ""))) Then   'If (as above) the result is Even then
    sEvil &= Str(icount) & " "                       'Add it to sEvil
    Inc iEvil                                        'Increase iEvil
  End If
  If Odd(Len(Replace(Bin(iCount), "0", ""))) Then    'If (as above) the result is Odd then
    sOdious &= Str(icount) & " "                     'Add it to sOdious
    Inc iOdious                                      'Increase iOdious
  End If
  Inc iCount                                         'Increase iCount
Until iEvil = 30 And iOdious = 30                    'Until both iEvil and iOdious = 30 then exit the loop

Print "\n1st 30 Evil numbers =\t" & sEvil            'Print Evil
Print "1st 30 Odious numbers =\t" & sOdious          'Print Odious

End

Output:

First 30 numbers ^3     1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
1st 30 Evil numbers =   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
1st 30 Odious numbers = 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Go

Standard Library

As of Go 1.9, this function is in the standard Library.

package main

import (
    "fmt"
    "math/bits"
)

func main() {
    fmt.Println("Pop counts, powers of 3:")
    n := uint64(1) // 3^0
    for i := 0; i < 30; i++ {
        fmt.Printf("%d ", bits.OnesCount64(n))
        n *= 3
    }
    fmt.Println()
    fmt.Println("Evil numbers:")
    var od [30]uint64
    var ne, no int
    for n = 0; ne+no < 60; n++ {
        if bits.OnesCount64(n)&1 == 0 {
            if ne < 30 {
                fmt.Printf("%d ", n)
                ne++
            }
        } else {
            if no < 30 {
                od[no] = n
                no++
            }
        }
    }
    fmt.Println()
    fmt.Println("Odious numbers:")
    for _, n := range od {
        fmt.Printf("%d ", n)
    }
    fmt.Println()
}
Output:
Pop counts, powers of 3:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
Evil numbers:
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
Odious numbers:
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Implementation

Method of WP example popcount_3:

func pop64(w uint64) int {
    const (
        ff    = 1<<64 - 1
        mask1 = ff / 3
        mask3 = ff / 5
        maskf = ff / 17
        maskp = maskf >> 3 & maskf
    )
    w -= w >> 1 & mask1
    w = w&mask3 + w>>2&mask3
    w = (w + w>>4) & maskf
    return int(w * maskp >> 56)
}

Method of WP example popcount_4:

func pop64(w uint64) (c int) {
    for w != 0 {
        w &= w - 1
        c++
    }
    return
}

Haskell

Works with: GHC version 7.4+
import Data.Bits (popCount)

printPops :: (Show a, Integral a) => String -> [a] -> IO ()
printPops title counts = putStrLn $ title ++ show (take 30 counts)

main :: IO ()
main = do
  printPops "popcount " $ map popCount $ iterate (*3) (1 :: Integer)
  printPops "evil     " $ filter (even . popCount) ([0..] :: [Integer])
  printPops "odious   " $ filter ( odd . popCount) ([0..] :: [Integer])
Output:
popcount [1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]
evil     [0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]
odious   [1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]


Or, if we want to write our own popCount, perhaps something like:

import Data.Bifoldable (biList)
import Data.List (partition, unfoldr)
import Data.Tuple (swap)

--------------------- POPULATION COUNT -------------------
popCount :: Int -> Int
popCount = sum . unfoldr go
  where
    go x
      | 0 < x = (Just . swap) (quotRem x 2)
      | otherwise = Nothing

--------------------------- TEST -------------------------
main :: IO ()
main =
  mapM_ putStrLn $
    zipWith
      (\k xs -> concat [k, ":\n", show xs, "\n"])
      ["Population count of powers of 3", "evil", "odious"]
      ( (popCount . (3 ^) <$> [0 .. 29]) :
        biList (partition (even . popCount) [0 .. 59])
      )
Output:
Population count of powers of 3:
[1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]

evil:
[0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]

odious:
[1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]

Idris

module Main
import Data.Vect

isOdd : (x : Int) -> Bool
isOdd x = case mod x 2 of
            0 => False
            1 => True

popcnt : Int -> Int
popcnt 0 = 0
popcnt x = case isOdd x of
  False => popcnt (shiftR x 1)
  True => 1 + popcnt (shiftR x 1)
  
isOdious : Int -> Bool
isOdious k = isOdd (popcnt k)

isEvil : Int -> Bool
isEvil k = not (isOdious k)

filterUnfoldN : (n : Nat) -> 
                (pred : Int -> Bool) -> (f : Int -> a) -> 
                (next : Int -> Int) -> (seed : Int) ->
                Vect n a
filterUnfoldN Z pred f next seed = []
filterUnfoldN (S k) pred f next seed = 
  if pred seed
  then (f seed) :: filterUnfoldN k pred f next (next seed)
  else filterUnfoldN (S k) pred f next (next seed)
  
printCompact : (Show a) => Vect n a -> IO ()
printCompact v = putStrLn (unwords (map show (toList v)))

main : IO ()
main = do putStr "popcnt(3**i): "
          printCompact (filterUnfoldN 30 (\_ => True) popcnt (3 *) 1)
          putStr "Evil:         "
          printCompact (filterUnfoldN 30 isEvil id (1 +) 0)
          putStr "Odious:       "
          printCompact (filterUnfoldN 30 isOdious id (1 +) 0)
Output:
popcnt(3**i): 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:         0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious:       1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

J

Implementation:

countPopln=: +/"1@#:
isOdd=: 1 = 2&|
isEven=: 0 = 2&|


Task:

   countPopln 3^i.30x
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
   30{.(#~ isOdd@countPopln) i. 100 NB. odd population count (aka "ODious numbers")
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59
   30{.(#~ isEven@countPopln) i. 100 NB. even population count (aka "EVil numbers")
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58

Java

import java.math.BigInteger;

public class PopCount {
    public static void main(String[] args) {
	{ // with int
	    System.out.print("32-bit integer: ");
	    int n = 1;
	    for (int i = 0; i < 20; i++) {
		System.out.printf("%d ", Integer.bitCount(n));
		n *= 3;
	    }
	    System.out.println();
	}
	{ // with long
	    System.out.print("64-bit integer: ");
	    long n = 1;
	    for (int i = 0; i < 30; i++) {
		System.out.printf("%d ", Long.bitCount(n));
		n *= 3;
	    }
	    System.out.println();
	}
	{ // with BigInteger
	    System.out.print("big integer   : ");
	    BigInteger n = BigInteger.ONE;
	    BigInteger three = BigInteger.valueOf(3);
	    for (int i = 0; i < 30; i++) {
		System.out.printf("%d ", n.bitCount());
		n = n.multiply(three);
	    }
	    System.out.println();
	}

	int[] od = new int[30];
	int ne = 0, no = 0;
	System.out.print("evil   : ");
	for (int n = 0; ne+no < 60; n++) {
	    if ((Integer.bitCount(n) & 1) == 0) {
		if (ne < 30) {
		    System.out.printf("%d ", n);
		    ne++;
		}
	    } else {
		if (no < 30) {
		    od[no++] = n;
		}
	    }
	}
	System.out.println();
	System.out.print("odious : ");
	for (int n : od) {
	    System.out.printf("%d ", n);
	}
	System.out.println();
    }
}
Output:
32-bit integer: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 
64-bit integer: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
big integer   : 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil   : 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious : 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 

JavaScript

ES6

(() => {
    'use strict';

    // populationCount :: Int -> Int
    const populationCount = n =>
        // The number of non-zero bits in the binary
        // representation of the integer n.
        sum(unfoldr(
            x => 0 < x ? (
                Just(Tuple(x % 2)(Math.floor(x / 2)))
            ) : Nothing()
        )(n));

    // ----------------------- TEST ------------------------
    // main :: IO ()
    const main = () => {
        const [evens, odds] = Array.from(
            partition(compose(even, populationCount))(
                enumFromTo(0)(59)
            )
        );
        return [
            'Population counts of the first 30 powers of three:',
            `    [${enumFromTo(0)(29).map(
                    compose(populationCount, raise(3))
                 ).join(',')}]`,
            "\nFirst thirty 'evil' numbers:",
            `    [${[evens.join(',')]}]`,
            "\nFirst thirty 'odious' numbers:",
            `    [${odds.join(',')}]`
        ].join('\n');
    };


    // ----------------- GENERIC FUNCTIONS -----------------

    // Just :: a -> Maybe a
    const Just = x => ({
        type: 'Maybe',
        Nothing: false,
        Just: x
    });


    // Nothing :: Maybe a
    const Nothing = () => ({
        type: 'Maybe',
        Nothing: true,
    });


    // Tuple (,) :: a -> b -> (a, b)
    const Tuple = a =>
        b => ({
            type: 'Tuple',
            '0': a,
            '1': b,
            length: 2
        });


    // compose (<<<) :: (b -> c) -> (a -> b) -> a -> c
    const compose = (...fs) =>
        // A function defined by the right-to-left
        // composition of all the functions in fs.
        fs.reduce(
            (f, g) => x => f(g(x)),
            x => x
        );


    // enumFromTo :: Int -> Int -> [Int]
    const enumFromTo = m =>
        n => !isNaN(m) ? (
            Array.from({
                length: 1 + n - m
            }, (_, i) => m + i)
        ) : enumFromTo_(m)(n);


    // even :: Int -> Bool
    const even = n =>
        // True if n is an even number.
        0 === n % 2;


    // partition :: (a -> Bool) -> [a] -> ([a], [a])
    const partition = p =>
        // A tuple of two lists - those elements in
        // xs which match p, and those which don't.
        xs => ([...xs]).reduce(
            (a, x) =>
            p(x) ? (
                Tuple(a[0].concat(x))(a[1])
            ) : Tuple(a[0])(a[1].concat(x)),
            Tuple([])([])
        );


    // raise :: Num -> Int -> Num
    const raise = x =>
        // X to the power of n.
        n => Math.pow(x, n);


    // sum :: [Num] -> Num
    const sum = xs =>
        // The numeric sum of all values in xs.
        xs.reduce((a, x) => a + x, 0);


    // unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
    const unfoldr = f =>
        v => {
            const xs = [];
            let xr = [v, v];
            while (true) {
                const mb = f(xr[1]);
                if (mb.Nothing) {
                    return xs
                } else {
                    xr = mb.Just;
                    xs.push(xr[0])
                }
            }
        };

    // ---
    return main();
})();
Output:
Population counts of the first 30 powers of three:
    [1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]

First thirty 'evil' numbers:
    [0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]

First thirty 'odious' numbers:
    [1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]

jq

Works with: jq version 1.4
def popcount: 
  def bin: recurse( if . == 0 then empty else ./2 | floor end ) % 2;
  [bin] | add;

def firstN(count; condition):
  if count > 0 then
    if condition then ., (1+.| firstN(count-1; condition))
    else (1+.) | firstN(count; condition) 
    end
  else empty
  end;

def task:
  def pow(n): . as $m | reduce range(0;n) as $i (1; . * $m);

  "The pop count of the first thirty powers of 3:",
   [range(0;30) as $n | 3 | pow($n) | popcount],

  "The first thirty evil numbers:",
   [0 | firstN(30; (popcount % 2) == 0)],

  "The first thirty odious numbers:",
   [0 | firstN(30; (popcount % 2) == 1)]
;

task
Output:
$ jq -n -r -c -f Population_count.jq
The pop count of the first thirty powers of 3:
[1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]
The first thirty evil numbers:
[0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]
The first thirty odious numbers:
[1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]

Julia

println("First 3 ^ i, up to 29 pop. counts: ", join((count_ones(3 ^ n) for n in 0:29), ", "))
println("Evil numbers: ", join(filter(x -> iseven(count_ones(x)), 0:59), ", "))
println("Odious numbers: ", join(filter(x -> isodd(count_ones(x)), 0:59), ", "))
Output:
First 3 ^ i, up to 29 pop. counts: 1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25
Evil numbers: 0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58
Odious numbers: 1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59

Kotlin

// version 1.0.6

fun popCount(n: Long) = when {
    n < 0L -> throw IllegalArgumentException("n must be non-negative")
    else   -> java.lang.Long.bitCount(n)
}

fun main(args: Array<String>) {
    println("The population count of the first 30 powers of 3 are:")
    var pow3 = 1L
    for (i in 1..30) {
        print("${popCount(pow3)} ")
        pow3 *= 3L
    }
    println("\n")
    println("The first thirty evil numbers are:")
    var count = 0
    var i = 0
    while (true) {
        val pc = popCount(i.toLong())
        if (pc % 2 == 0) {
           print("$i ")
           if (++count == 30) break
        }
        i++
    }
    println("\n")
    println("The first thirty odious numbers are:")
    count = 0
    i = 1
    while (true) {
        val pc = popCount(i.toLong())
        if (pc % 2 == 1) {
            print("$i ")
            if (++count == 30) break
        }
        i++
    }
    println() 
}
Output:
The population count of the first 30 powers of 3 are:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25

The first thirty evil numbers are:
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58

The first thirty odious numbers are:
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Lua

-- Take decimal number, return binary string
function dec2bin (n)
    local bin, bit = ""
    while n > 0 do
        bit = n % 2
        n = math.floor(n / 2)
        bin = bit .. bin
    end
    return bin
end
 
-- Take decimal number, return population count as number
function popCount (n)
    local bin, count = dec2bin(n), 0
    for pos = 1, bin:len() do
        if bin:sub(pos, pos) == "1" then count = count + 1 end
    end
    return count
end

-- Implement task requirements
function firstThirty (mode)
    local numStr, count, n, remainder = "", 0, 0
    if mode == "Evil" then remainder = 0 else remainder = 1 end
    while count < 30 do
        if mode == "3^x" then
            numStr = numStr .. popCount(3 ^ count) .. " "
            count = count + 1
        else
            if popCount(n) % 2 == remainder then
                numStr = numStr .. n .. " "
                count = count + 1
            end
            n = n + 1
        end
    end
    print(mode .. ":" , numStr)
end

-- Main procedure
firstThirty("3^x")
firstThirty("Evil")
firstThirty("Odious")
Output:
3^x:    1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

M2000 Interpreter

Using just Count() and loops
Module Population_count{
	Function Count(x as long long) {
		integer Count
		long long m=x
		m|div 0x1_0000_0000&&
		x|mod 0x1_0000_0000&&
		While x<>0&
			x=Binary.And(X, X-1&&)
			Count++
		End While
		x=m
		While x<>0&
			x=Binary.And(X, X-1&&)
			Count++
		End While	
		=Count
	}
	long long i, b=3
	stack new {
		for i=0 to 29
			Data  count(b^i)
		next
		print "3^x  population:", array([])#str$()
		i=0: b=0
		while i<30
			if Count(b) mod 2=0 then data b:i++
			b++
		end while
		print "evil    numbers:", array([])#str$()
		i=0: b=0
		while i<30
			if Count(b) mod 2=1 then data b:i++
			b++
		end while
		print "odious  numbers:", array([])#str$()
	}
}
Population_count
Using Generators
Module Population_count{
	Count=lambda (x as long long)->{
		integer Count
		long long m=x
		m|div 0x1_0000_0000&&
		x|mod 0x1_0000_0000&&
		While x<>0&
			x=Binary.And(X, X-1&&)
			Count++
		End While
		x=m
		While x<>0&
			x=Binary.And(X, X-1&&)
			Count++
		End While	
		=Count
	}
	series3pow=lambda Count, i=0&& -> {
		=count(3&&^i):i++
	}
	seriesEvil=lambda Count, i=0&&-> {
		while Count(i) mod 2=1{i++}
		=i:i++
	}
	seriesOdious=lambda Count, i=0&&-> {
		while Count(i) mod 2=0{i++}
		=i:i++
	}
	Dim a(30)<<series3pow()
	print "3^x  population:", a()#str$()
	Dim a(30)<<seriesEvil()
	print "evil    numbers:", a()#str$()
	Dim a(30)<<seriesOdious()
	print "odious  numbers:", a()#str$()
}
Population_count
Output:
3^x  population:1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil    numbers:0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious  numbers:1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

MAD

            NORMAL MODE IS INTEGER
            
            INTERNAL FUNCTION LOWBIT.(K) = K-K/2*2
            
          R FUNCTION TO CALC POP COUNT  
            INTERNAL FUNCTION(N)
            ENTRY TO POPCNT.
            RSLT = 0
            PCTNUM = N
LOOP        PCTNXT = PCTNUM/2
            RSLT = RSLT + PCTNUM-PCTNXT*2
            PCTNUM = PCTNXT
            WHENEVER PCTNUM.NE.0, TRANSFER TO LOOP
            FUNCTION RETURN RSLT
            END OF FUNCTION
            
          R POP COUNT OF 3^0 TO 3^29
            POW3 = 1
            THROUGH P3CNT, FOR I=0, 1, I.GE.30
            PRINT FORMAT P3FMT, I, POPCNT.(POW3)
P3CNT       POW3 = POW3 * 3
            VECTOR VALUES P3FMT = $15HPOP COUNT OF 3^,I2,2H: ,I3*$
          
          R EVIL AND ODIOUS NUMBERS   
            PRINT COMMENT$ $
            PRINT COMMENT$ FIRST 30 EVIL NUMBERS ARE$
            SEEN = 1
            THROUGH EVIL, FOR I=0, 1, SEEN.GE.30
            WHENEVER LOWBIT.(POPCNT.(I)).E.0
                PRINT FORMAT NUMFMT,I
                SEEN = SEEN + 1
EVIL        END OF CONDITIONAL

            PRINT COMMENT$ $
            PRINT COMMENT$ FIRST 30 ODIOUS NUMBERS ARE$
            SEEN = 1
            THROUGH ODIOUS, FOR I=0, 1, SEEN.GE.30
            WHENEVER LOWBIT.(POPCNT.(I)).E.1
                PRINT FORMAT NUMFMT,I
                SEEN = SEEN + 1
ODIOUS      END OF CONDITIONAL
           
            VECTOR VALUES NUMFMT = $I2*$
            END OF PROGRAM
Output:
POP COUNT OF 3^ 0:   1
POP COUNT OF 3^ 1:   2
POP COUNT OF 3^ 2:   2
POP COUNT OF 3^ 3:   4
POP COUNT OF 3^ 4:   3
POP COUNT OF 3^ 5:   6
POP COUNT OF 3^ 6:   6
POP COUNT OF 3^ 7:   5
POP COUNT OF 3^ 8:   6
POP COUNT OF 3^ 9:   8
POP COUNT OF 3^10:   9
POP COUNT OF 3^11:  13
POP COUNT OF 3^12:  10
POP COUNT OF 3^13:  11
POP COUNT OF 3^14:  14
POP COUNT OF 3^15:  15
POP COUNT OF 3^16:  11
POP COUNT OF 3^17:  14
POP COUNT OF 3^18:  14
POP COUNT OF 3^19:  17
POP COUNT OF 3^20:  17
POP COUNT OF 3^21:  20
POP COUNT OF 3^22:  19
POP COUNT OF 3^23:  22
POP COUNT OF 3^24:  16
POP COUNT OF 3^25:  18
POP COUNT OF 3^26:  24
POP COUNT OF 3^27:  30
POP COUNT OF 3^28:  25
POP COUNT OF 3^29:  25

FIRST 30 EVIL NUMBERS ARE
 0
 3
 5
 6
 9
10
12
15
17
18
20
23
24
27
29
30
33
34
36
39
40
43
45
46
48
51
53
54
57

FIRST 30 ODIOUS NUMBERS ARE
 1
 2
 4
 7
 8
11
13
14
16
19
21
22
25
26
28
31
32
35
37
38
41
42
44
47
49
50
52
55
56


Mathematica/Wolfram Language

popcount[n_Integer] := IntegerDigits[n, 2] // Total
Print["population count of powers of 3"]
popcount[#] & /@ (3^Range[0, 30])
(*******)
evilQ[n_Integer] := popcount[n] // EvenQ
evilcount = 0;
evillist = {};
i = 0;
While[evilcount < 30,
 If[evilQ[i], AppendTo[evillist, i]; evilcount++];
 i++
 ]
Print["first thirty evil numbers"]
evillist
(*******)
odiousQ[n_Integer] := popcount[n] // OddQ
odiouscount = 0;
odiouslist = {};
i = 0;
While[odiouscount < 30,
 If[odiousQ[i], AppendTo[odiouslist, i]; odiouscount++];
 i++
 ]
Print["first thirty odious numbers"]
odiouslist
Output:
population count of powers of 3
{1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25, 25}
first thirty evil numbers
{0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58}
first thirty odious numbers
{1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59}

min

Works with: min version 0.19.3
(2 over over mod 'div dip) :divmod2

(
  :n () =list
  (n 0 >) (n divmod2 list append #list @n) while
  list (1 ==) filter size
) :pop-count

(:n 0 () (over swap append 'succ dip) n times) :iota

"3^n:    " print! 30 iota (3 swap pow int pop-count) map puts!
60 iota (pop-count odd?) partition
"Evil:   " print! puts! "Odious: " print! puts!
Output:
3^n:    (1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25)
Evil:   (0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58)
Odious: (1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59)

Miranda

main :: [sys_message]
main = [Stdout (lay (map (show . take 30) [powers_of_3, evil, odious]))]

powers_of_3 :: [num]
powers_of_3 = map (popcount . (3^)) [0..]

evil :: [num]
evil = filter f [0..] where f n = popcount n mod 2 = 0

odious :: [num]
odious = filter f [0..] where f n = popcount n mod 2 = 1

popcount :: num -> num
popcount 0 = 0
popcount n = n mod 2 + popcount (n div 2)
Output:
[1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]
[0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]
[1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]

Nim

import bitops
import strformat

var n = 1
write(stdout, "3^x   :") 
for i in 0..<30:
  write(stdout, fmt"{popcount(n):2} ")
  n *= 3

var od: array[30, int]
var ne, no = 0
n = 0
write(stdout, "\nevil  :")
while ne + no < 60:
  if (popcount(n) and 1) == 0:
    if ne < 30:
      write(stdout, fmt"{n:2} ")
      inc ne
  else:
    if no < 30:
      od[no] = n
      inc no
  inc n

write(stdout, "\nodious:")
for i in 0..<30:
  write(stdout, fmt"{od[i]:2} ")
write(stdout, '\n')
Output:
3^x   : 1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil  : 0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious: 1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 

Another version, in functional style, with most computations done at compile time:

import bitops, math, sequtils, strutils

const
  N = 30
  popcounts = toSeq(0..<N).mapIt(popcount(3^it))
  mapping = toSeq(0..<(2 * N)).mapIt((it, it.popcount))
  evil = mapping.filterIt((it[1] and 1) == 0).mapIt(it[0])
  odious = mapping.filterIt((it[1] and 1) != 0).mapIt(it[0])

echo "3^n:   ", popcounts.mapIt(($it).align(2)).join(" ")
echo "evil:  ", evil.mapIt(($it).align(2)).join(" ")
echo "odious:", odious.mapIt(($it).align(2)).join(" ")
Output:
3^n:    1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil:   0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious: 1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

OCaml

let popcount n =
  let rec aux acc = function
    | 0 -> acc
    | x -> aux (succ acc) (x land pred x)
  in
  aux 0 n

let is_parity p x =
  p = 1 land popcount x

(* test code *)

let powers3_seq () =
  Seq.unfold (fun x -> Some (popcount x, x * 3)) 1

let parity_seq p =
  Seq.(filter (is_parity p) (ints 0))

let print_seq_30 s =
  Seq.(s |> take 30 |> map string_of_int)
  |> List.of_seq |> String.concat " " |> print_endline

let () = print_seq_30 (powers3_seq ())
let () = print_seq_30 (parity_seq 0)
let () = print_seq_30 (parity_seq 1)
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Oforth

: popcount(n)
   0 while ( n ) [ n isOdd + n bitRight(1) ->n ] ;

: test
| i count |
   30 seq map(#[ 3 swap 1- pow ]) map(#popcount) println
   
   0 ->count
   0 while( count 30 <> ) [ dup popcount isEven ifTrue: [ dup . count 1+ ->count ] 1+ ] drop printcr

   0 ->count
   0 while( count 30 <> ) [ dup popcount isOdd ifTrue: [ dup . count 1+ ->count ] 1+ ] drop ;
Output:
>test
[1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 ok

Ol

(define (popcount n)
   (let loop ((n n) (c 0))
      (if (= n 0)
         c
         (loop (>> n 1)
               (if (eq? (band n 1) 0) c (+ c 1))))))
(print (popcount 31415926535897932384626433832795028841971693993751058209749445923078164062862089986280348253))


(define thirty 30)

(display "popcount:")
(for-each (lambda (i)
      (display " ")
      (display (popcount (expt 3 i))))
   (iota thirty 0))
(print)

(define (evenodd name test)
   (display name) (display ":")
   (for-each (lambda (i)
         (display " ")
         (display i))
      (reverse
         (let loop ((n 0) (i 0) (out '()))
            (if (= i thirty)
               out
               (if (test (popcount n))
                  (loop (+ n 1) (+ i 1) (cons n out))
                  (loop (+ n 1) i out))))))
   (print))

(evenodd "evil" even?)
(evenodd "odius" odd?)
Output:
159
popcount: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odius: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

PARI/GP

vector(30,n,hammingweight(3^(n-1)))
od=select(n->hammingweight(n)%2,[0..100]); ev=setminus([0..100],od);
ev[1..30]
od[1..30]
Output:
%1 = [1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
%2 = [0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]
%3 = [1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]

Pascal

Works with: freepascal

Like Ada a unit is used.

unit popcount;
{$IFDEF FPC}
   {$MODE DELPHI}
   {$OPTIMIZATION ON,ASMCSE,CSE,PEEPHOLE}
   {$Smartlink OFF}
{$ENDIF}

interface
  function popcnt(n:Uint64):integer;overload;
  function popcnt(n:Uint32):integer;overload;
  function popcnt(n:Uint16):integer;overload;
  function popcnt(n:Uint8):integer;overload;

implementation
const
//K1  = $0101010101010101;
  K33  = $3333333333333333;
  K55  = $5555555555555555;
  KF1 = $0F0F0F0F0F0F0F0F;
  KF2 = $00FF00FF00FF00FF;
  KF4 = $0000FFFF0000FFFF;
  KF8 = $00000000FFFFFFFF;
{
function popcnt64(n:Uint64):integer;
begin
  n := n- (n shr 1) AND K55;
  n := (n AND K33)+ ((n shr 2) AND K33);
  n := (n + (n shr 4)) AND KF1;
  n := (n*k1) SHR 56;
  result := n;
end;
}
function popcnt(n:Uint64):integer;overload;
// on Intel Haswell 2x faster for fpc 32-Bit
begin
  n := (n AND K55)+((n shr  1)  AND K55);
  n := (n AND K33)+((n shr  2)  AND K33);
  n := (n AND KF1)+((n shr  4)  AND KF1);
  n := (n AND KF2)+((n shr  8)  AND KF2);
  n := (n AND KF4)+((n shr 16)  AND KF4);
  n := (n AND KF8)+ (n shr 32);
  result := n;
end;

function popcnt(n:Uint32):integer;overload;
var
  c,b : NativeUint;
begin
  b := n;
  c := (b shr 1) AND NativeUint(K55);   b := (b AND NativeUint(K55))+C;
  c := ((b shr 2)  AND NativeUint(K33));b := (b AND NativeUint(K33))+C;
  c:= ((b shr 4)  AND NativeUint(KF1)); b := (b AND NativeUint(KF1))+c;
  c := ((b shr 8)  AND NativeUint(KF2));b := (b AND NativeUint(KF2))+c;
  c := b shr 16; b := (b AND NativeUint(KF4))+ C;
  result := b;
end;

function popcnt(n:Uint16):integer;overload;
var
  c,b : NativeUint;
begin
  b := n;
  c := (b shr 1) AND NativeUint(K55);  b := (b AND NativeUint(K55))+C;
  c :=((b shr 2)  AND NativeUint(K33)); b := (b AND NativeUint(K33))+C;
  c:= ((b shr 4)  AND NativeUint(KF1)); b := (b AND NativeUint(KF1))+c;
  c :=  b shr 8; b := (b AND NativeUint(KF2))+c;
  result := b;
end;

function popcnt(n:Uint8):integer;overload;
var
  c,b : NativeUint;
begin
  b := n;
  c := (b shr 1) AND NativeUint(K55);  b := (b AND NativeUint(K55))+C;
  c :=((b shr 2)  AND NativeUint(K33));b := (b AND NativeUint(K33))+C;
  c:=   b shr 4;
  result := (b AND NativeUint(KF1))+c;
end;

Begin
End.

The program

program pcntTest;
uses
  sysutils,popCount;

function Odious(n:Uint32):boolean;inline;
Begin
  Odious := boolean(PopCnt(n) AND 1)
end;

function EvilNumber(n:Uint32):boolean;inline;
begin
  EvilNumber := boolean(NOT(PopCnt(n)) AND 1);
end;

var
  s : String;
  i : Uint64;
  k : LongWord;
Begin
  s :='PopCnt 3^i     :';
  i:= 1;
  For k := 1 to 30 do
  Begin
    s := s+InttoStr(PopCnt(i)) +' ';
    i := 3*i;
  end;
  writeln(s);writeln;

  s:='Evil numbers   :';i := 0;k := 0;
  repeat
    IF EvilNumber(i) then
    Begin
      inc(k);s := s+InttoStr(i) +' ';
    end;
    inc(i);
  until k = 30;
  writeln(s);writeln;s:='';


  s:='Odious numbers :';i := 0;k := 0;
  repeat
    IF Odious(i) then
    Begin
      inc(k);s := s+InttoStr(i) +' ';
    end;
    inc(i);
  until k = 30;
  writeln(s);
end.
Output
PopCnt 3^i     :1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil numbers   :0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious numbers :1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Some processors define the card function, which can be used in conjunction with sets:

var
	i: integer;
	f: set of 0..(bitSizeOf(i)-1) absolute i; // same address as i, but different interpretation
begin
	writeLn(card(f));
end;

Perl

Translation of: Raku

We'll emulate infinite lists with closures.

use strict;
use warnings;
use feature 'say';

sub evil {
    my $i = 0;
    sub { $i++ while population_count($i) % 2; $i++ }
}

sub odious {
    my $i = 0;
    sub { $i++ until population_count($i) % 2; $i++ }
}

sub population_count { 
    my $n = shift;
    my $c;
    for ($c = 0; $n; $n >>= 1) { $c += $n & 1 } 
    $c
}

say join ' ', map { population_count 3**$_ } 0 .. 30 - 1;

my (@evil, @odious);
my ($evil, $odious) = (evil, odious);
push( @evil, $evil->() ), push @odious, $odious->() for 1 .. 30;

say "Evil   @evil";
say "Odious @odious";
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

A faster population count can be done with pack/unpack:

say unpack("%b*",pack "J*", 1234567); # J = UV

Various modules can also perform a population count, with the first of these being faster than the pack/unpack builtins. The first three easily support bigints, the last will with some adjustment.

use ntheory qw/hammingweight/;
say hammingweight(1234567);

use Math::GMPz qw/Rmpz_popcount/;
say Rmpz_popcount(Math::GMPz->new(1234567));

use Math::BigInt;
say 0 + (Math::BigInt->new(1234567)->as_bin() =~ tr/1//);

use Bit::Vector;
say Bit::Vector->new_Dec(64,1234567)->Norm;

Phix

As of 1.0.2 there is a builtin count_bits(), and also mpz_popcount(), both of which match the results from pop_count() below.

with javascript_semantics
function pop_count(atom n)
    if n<0 then ?9/0 end if
    integer res = 0
    while n!=0 do
        res += and_bits(n,1)
        n = floor(n/2)
    end while
    return res
end function
 
printf(1,"3^x pop_counts:%v\n",{apply(apply(true,power,{3,tagset(29,0)}),pop_count)})
 
procedure eo(integer b0, string name)
    sequence s = repeat(0,30)
    integer k=0, l=1
    while l<=30 do
        if and_bits(pop_count(k),1)=b0 then
            s[l] = k
            l += 1
        end if
        k += 1
    end while
    printf(1,"%s numbers:%v\n",{name,s})
end procedure
eo(0,"  evil")
eo(1,"odious")
Output:
3^x pop_counts:{1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25}
  evil numbers:{0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58}
odious numbers:{1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59}

PHP

function convertToBinary($integer) {
    $binary = "";

    do {
        $quotient = (int) ($integer / 2);
        $binary .= $integer % 2;
        $integer = $quotient;    
    } while ($quotient > 0);

    return $binary;
}

function getPopCount($integer) {
    $binary = convertToBinary($integer);
    $offset = 0;
    $popCount = 0;

    do {
        $pos = strpos($binary, "1", $offset);
        if($pos !== FALSE) $popCount++;
        $offset = $pos + 1;
    } while ($pos !== FALSE);

    return $popCount;
}

function print3PowPopCounts() {
    for ($p = 0; $p < 30; $p++) {
        echo " " . getPopCount(3 ** $p);
    }
}

function printFirst30Evil() {
    $counter = 0;
    $pops = 0;

    while ($pops < 30) {
        $popCount = getPopCount($counter);
        if ($popCount % 2 == 0)  {
            echo " " . $counter;
            $pops++;
        }
        $counter++;
    }
}

function printFirst30Odious() {
    $counter = 1;
    $pops = 0;

    while ($pops < 30) {
        $popCount = getPopCount($counter);
        if ($popCount % 2 != 0)  {
            echo " " . $counter;
            $pops++;
        }
        $counter++;
    }
}

echo "3 ^ x pop counts:";
print3PowPopCounts();

echo "\nfirst 30 evil numbers:";
printFirst30Evil();

echo "\nfirst 30 odious numbers:";
printFirst30Odious();
Output:
03 ^ x pop counts: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
first 30 evil numbers: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
first 30 odious numbers: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Picat

go =>
  println(powers_of_three=[pop_count(3**I) : I in 0..29]),
  println('evil_numbers   '=take_n($evil_number, 30,0)),
  println('odious_numbers '=take_n($odious_number, 30,0)),
  nl.

% Get the first N numbers that satisfies function F, starting with S
take_n(F,N,S) = L =>
  I = S,
  C = 0,
  L = [],
  while(C < N)
    if call(F,I) then
       L := L ++ [I],
       C := C + 1
    end,
    I := I + 1
  end.

evil_number(N) => pop_count(N) mod 2 == 0.
odious_number(N) => pop_count(N) mod 2 == 1.

pop_count(N) = sum([1: I in N.to_binary_string(), I = '1']).
Output:
powers_of_three = [1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]
evil_numbers    = [0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]
odious_numbers  = [1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]


PicoLisp

(de popz (N)
   (cnt
      '((N) (= "1" N))
      (chop (bin N)) ) )

(println
   'pops:
   (mapcar
      '((N) (popz (** 3 N)))
      (range 0 29) ) )
(setq N -1)
(println
   'evil:
   (make
      (for (C 0 (> 30 C))
         (unless (bit? 1 (popz (inc 'N)))
            (link N)
            (inc 'C) ) ) ) )
(setq N -1)
(println
   'odio:
   (make
      (for (C 0 (> 30 C))
         (when (bit? 1 (popz (inc 'N)))
            (link N)
            (inc 'C) ) ) ) )
Output:
pops: (1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25)
evil: (0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58)
odio: (1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59)

PowerShell

function pop-count($n) {
    (([Convert]::ToString($n, 2)).toCharArray() | where {$_ -eq '1'}).count 
}
"pop_count 3^n: $(1..29 | foreach -Begin {$n = 1; (pop-count $n)} -Process {$n = 3*$n; (pop-count $n)} )"
"even pop_count: $($m = $n = 0; while($m -lt 30) {if(0 -eq ((pop-count $n)%2)) {$m += 1; $n}; $n += 1} )"
"odd pop_count: $($m = $n = 0; while($m -lt 30) {if(1 -eq ((pop-count $n)%2)) {$m += 1; $n}; $n += 1} )"

Output:

pop_count 3^n: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
even pop_count: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odd pop_count: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

PureBasic

Procedure.i PopCount(n.i) : ProcedureReturn CountString(Bin(Pow(3,n)),"1") : EndProcedure
Procedure   PutR(v.i)     : Print(RSet(Str(v),3))                          : EndProcedure

If OpenConsole()
  NewList ne() : NewList no()  
  i=0
  While ListSize(ne())+ListSize(no())<60
    If CountString(Bin(i),"1")%2=0 : AddElement(ne()) : ne()=i 
    Else                           : AddElement(no()) : no()=i : EndIf
    i+1
  Wend
  Print("3^i [i=0..29]") : For i=0 To 29 : PutR(PopCount(i)) : Next : PrintN("")
  Print("Evil numbers ") : ForEach ne()  : PutR(ne())        : Next : PrintN("")
  Print("Odious numb..") : ForEach no()  : PutR(no())        : Next : Input()
EndIf
Output:
3^i [i=0..29]  1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil numbers   0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious numb..  1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Python

Procedural

>>> def popcount(n): return bin(n).count("1")
... 
>>> [popcount(3**i) for i in range(30)]
[1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
>>> evil, odious, i = [], [], 0
>>> while len(evil) < 30 or len(odious) < 30:
...     p = popcount(i)
...     if p % 2: odious.append(i)
...     else: evil.append(i)
...     i += 1
... 
>>> evil[:30]
[0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]
>>> odious[:30]
[1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]
>>>

Python: Kernighans' algorithm

The algorithm is explained here. Replace popcount with pop_kernighan in the example above to get the same evil and odious results.

def pop_kernighan(n):
    i = 0
    while n:
        i, n = i + 1, n & (n - 1)
    return i

Composition of pure functions

Works with: Python version 3
'''Population count'''

from functools import reduce


# popCount :: Int -> Int
def popCount(n):
    '''The count of non-zero digits in the binary
       representation of the positive integer n.'''
    def go(x):
        return Just(divmod(x, 2)) if 0 < x else Nothing()
    return sum(unfoldl(go)(n))


# -------------------------- TEST --------------------------
def main():
    '''Tests'''

    print('Population count of first 30 powers of 3:')
    print('    ' + showList(
        [popCount(pow(3, x)) for x in enumFromTo(0)(29)]
    ))

    evilNums, odiousNums = partition(
        compose(even, popCount)
    )(enumFromTo(0)(59))

    print("\nFirst thirty 'evil' numbers:")
    print('    ' + showList(evilNums))

    print("\nFirst thirty 'odious' numbers:")
    print('    ' + showList(odiousNums))


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

# Just :: a -> Maybe a
def Just(x):
    '''Constructor for an inhabited Maybe (option type) value.
       Wrapper containing the result of a computation.
    '''
    return {'type': 'Maybe', 'Nothing': False, 'Just': x}


# Nothing :: Maybe a
def Nothing():
    '''Constructor for an empty Maybe (option type) value.
       Empty wrapper returned where a computation is not possible.
    '''
    return {'type': 'Maybe', 'Nothing': True}


# compose :: ((a -> a), ...) -> (a -> a)
def compose(*fs):
    '''Composition, from right to left,
       of a series of functions.
    '''
    def go(f, g):
        def fg(x):
            return f(g(x))
        return fg
    return reduce(go, fs, lambda x: x)


# enumFromTo :: Int -> Int -> [Int]
def enumFromTo(m):
    '''Enumeration of integer values [m..n]'''
    return lambda n: range(m, 1 + n)


# even :: Int -> Bool
def even(x):
    '''True if x is an integer
       multiple of two.
    '''
    return 0 == x % 2


# partition :: (a -> Bool) -> [a] -> ([a], [a])
def partition(p):
    '''The pair of lists of those elements in xs
       which respectively do, and don't
       satisfy the predicate p.
    '''

    def go(a, x):
        ts, fs = a
        return (ts + [x], fs) if p(x) else (ts, fs + [x])
    return lambda xs: reduce(go, xs, ([], []))


# showList :: [a] -> String
def showList(xs):
    '''Stringification of a list.'''
    return '[' + ','.join(repr(x) for x in xs) + ']'


# unfoldl(lambda x: Just(((x - 1), x)) if 0 != x else Nothing())(10)
# -> [1, 2, 3, 4, 5, 6, 7, 8, 9, 10]
# unfoldl :: (b -> Maybe (b, a)) -> b -> [a]
def unfoldl(f):
    '''Dual to reduce or foldl.
       Where these reduce a list to a summary value, unfoldl
       builds a list from a seed value.
       Where f returns Just(a, b), a is appended to the list,
       and the residual b is used as the argument for the next
       application of f.
       When f returns Nothing, the completed list is returned.
    '''
    def go(v):
        x, r = v, v
        xs = []
        while True:
            mb = f(x)
            if mb.get('Nothing'):
                return xs
            else:
                x, r = mb.get('Just')
                xs.insert(0, r)
        return xs
    return go


# MAIN ---
if __name__ == '__main__':
    main()
Output:
Population count of first 30 powers of 3:
    [1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25]

First thirty 'evil' numbers:
    [0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58]

First thirty 'odious' numbers:
    [1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59]

Quackery

  [ 0 swap
    [ dup while
      dup 1 &
      rot + swap
      1 >>
      again ]
    drop ]                    is popcount       ( n --> n )

  [ 1 & ]                     is odd            ( n --> b )

  [ odd not ]                 is even           ( n --> b )


  [ ]'[ temp put 0
    [ over while 
        [ dup popcount
          temp share do
          if [ dup echo sp 
               dip [ 1 - ] ]
           1+ ] 
        again ] 
    2drop temp release ]      is echopopwith    ( n -->   )

  say "Population counts of the first thirty powers of 3." cr  
  30 times 
    [ 3 i^ ** popcount echo sp ] cr 
  cr
  say "The first thirty evil numbers." cr
  30 echopopwith even cr
  cr
  say "The first thirty odious numbers." cr
  30 echopopwith odd cr
Output:
Population counts of the first thirty powers of 3.
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 

The first thirty evil numbers.
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 

The first thirty odious numbers.
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

R

By default, R does not support 64-bit integer types. We therefore need the bit64 library and an awkward popCount function in order to make this work. Aside from the ugly one-liner that is the popCount function, the rest is trivial.

library(bit64)
popCount <- function(x) sum(as.numeric(strsplit(as.bitstring(as.integer64(x)), "")[[1]]))
finder <- function()
{
  odious <- evil <- integer(0)
  x <- odiousLength <- evilLength <- 0
  while(evilLength + odiousLength != 60)#We could be smarter, but this condition suffices.
  {
    if(popCount(x) %% 2 == 0) evil[evilLength + 1] <- x else odious[odiousLength + 1] <- x
    x <- x + 1
    evilLength <- length(evil)
    odiousLength <- length(odious)
  }
  cat("The pop count of the 1st 30 powers of 3 are:", sapply(3^(0:29), popCount), "\n")
  cat("The first 30 evil numbers are:", evil, "\n")
  cat("The first 30 odious numbers are:", odious)
}
finder()
Output:
The pop count of the 1st 30 powers of 3 are: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
The first 30 evil numbers are: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
The first 30 odious numbers are: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Racket

#lang racket
;; Positive version from "popcount_4" in:
;;   https://en.wikipedia.org/wiki/Hamming_weight#Efficient_implementation
;; negative version follows R6RS definition documented in:
;;   http://docs.racket-lang.org/r6rs/r6rs-lib-std/r6rs-lib-Z-H-12.html?q=bitwise-bit#node_idx_1074
(define (population-count n)
  (if (negative? n)
      (bitwise-not (population-count (bitwise-not n)))
      (let inr ((x n) (rv 0))
        (if (= x 0) rv (inr (bitwise-and x (sub1 x)) (add1 rv))))))

(define (evil? x)
  (and (not (negative? x))
       (even? (population-count x))))

(define (odious? x)
  (and (positive? x)
       (odd? (population-count x))))

(define tasks
  (list
   "display the pop count of the 1st thirty powers of 3 (3^0, 3^1, 3^2, 3^3, 3^4, ...)."
   (for/list ((i (in-range 30))) (population-count (expt 3 i)))
   "display the 1st thirty evil numbers."
   (for/list ((_ (in-range 30)) (e (sequence-filter evil? (in-naturals)))) e)
   "display the 1st thirty odious numbers."
   (for/list ((_ (in-range 30)) (o (sequence-filter odious? (in-naturals)))) o)))

(for-each displayln tasks)

(module+ test
  (require rackunit)
  (check-equal?
   (for/list ((p (sequence-map population-count (in-range 16)))) p)
   '(0 1 1 2 1 2 2 3 1 2 2 3 2 3 3 4))  
  (check-true (evil? 0) "0 has just *got* to be evil")
  (check-true (evil? #b011011011) "six bits... truly evil")
  (check-false (evil? #b1011011011) "seven bits, that's odd!")  
  (check-true (odious? 1) "the least odious number")
  (check-true (odious? #b1011011011) "seven (which is odd) bits")
  (check-false (odious? #b011011011) "six bits... is evil"))
Output:
display the pop count of the 1st thirty powers of 3 (3^0, 3^1, 3^2, 3^3, 3^4, ...).
(1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25)
display the 1st thirty evil numbers.
(0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58)
display the 1st thirty odious numbers.
(1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59)

Raku

(formerly Perl 6)

sub population-count(Int $n where * >= 0) { [+] $n.base(2).comb }

say map &population-count, 3 «**« ^30;
say "Evil: ", (grep { population-count($_) %% 2 }, 0 .. *)[^30];
say "Odious: ", (grep { population-count($_)  % 2 }, 0 .. *)[^30];
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

That's the convenient way to write it, but the following avoids string processing and is therefore about twice as fast:

sub population-count(Int $n is copy where * >= 0) { 
    loop (my $c = 0; $n; $n +>= 1) { 
        $c += $n +& 1; 
    } 
    $c;
}

REXX

The   pop count   is used in some encryption/decryption methods;   a major mainframe manufacturer was coerced  
(many years ago)   to add a hardware instruction to count the bits in a (binary) integer.

/*REXX program counts the number of "one" bits in the binary version of a decimal number*/
/*─────────────────── and also generates a specific number of  EVIL and ODIOUS  numbers.*/
parse arg N B .                                  /*get optional arguments from the C.L. */
if N==''  |  N==","   then N= 30                 /*N not specified?   Then use default. */
if B==''  |  B==","   then B=  3                 /*B  "      "          "   "      "    */
numeric digits 2000                              /*be able to handle  gihugeic  numbers.*/
numeric digits max(20, length(B**N) )            /*whittle the  precision  down to size.*/
$=                                               /* [↑]  a little calculation for sizing*/
     do j=0  for  N;   $= $ popCount(B**j)       /*generate N popCounts for some powers.*/
     end   /*j*/                                 /* [↑]  append popCount to the $ list. */
                                                 /* [↓]  display popCounts of "3" powers*/
call showList  'popCounts of the powers of'  B   /*display the list with a header/title.*/

     do j=0  until  #>=N                         /*generate   N   evil  numbers.        */
     if popCount(j) // 2  then iterate           /*if  odd population count, skip it.   */
     #= # + 1;      $= $ j                       /*bump evil # count;  add it to $ list.*/
     end   /*j*/                                 /* [↑]  build a list of evil numbers.  */
                                                 /* [↓]  display the evil number list.  */
call showList  'evil numbers'                    /*display the  $  list with a header.  */

     do j=0  until  #>=N                         /*generate   N   odious  numbers.      */
     if popCount(j) // 2 ==0  then iterate       /*if even population count, then skip. */
     #= # + 1;      $=$ j                        /*bump odious # count;  add to $ list. */
     end   /*j*/                                 /* [↑]  build a list of odious numbers.*/
                                                 /* [↓]  display the odious number list.*/
call showList  'odious numbers'                  /*display the   $  list with a header. */
exit                                             /*stick a fork in it,  we're all done. */
/*──────────────────────────────────────────────────────────────────────────────────────*/
d2b:      return word( strip( x2b( d2x( arg(1) ) ), 'L', 0)  0, 1)        /*dec ──► bin.*/
popCount: return length( space( translate( d2b(arg(1) ), , 0), 0) )       /*count ones. */
showList: say;   say 'The 1st'   N   arg(1)":";   say strip($);     #= 0;     $=;   return
output   when using the default input:
The 1st 30 popCounts of the powers of 3:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25

The 1st 30 evil numbers:
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58

The 1st 30 odious numbers:
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Ring

# Project : Population count

odds = []
evens = []
pows = []

for n = 0 to 59
      if n < 30 add(pows, onesCount(pow(3, n))) ok
      num = onesCount(n)
      if num & 1 = 0 add(evens, n) else add(odds, n) ok
next

showOne("3^x:", pows)
showOne("Evil numbers:", evens)
showOne("Odious numbers:", odds)

func onesCount(b)
      c = 0 m = 50
      while b > 0
            p = pow(2, m)
            if b >= p b -= p c++ ok
            m--
      end return c

func arrayToStr(ary)
      res = "[" s = ", "
      for n = 1 to len(ary)
            if ary[n] < 10 res += " " ok
            if n = len(ary) s = "]" ok
            res += "" + ary[n] + s
      next return res

func showOne(title, ary)
      ? title
      ? arrayToStr(ary) + nl
Output:
3^x:
[ 1,  2,  2,  4,  3,  6,  6,  5,  6,  8,  9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]

Evil numbers:
[ 0,  3,  5,  6,  9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]

Odious numbers:
[ 1,  2,  4,  7,  8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]

RPL

Translation of: Forth
≪ # 0b SWAP 
  WHILE DUP # 0b ≠ REPEAT 
     DUP # 1b AND ROT + SWAP SR END 
  DROP B→R 
≫ 'POPCT' STO

≪ POPCT 2 MOD 
≫ ‘ODUS?’ STO

≪ ODUS? NOT 
≫ ‘EVIL?’ STO
≪ → n 
  ≪ { } # 1b 1 n START 
        DUP POPCT ROT SWAP + SWAP 3 * NEXT DROP 
    { } # 0b WHILE OVER SIZE n < REPEAT 
        IF DUP EVIL? THEN SWAP OVER B→R + SWAP END 1 + END DROP 
    { } # 0b WHILE OVER SIZE n < REPEAT 
        IF DUP ODUS? THEN SWAP OVER B→R + SWAP END 1 + END DROP 
≫ ≫ ‘TASK’ STO

30 TASK
Output:
3: { 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 }
2: { 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 }
1: { 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 }

Ruby

Demonstrating lazy enumerators.

class Integer
 
  def popcount
    digits(2).count(1)     #pre Ruby 2.4: self.to_s(2).count("1")
  end
 
  def evil?
    self >= 0 && popcount.even?
  end

end
 
puts "Powers of 3:",  (0...30).map{|n| (3**n).popcount}.join(' ')
puts "Evil:"  , 0.step.lazy.select(&:evil?).first(30).join(' ')
puts "Odious:", 0.step.lazy.reject(&:evil?).first(30).join(' ')
Output:

Powers of 3: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 Evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Rust

fn main() {
    let mut num = 1u64;
    let mut vec = Vec::new();
    for _ in 0..30 {
        vec.push(num.count_ones());
        num *= 3;
    }
    println!("pop count of 3^0, 3^1 ... 3^29:\n{:?}",vec);
    let mut even = Vec::new();
    let mut odd  = Vec::new();
    num = 1;
    while even.len() < 30 || odd.len() < 30 {
        match 0 == num.count_ones()%2 {
            true if even.len() < 30 => even.push(num),
            false if odd.len() < 30 => odd.push(num),
            _                       => {}
        }
        num += 1;
    }
    println!("\nFirst 30 even pop count:\n{:?}",even);
    println!("\nFirst 30 odd pop count:\n{:?}",odd);
}
Output:
pop count of 3^0, 3^1 ... 3^29:
[1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]

First 30 even pop count:
[3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58, 60]

First 30 odd pop count:
[1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]

Scala

Output:
See it yourself by running in your browser either by ScalaFiddle (ES aka JavaScript, non JVM) or Scastie (remote JVM).
Works with: Scala version 2.13
import java.lang.Long.bitCount

object PopCount extends App {
  val nNumber = 30

  def powersThree(start: Long): LazyList[Long] = start #:: powersThree(start * 3L)

  println("Population count of 3ⁿ :")
  println(powersThree(1L).map(bitCount).take(nNumber).mkString(", "))

  def series(start: Long): LazyList[Long] = start #:: series(start + 1L)

  println("Evil numbers:")
  println(series(0L).filter(bitCount(_) % 2 == 0).take(nNumber).mkString(", "))

  println("Odious numbers:")
  println(series(0L).filter(bitCount(_) % 2 != 0).take(nNumber).mkString(", "))

}

Seed7

The function popcount below converts the integer into a bitset. The function card is used to compute the population count of the bitset.

$ include "seed7_05.s7i";
 
const func integer: popcount (in integer: n) is
    return card(bitset(n));
 
const proc: main is func
  local
    var integer: count is 0;
    var integer: num is 0;
  begin
    for num range 0 to 29 do
      write(popcount(3 ** num) <& " ");
    end for;
    writeln;
    write("evil:   ");
    for num range 0 to integer.last until count >= 30 do
      if not odd(popcount(num)) then
        write(num <& " ");
	incr(count);
      end if;
    end for;
    writeln;
    write("odious: ");
    count := 0;
    for num range 0 to integer.last until count >= 30 do
      if odd(popcount(num)) then
        write(num <& " ");
        incr(count);
      end if;
    end for;
    writeln;
  end func;
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 
evil:   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 
odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59 

SETL

program population_count;
    print([popcount(3**n) : n in [0..29]]);
    print([n : n in [0..59] | evil n]);
    print([n : n in [0..59] | odious n]);

    op evil(n);
        return even popcount n;
    end op;

    op odious(n);
        return odd popcount n;
    end op;

    op popcount(n);
        return +/[[n mod 2, n div:=2](1) : until n=0];
    end op;
end program;
Output:
[1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25]
[0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58]
[1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59]

Sidef

func population_count(n) { n.as_bin.count('1') }
say "#{0..29 «**« 3 «call« population_count -> join(' ')}"
 
var numbers = 60.of { |i|
    [i, population_count(i)]
}
 
say "Evil:   #{numbers.grep{_[1] %% 2}.map{.first}.join(' ')}"
say "Odious: #{numbers.grep{_[1] &  1}.map{.first}.join(' ')}"
Output:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Swift

func populationCount(n: Int) -> Int {
  guard n >= 0 else { fatalError() }

  return String(n, radix: 2).filter({ $0 == "1" }).count
}

let pows = (0...)
    .lazy
    .map({ Int(pow(3, Double($0))) })
    .map(populationCount)
    .prefix(30)

let evils = (0...)
    .lazy
    .filter({ populationCount(n: $0) & 1 == 0 })
    .prefix(30)

let odious = (0...)
    .lazy
    .filter({ populationCount(n: $0) & 1 == 1 })
    .prefix(30)

print("Powers:", Array(pows))
print("Evils:", Array(evils))
print("Odious:", Array(odious))
Output:
Powers: [1, 2, 2, 4, 3, 6, 6, 5, 6, 8, 9, 13, 10, 11, 14, 15, 11, 14, 14, 17, 17, 20, 19, 22, 16, 18, 24, 30, 25, 25]
Evils: [0, 3, 5, 6, 9, 10, 12, 15, 17, 18, 20, 23, 24, 27, 29, 30, 33, 34, 36, 39, 40, 43, 45, 46, 48, 51, 53, 54, 57, 58]
Odious: [1, 2, 4, 7, 8, 11, 13, 14, 16, 19, 21, 22, 25, 26, 28, 31, 32, 35, 37, 38, 41, 42, 44, 47, 49, 50, 52, 55, 56, 59]


Symsyn

| Pop Count 3^i

 i
 if i < 30
    (3^i) x
    popcount x 63 x
    ~ x $r
    + $r $s
    + ' ' $s
    + i
    goif
 endif
 "' Pop Count 3^i : ' $s " []

| Evil Numbers

 i
 cnt
 if cnt < 30
    popcount i 7 x
    x:0:1 y
    if y <> 1
       + cnt
       ~ i $r
       + $r $e
       + ' ' $e
    endif 
    + i
    goif
 endif
 "' Evil Numbers  : ' $e " []

| Odious Numbers 

 i
 cnt
 if cnt < 30
    popcount i 7 x
    x:0:1 y
    if y = 1
       + cnt
       ~ i $r
       + $r $o
       + ' ' $o
    endif 
    + i
    goif
 endif
 "' Odious Numbers : ' $o " []
Output:
Pop Count 3^i : 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil Numbers  : 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious Numbers : 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Tcl

Works with: Tcl version 8.6
package require Tcl 8.6

proc hammingWeight {n} {
    tcl::mathop::+ {*}[split [format %llb $n] ""]
}
for {set n 0;set l {}} {$n<30} {incr n} {
    lappend l [hammingWeight [expr {3**$n}]]
}
puts "p3: $l"
for {set n 0;set e [set o {}]} {[llength $e]<30||[llength $o]<30} {incr n} {
    lappend [expr {[hammingWeight $n]&1 ? "o" : "e"}] $n
}
puts "evil: [lrange $e 0 29]"
puts "odious: [lrange $o 0 29]"
Output:
p3: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil: 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

UNIX Shell

Works with: bash
popcount() {
    local -i n=$1
    (( n < 0 )) && return 1
    local ones=0
    while (( n > 0 )); do 
        (( ones += n%2 ))
        (( n /= 2 ))
    done
    echo $ones
}

popcount_3s=()
n=1
for (( i=0; i<30; i++ )); do
    popcount_3s+=( $(popcount $n) )
    (( n *= 3 ))
done
echo "powers of 3 popcounts: ${popcount_3s[*]}"

evil=()
odious=()
n=0
while (( ${#evil[@]} < 30 || ${#odious[@]} < 30 )); do
    p=$( popcount $n )
    if (( $p%2 == 0 )); then 
        evil+=( $n )
    else
        odious+=( $n )
    fi
    (( n++ ))
done
echo "evil nums:   ${evil[*]:0:30}"
echo "odious nums: ${odious[*]:0:30}"
Output:
powers of 3 popcounts: 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil nums:   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious nums: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

VBA

Translation of: VBScript
Works with: VBA version VBA Excel 2013

The Decimal subtype of Variant does the job to expand 32-bit integers (Long) to 28-digit integers (Decimal).

Sub Population_count()
    nmax = 30
    b = 3
    n = 0: List = "": bb = 1
    For i = 0 To nmax - 1
        List = List & " " & popcount(bb)
        bb = bb * b
    Next 'i
    Debug.Print "popcounts of the powers of " & b
    Debug.Print List
    For j = 0 To 1
        If j = 0 Then c = "evil numbers" Else c = "odious numbers"
        n = 0: List = "": i = 0
        While n < nmax
            If (popcount(i) Mod 2) = j Then
                n = n + 1
                List = List & " " & i
            End If
            i = i + 1
        Wend
        Debug.Print c
        Debug.Print List
    Next 'j
End Sub 'Population_count

Private Function popcount(x)
    Dim y, xx, xq, xr
    xx = x
    While xx > 0
        xq = Int(xx / 2)
        xr = xx - xq * 2
        If xr = 1 Then y = y + 1
        xx = xq
    Wend
    popcount = y
End Function 'popcount
Output:
popcounts of the powers of 3:
 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil numbers:
 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious numbers:
' 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

VBScript

Use of the variant currency subtype. Currency mode is a gray area where some operators do not work, for instance: ^ \ Mod

' Population count - VBScript - 10/05/2019
	nmax=30
	b=3
	n=0: list="": bb=1
	For i=0 To nmax-1
		list=list & " " & popcount(bb)
		bb=bb*b
	Next 'i
	Msgbox list,,"popcounts of the powers of " & b
	For j=0 to 1
		If j=0 Then c="evil numbers": Else c="odious numbers"
		n=0: list="": i=0
		While n<nmax
			If (popcount(i) Mod 2)=j Then
				n=n+1
				list=list & " " & i
			End If
			i=i+1
		Wend
		Msgbox list,,c
	Next 'j

Function popcount(x)
	Dim y,xx,xq,xr
	xx=x
	While xx>0
		xq=Int(xx/2)
		xr=xx-xq*2
		If xr=1 Then y=y+1
		xx=xq
	Wend
	popcount=y
End Function 'popcount
Output:
popcounts of the powers of 3:
 1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
evil numbers:
 0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
odious numbers:
 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Visual Basic .NET

Translation of: C#
Imports System.Console, System.Diagnostics

Module Module1

  Dim i As Integer, eo As Boolean
 
  Function PopCnt(n As Long) As Integer
    Return Convert.ToString(n, 2).ToCharArray().Where(Function(x) x = "1").Count()
  End Function
 
  Sub Aline(a As List(Of Integer), title As String)
    WriteLine("{0,-8}{1}", title, String.Join(" ", a.Take(30)))
  End Sub

  Sub Main(ByVal args As String())
    WriteLine("Population Counts:") : Dim t, e, o As New List(Of Integer)
    For c As Integer = 0 To 99
      If (PopCnt(c) And 1) = 0 Then e.Add(c) Else o.Add(c)
      If c < 30 Then t.Add(PopCnt(CLng(Math.Pow(3, c))))
    Next
    Aline(t, "3^n :") : Aline(e, "Evil:") : Aline(o, "Odious:")
    ' Extra:
    WriteLine(vbLf & "Pattern:{0}", Pattern(e, o))
    If Debugger.IsAttached Then ReadKey()
  End Sub

  ' support routines for pattern output
  Function Same(a As List(Of Integer)) As Boolean
    Return a(i) + 1 = a(i + 1)
  End Function

  Function Odd(a As List (Of Integer), b As List (Of Integer)) As Boolean
    eo = Not eo : If a(i) = b(i) + 1 Then i -= 1 : Return True
    Return False
  End Function

  Function SoO(a As List (Of Integer), b As List (Of Integer), c As String) As String
    Return If(Same(a), c(0), If(Odd(b, a), c(1), c(2)))
  End Function

  Function Either(a As List(Of Integer), b As List(Of Integer)) As String
    Return If(eo, SoO(a, b, "⌢↓↘"), SoO(b, a, "⌣↑↗"))
  End Function

  Function Pattern(a As List(Of Integer), b As List(Of Integer)) As String
    eo = a.Contains(0) : Dim res As New Text.StringBuilder
    For i = 0 To a.Count - 2 : res.Append(Either(a, b)) : Next
    Return res.ToString()
  End Function

End Module
Output:

Added a "Pattern" line. The "Pattern" line shows the sequence pattern of integers for the Evil and Odious output. The pattern goes to about 50, whereas only the first 30 Evil and Odious integers are shown.

Population Counts:
3^n :   1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:   0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious: 1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Pattern:↓⌣↑↘↑⌢↓⌣↑⌢↓↗↓⌣↑↘↑⌢↓↗↓⌣↑⌢↓⌣↑↘↑⌢↓⌣↑⌢↓↗↓⌣↑⌢↓⌣↑↘↑⌢↓↗↓⌣↑↘↑⌢↓⌣↑⌢↓↗↓⌣↑↘↑⌢↓↗↓⌣↑⌢↓⌣↑↘↑⌢↓↗↓⌣↑↘↑⌢↓⌣↑⌢↓↗↓⌣↑⌢↓⌣
P.S., The Pattern line may not appear properly on some browsers.

Wren

Library: Wren-big
Library: Wren-fmt

The first part is slightly awkward for Wren as 'native' bit-wise operations are limited to unsigned 32-bit integers and 3^21 exceeds this limit. We therefore need to switch to BigInts just before that point to process the remaining powers.

import "./big" for BigInt
import "./fmt" for Fmt

var popCount = Fn.new { |n|
    var count = 0
    while (n != 0) {
        n = n & (n - 1)
        count = count + 1
    }
    return count
}

System.print("The population count of the first 30 powers of 3 is:")
var p3 = 1
for (i in 0..29) {
    System.write("%(popCount.call(p3)) ")
    p3 = p3 * 3
    if (i == 20) p3 = BigInt.new(p3)
}
var odious = []
System.print("\n\nThe first 30 evil numbers are:")
var count = 0
var n = 0
while (count < 30) {
    var pc = popCount.call(n)
    if (pc%2 == 0) {
        System.write("%(n) ")
        count = count + 1
    } else {
        odious.add(n)
    }
    n = n + 1
}
odious.add(n)
System.print("\n\nThe first 30 odious numbers are:")
Fmt.print("$d", odious)
Output:
The population count of the first 30 powers of 3 is:
1 2 2 4 3 6 6 5 6 8 9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25 

The first 30 evil numbers are:
0 3 5 6 9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58 

The first 30 odious numbers are:
1 2 4 7 8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

XPL0

Double precision floating point numbers are used because XPL0's 32-bit integers don't have sufficient precision to reach 3^29. Double precision has a 53-bit mantissa that can represent integers up to 2^53, which is approximately 9.0e15 or approximately 3^33, which is sufficient.

func PopCnt(N);         \Return count of 1s in binary representation of N
real N;  int  C;
[C:= 0;
while N >= 0.5 do
    [if fix(Mod(N, 2.)) = 1 then C:= C+1;
    N:= Floor(N/2.);
    ];
return C;
];

proc Show30(LSb);       \Display 30 numbers with even or odd population count
int  LSb, C;  real N;   \Least Significant bit determines even or odd
[N:= 0.;  C:= 0;
repeat  if (PopCnt(N)&1) = LSb then
            [RlOut(0, N);  C:= C+1];
        N:= N+1.;
until   C >= 30;
CrLf(0);
];

real N;  int  P;
[Format(3, 0);
Text(0, "Pow 3: ");
N:= 1.;
for P:= 0 to 29 do
    [RlOut(0, float(PopCnt(N)));  N:= N*3.];
CrLf(0);
Text(0, "Evil:  ");  Show30(0);
Text(0, "Odious:");  Show30(1);
]
Output:
Pow 3:   1  2  2  4  3  6  6  5  6  8  9 13 10 11 14 15 11 14 14 17 17 20 19 22 16 18 24 30 25 25
Evil:    0  3  5  6  9 10 12 15 17 18 20 23 24 27 29 30 33 34 36 39 40 43 45 46 48 51 53 54 57 58
Odious:  1  2  4  7  8 11 13 14 16 19 21 22 25 26 28 31 32 35 37 38 41 42 44 47 49 50 52 55 56 59

Yabasic

print "Pop count (3^x): "

for i = 0 to 29
    print population(3^i);
next
print "\n"

print "Evil: "
EvilOdious(30)
print "\n"

print "Odious: "
EvilOdious(30, 1)
print "\n"

sub EvilOdious(limit, type)
    local i, count, eo
    
    repeat
        eo = mod(population(i), 2)
        if (type and eo) or (not type and not eo) count = count + 1 : print i;
        i = i + 1
    until(count = limit)
end sub

sub population(number)
    local i, binary$, popul
    
    binary$ = bin$(number)
    for i = 1 to len(binary$)
        popul = popul + val(mid$(binary$, i, 1))
    next
    return popul
end sub

zkl

Ints have the 1s count as a property.

n:=1; do(30){ print(n.num1s,","); n*=3 } println();
 
println("evil: ",[0..].filter(30,fcn(n){ n.num1s.isEven }).concat(","));

// now, as an iterator aka lazy:
println("odious: ",(0).walker(*).tweak(   // 0,1,2,3,4... iterator
   fcn(n){ if(n.num1s.isEven) Void.Skip else n }).walk(30).concat(","));
Output:
1,2,2,4,3,6,6,5,6,8,9,13,10,11,14,15,11,14,14,17,17,20,19,22,16,18,24,30,25,25,
evil: 0,3,5,6,9,10,12,15,17,18,20,23,24,27,29,30,33,34,36,39,40,43,45,46,48,51,53,54,57,58
odious: 1,2,4,7,8,11,13,14,16,19,21,22,25,26,28,31,32,35,37,38,41,42,44,47,49,50,52,55,56,59