Free polyominoes enumeration: Difference between revisions

From Rosetta Code
Content added Content deleted
(→‎{{header|Java}}: added Java)
Line 698: Line 698:


=={{header|Java}}==
=={{header|Java}}==
Translation of [[Free_polyominoes_enumeration#Haskell|Haskell]] via [[Free_polyominoes_enumeration#D|D]]
{{works with|Java|8}}
{{works with|Java|8}}
<lang java>import java.awt.Point;
<lang java>import java.awt.Point;

Revision as of 20:01, 28 March 2016

Free polyominoes enumeration is a draft programming task. It is not yet considered ready to be promoted as a complete task, for reasons that should be found in its talk page.

A Polyomino is a plane geometric figure formed by joining one or more equal squares edge to edge. Free polyominoes are distinct when none is a translation, rotation, reflection or glide reflection of another polyomino.

Task: generate all the free polyominoes with n cells.

You can visualize them just as a sequence of the coordinate pairs of their cells (rank 5):

[(0, 0), (0, 1), (0, 2), (0, 3), (0, 4)]
[(0, 0), (0, 1), (0, 2), (0, 3), (1, 0)]
[(0, 0), (0, 1), (0, 2), (0, 3), (1, 1)]
[(0, 0), (0, 1), (0, 2), (1, 0), (1, 1)]
[(0, 0), (0, 1), (0, 2), (1, 0), (1, 2)]
[(0, 0), (0, 1), (0, 2), (1, 0), (2, 0)]
[(0, 0), (0, 1), (0, 2), (1, 1), (2, 1)]
[(0, 0), (0, 1), (0, 2), (1, 2), (1, 3)]
[(0, 0), (0, 1), (1, 1), (1, 2), (2, 1)]
[(0, 0), (0, 1), (1, 1), (1, 2), (2, 2)]
[(0, 0), (0, 1), (1, 1), (2, 1), (2, 2)]
[(0, 1), (1, 0), (1, 1), (1, 2), (2, 1)]

But a better basic visualization is using ASCII art (rank 5):

#    ##   #    ##  ##  ###  #     #    #    #    #      #
#    #    ##   ##  #   #    ###   #    ###  ##   ###   ###
#    #    #    #   ##  #    #     ##    #    ##    #    #
#    #    #                        #
#

For a slow but clear solution see this Haskell Wiki page: http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue5/Generating_Polyominoes

Bonus Task: you can create an alternative program (or specialize your first program) to generate very quickly just the number of distinct free polyominoes, and to show a sequence like:

1, 1, 1, 2, 5, 12, 35, 108, 369, 1285, 4655, 17073, 63600, 238591, 901971, 3426576, ...

Number of free polyominoes (or square animals) with n cells: http://oeis.org/A000105

D

Translation of: Haskell

<lang d>import std.stdio, std.range, std.algorithm, std.typecons, std.conv;

alias Coord = byte; alias Point = Tuple!(Coord,"x", Coord,"y"); alias Polyomino = Point[];

/// Finds the min x and y coordiate of a Polyomino. enum minima = (in Polyomino poly) pure @safe =>

   Point(poly.map!q{ a.x }.reduce!min, poly.map!q{ a.y }.reduce!min);

Polyomino translateToOrigin(in Polyomino poly) {

   const minP = poly.minima;
   return poly.map!(p => Point(cast(Coord)(p.x - minP.x), cast(Coord)(p.y - minP.y))).array;

}

enum Point function(in Point p) pure nothrow @safe @nogc

   rotate90  = p => Point( p.y, -p.x),
   rotate180 = p => Point(-p.x, -p.y),
   rotate270 = p => Point(-p.y,  p.x),
   reflect   = p => Point(-p.x,  p.y);

/// All the plane symmetries of a rectangular region. auto rotationsAndReflections(in Polyomino poly) pure nothrow {

   return only(poly,
               poly.map!rotate90.array,
               poly.map!rotate180.array,
               poly.map!rotate270.array,
               poly.map!reflect.array,
               poly.map!(pt => pt.rotate90.reflect).array,
               poly.map!(pt => pt.rotate180.reflect).array,
               poly.map!(pt => pt.rotate270.reflect).array);

}

enum canonical = (in Polyomino poly) =>

   poly.rotationsAndReflections.map!(pl => pl.translateToOrigin.sort().release).reduce!min;

auto unique(T)(T[] seq) pure nothrow {

   return seq.sort().uniq;

}

/// All four points in Von Neumann neighborhood. enum contiguous = (in Point pt) pure nothrow @safe @nogc =>

   only(Point(cast(Coord)(pt.x - 1), pt.y), Point(cast(Coord)(pt.x + 1), pt.y),
        Point(pt.x, cast(Coord)(pt.y - 1)), Point(pt.x, cast(Coord)(pt.y + 1)));

/// Finds all distinct points that can be added to a Polyomino. enum newPoints = (in Polyomino poly) nothrow =>

   poly.map!contiguous.joiner.filter!(pt => !poly.canFind(pt)).array.unique;

enum newPolys = (in Polyomino poly) =>

   poly.newPoints.map!(pt => canonical(poly ~ pt)).array.unique;

/// Generates polyominoes of rank n recursively. Polyomino[] rank(in uint n) {

   static immutable Polyomino monomino = [Point(0, 0)];
   static Polyomino[] monominoes = [monomino]; // Mutable.
   if (n == 0) return [];
   if (n == 1) return monominoes;
   return rank(n - 1).map!newPolys.join.unique.array;

}

/// Generates a textual representation of a Polyomino. char[][] textRepresentation(in Polyomino poly) pure @safe {

   immutable minPt = poly.minima;
   immutable maxPt = Point(poly.map!q{ a.x }.reduce!max, poly.map!q{ a.y }.reduce!max);
   auto table = new char[][](maxPt.y - minPt.y + 1, maxPt.x - minPt.x + 1);
   foreach (row; table)
       row[] = ' ';
   foreach (immutable pt; poly)
       table[pt.y - minPt.y][pt.x - minPt.x] = '#';
   return table;

}

void main(in string[] args) {

   iota(1, 11).map!(n => n.rank.length).writeln;
   immutable n = (args.length == 2) ? args[1].to!uint : 5;
   writefln("\nAll free polyominoes of rank %d:", n);
   foreach (const poly; n.rank)
       writefln("%-(%s\n%)\n", poly.textRepresentation);

}</lang>

Output:
[1, 1, 2, 5, 12, 35, 108, 369, 1285, 4655]

All free polyominoes of rank 5:
#
#
#
#
#

##
#
#
#

#
##
#
#

##
##
#

##
#
##

###
#
#

#
###
#

#
#
##
 #

#
###
 #

#
##
 ##

#
###
  #

 #
###
 #

D: Count Only

Translated and modified from C code: http://www.geocities.jp/tok12345/countomino.txt

<lang d>import core.stdc.stdio: printf; import core.stdc.stdlib: atoi;

__gshared ulong[] g_pnCountNH; __gshared uint[] g_pnFieldCheck, g_pnFieldCheckR; __gshared uint g_nFieldSize, g_nFieldWidth; __gshared uint[4] g_anLinkData; __gshared uint[8] g_anRotationOffset, g_anRotationX, g_anRotationY;

void countMain(in uint n) nothrow {

   g_nFieldWidth = n * 2 - 2;
   g_nFieldSize = (n - 1) * (n - 1) * 2 + 1;
   g_pnCountNH = new ulong[n + 1];
   auto pnField = new uint[g_nFieldSize];
   auto pnPutList = new uint[g_nFieldSize];
   g_pnFieldCheck = new uint[n ^^ 2];
   g_pnFieldCheckR = new uint[n ^^ 2];
   g_anLinkData[0] = 1;
   g_anLinkData[1] = g_nFieldWidth;
   g_anLinkData[2] = -1;
   g_anLinkData[3] = -g_nFieldWidth;
   initOffset(n);
   countSub(n, 0, pnField, pnPutList, 0, 1);

}

void countSub(in uint n, in uint lv, uint[] field, uint[] putlist,

             in uint putno, in uint putlast) nothrow @nogc {
   check(field, n, lv);
   if (n == lv) {
       return;
   }
   foreach (immutable uint i; putno .. putlast) {
       immutable pos = putlist[i];
       field[pos] |= 1;
       uint k = 0;
       foreach (immutable uint j; 0 .. 4) {
           immutable pos2 = pos + g_anLinkData[j];
           if (0 <= pos2 && pos2 < g_nFieldSize && !field[pos2]) {
               field[pos2] = 2;
               putlist[putlast + k] = pos2;
               k++;
           }
       }
       countSub(n, lv + 1, field, putlist, i + 1, putlast + k);
       foreach (immutable uint j; 0 .. k)
           field[putlist[putlast + j]] = 0;
       field[pos] = 2;
   }
   foreach (immutable uint i; putno .. putlast) {
       immutable pos = putlist[i];
       field[pos] &= -2;
   }

}

void initOffset(in uint n) nothrow @nogc {

   g_anRotationOffset[0] = 0;
   g_anRotationX[0] = 1;
   g_anRotationY[0] = n;
   // 90
   g_anRotationOffset[1] = n - 1;
   g_anRotationX[1] = n;
   g_anRotationY[1] = -1;
   // 180
   g_anRotationOffset[2] = n ^^ 2 - 1;
   g_anRotationX[2] = -1;
   g_anRotationY[2] = -n;
   // 270
   g_anRotationOffset[3] = n ^^ 2 - n;
   g_anRotationX[3] = -n;
   g_anRotationY[3] = 1;
   g_anRotationOffset[4] = n - 1;
   g_anRotationX[4] = -1;
   g_anRotationY[4] = n;
   // 90
   g_anRotationOffset[5] = 0;
   g_anRotationX[5] = n;
   g_anRotationY[5] = 1;
   // 180
   g_anRotationOffset[6] = n ^^ 2 - n;
   g_anRotationX[6] = 1;
   g_anRotationY[6] = -n;
   // 270
   g_anRotationOffset[7] = n ^^ 2 - 1;
   g_anRotationX[7] = -n;
   g_anRotationY[7] = -1;

}

void check(in uint[] field, in uint n, in uint lv) nothrow @nogc {

   g_pnFieldCheck[0 .. n ^^ 2] = 0;
   uint x, y;
   outer:
   for (x = n; x < n * 2 - 2; x++)
       for (y = 0; y + x < g_nFieldSize; y += g_nFieldWidth)
           if (field[x + y] & 1)
               break outer;
   immutable uint x2 = n - x;
   foreach (immutable uint i; 0 .. g_nFieldSize) {
       x = (i + n - 2) % g_nFieldWidth;
       y = (i + n - 2) / g_nFieldWidth * n;
       if (field[i] & 1)
           g_pnFieldCheck[x + x2 + y] = 1;
   }
   uint of1;
   for (of1 = 0; of1 < g_pnFieldCheck.length && !g_pnFieldCheck[of1]; of1++) {}
   bool c = true;
   for (uint r = 1; r < 8 && c; r++) {
       for (x = 0; x < n; x++) {
           for (y = 0; y < n; y++) {
               immutable pos = g_anRotationOffset[r] +
                               g_anRotationX[r] * x + g_anRotationY[r] * y;
               g_pnFieldCheckR[pos] = g_pnFieldCheck[x + y * n];
           }
       }
       uint of2;
       for (of2 = 0; of2 < g_pnFieldCheckR.length && !g_pnFieldCheckR[of2]; of2++) {}
       of2 -= of1;
       immutable ed = (of2 > 0) ? (n ^^ 2 - of2) : (n ^^ 2);
       foreach (immutable uint i; of1 .. ed) {
           if (g_pnFieldCheck[i] > g_pnFieldCheckR[i + of2])
               break;
           if (g_pnFieldCheck[i] < g_pnFieldCheckR[i + of2]) {
               c = false;
               break;
           }
       }
   }
   if (c) {
       uint parity;
       if (!(lv & 1)) {
           parity = (lv & 2) >> 1;
           for (x = 0; x < n; x++)
               for (y = 0; y < n; y++)
                   parity ^= (x + y) & g_pnFieldCheck[x + y * n];
           parity &= 1;
       } else
           parity = 0;
       g_pnCountNH[lv]++;
   }

}

int main(in string[] args) {

   immutable n = (args.length == 2) ? (args[1] ~ '\0').ptr.atoi : 11;
   if (n < 1)
       return 1;
   if (n == 1)
       countMain(2);
   else
       countMain(n);
   foreach (immutable i; 1 .. n + 1)
       printf("%llu\n", g_pnCountNH[i]);
   return 0;

}</lang>

Output:
1
1
2
5
12
35
108
369
1285
4655
17073

Output with n=14 (run-time about 36 seconds):

1
1
2
5
12
35
108
369
1285
4655
17073
63600
238591
901971

Elixir

Translation of: Ruby

<lang elixir>defmodule Polyominoes do

 defp translate2origin(poly) do
   # Finds the min x and y coordiate of a Polyomino.
   minx = Enum.map(poly, &elem(&1,0)) |> Enum.min
   miny = Enum.map(poly, &elem(&1,1)) |> Enum.min
   Enum.map(poly, fn {x,y} -> {x - minx, y - miny} end) |> Enum.sort
 end
 
 defp rotate90({x, y}), do: {y, -x}
 defp reflect({x, y}), do: {-x, y}
 
 # All the plane symmetries of a rectangular region.
 defp rotations_and_reflections(poly) do
   poly1 = Enum.map(poly,  &rotate90/1)
   poly2 = Enum.map(poly1, &rotate90/1)
   poly3 = Enum.map(poly2, &rotate90/1)
   poly4 = Enum.map(poly3, &reflect/1)
   poly5 = Enum.map(poly4, &rotate90/1)
   poly6 = Enum.map(poly5, &rotate90/1)
   poly7 = Enum.map(poly6, &rotate90/1)
   [poly, poly1, poly2, poly3, poly4, poly5, poly6, poly7]
 end
 
 defp canonical(poly) do
   rotations_and_reflections(poly) |> Enum.map(&translate2origin/1)
 end
 
 # All four points in Von Neumann neighborhood.
 defp contiguous({x,y}) do
   [{x - 1, y}, {x + 1, y}, {x, y - 1}, {x, y + 1}]
 end
 
 # Finds all distinct points that can be added to a Polyomino.
 defp new_points(poly) do
   points = Enum.flat_map(poly, &contiguous/1)
   Enum.uniq(points) -- poly
 end
 
 defp new_polys(polys) do
   Enum.reduce(polys, {[], HashSet.new}, fn poly, {polyomino, pattern} ->
     Enum.reduce(new_points(poly), {polyomino, pattern}, fn point, {pol, pat} ->
       pl = translate2origin([point | poly])
       if pl in pat do
         {pol, pat}
       else
         canon = canonical(pl)
         {[Enum.min(canon) | pol], Enum.into(canon, pat)}
       end
     end)
   end)
   |> elem(0)
 end
 
 # Generates polyominoes of rank n recursively.
 def rank(0), do: [[]]
 def rank(1), do: [[{0,0}]]
 def rank(n), do: new_polys(rank(n-1))
 
 # Generates a textual representation of a Polyomino.
 def text_representation(poly) do
   table = Enum.map(poly, &{&1, "#"}) |> Enum.into(Map.new)
   maxx = Enum.map(poly, &elem(&1,0)) |> Enum.max
   maxy = Enum.map(poly, &elem(&1,1)) |> Enum.max
   Enum.map_join(0..maxx, "\n", fn x ->
     Enum.map_join(0..maxy, fn y -> Dict.get(table, {x,y}, " ") end)
   end)
 end

end

IO.inspect Enum.map(0..10, fn n -> length(Polyominoes.rank(n)) end)

n = if System.argv==[], do: 5, else: String.to_integer(hd(System.argv)) IO.puts "\nAll free polyominoes of rank #{n}:" Enum.sort(Polyominoes.rank(n)) |> Enum.each(fn poly -> IO.puts "#{Polyominoes.text_representation(poly)}\n" end)</lang>

Output:
[1, 1, 1, 2, 5, 12, 35, 108, 369, 1285, 4655]

All free polyominoes of rank 5:
#####

####
#

####
 #

###
##

###
# #

###
#
#

###
 #
 #

###
  ##

##
 ##
 #

##
 ##
  #

##
 #
 ##

 #
###
 #

Haskell

This Haskell solution is relatively slow, it's meant to be readable and as manifestly correct as possible.

Code updated and slightly improved from: http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue5/Generating_Polyominoes <lang haskell>import Data.List (sort) import Data.Set (toList, fromList) import System.Environment (getArgs)

type Coord = Int type Point = (Coord, Coord) type Polyomino = [Point]

-- Finds the min x and y coordiate of a Polyomino. minima :: Polyomino -> Point minima (p:ps) = foldr (\(x, y) (mx, my) -> (min x mx, min y my)) p ps

translateToOrigin :: Polyomino -> Polyomino translateToOrigin p =

   let (minx, miny) = minima p in
       map (\(x, y) -> (x - minx, y - miny)) p

rotate90, rotate180, rotate270, reflect :: Point -> Point rotate90 (x, y) = ( y, -x) rotate180 (x, y) = (-x, -y) rotate270 (x, y) = (-y, x) reflect (x, y) = (-x, y)

-- All the plane symmetries of a rectangular region. rotationsAndReflections :: Polyomino -> [Polyomino] rotationsAndReflections p =

   [p,
    map rotate90 p,
    map rotate180 p,
    map rotate270 p,
    map reflect p,
    map (rotate90 . reflect) p,
    map (rotate180 . reflect) p,
    map (rotate270 . reflect) p]

canonical :: Polyomino -> Polyomino canonical = minimum . map (sort . translateToOrigin) . rotationsAndReflections

unique :: (Ord a) => [a] -> [a] unique = toList . fromList

-- All four points in Von Neumann neighborhood. contiguous :: Point -> [Point] contiguous (x, y) = [(x - 1, y), (x + 1, y), (x, y - 1), (x, y + 1)]

-- Finds all distinct points that can be added to a Polyomino. newPoints :: Polyomino -> [Point] newPoints p =

   let notInP = filter (not . flip elem p) in
       unique . notInP . concatMap contiguous $ p

newPolys :: Polyomino -> [Polyomino] newPolys p = unique . map (canonical . flip (:) p) $ newPoints p

monomino = [(0, 0)] monominoes = [monomino]

-- Generates polyominoes of rank n recursively. rank :: Int -> [Polyomino] rank 0 = [] rank 1 = monominoes rank n = unique . concatMap newPolys $ rank (n - 1)

-- Generates a textual representation of a Polyomino. textRepresentaton :: Polyomino -> String textRepresentaton p =

   unlines  x <- [0 .. maxx - minx
            | y <- [0 .. maxy - miny]]
   where
       maxima :: Polyomino -> Point
       maxima (p:ps) = foldr (\(x, y) (mx, my) -> (max x mx, max y my)) p ps
       (minx, miny) = minima p
       (maxx, maxy) = maxima p

main = do

   print $ map (length . rank) [1 .. 10]
   args <- getArgs
   let n = if null args then 5 else read $ head args :: Int
   putStrLn ("\nAll free polyominoes of rank " ++ show n ++ ":")
   mapM_ putStrLn $ map textRepresentaton $ rank n</lang>
Output:
[1,1,2,5,12,35,108,369,1285,4655]

All free polyominoes of rank 5:
#
#
#
#
#

##
# 
# 
# 

# 
##
# 
# 

##
##
# 

##
# 
##

###
#  
#  

#  
###
#  

# 
# 
##
 #

#  
###
 # 

#  
## 
 ##

#  
###
  #

 # 
###
 # 

J

Generating polyominoes as ascii art:

<lang J>polyominoes=:verb define

 if. 1>y do. i.0 0 0 return.end.
 if. 1=y do. 1 1 1$'#' return.end.
 }.~.' ',simplify ,/extend"2 polyominoes y-1

)

extend=:verb define

 reps=. ' ',"1~~.all y
 simplify ,/extend1"2 reps

)

extend1=:verb define

 b=. (i.#y),._1|."1 '# ' E."1 y
 simplify ,/b extend2"1 _ y

)

extend2=:verb define

 row=.{.x
 mask=.}.x
 row mask extend3 y&>1+i.+/mask

)

extend3=:conjunction define

 '#' (<x,I.m*y=+/\m)} n

)

simplify=:verb define

 t=. ~.trim"2 y
 t #~ +./"1 ((2{.$) $ (i.@# = i.~)@(,/)) all@trim"2 t

)

flip=: |."_1 all=: , flip@|:, |.@flip, |.@|:, |., |.@flip@|:, flip,: |:

trim=:verb define&|:^:2

 y#~+./"1 y~:' '

)</lang>

Example use (boxing each pentomino for display purposes):

<lang j> <"2 polyominoes 5 ┌─────┬─────┬─────┬─────┬─────┬─────┬─────┬─────┬─────┬─────┬─────┬─────┐ │#####│## │# │### │## │## │### │ ## │ # │ # │ # │ ## │ │ │# │## │# │## │# │ ## │ # │ ## │ # │### │## │ │ │# │# │# │# │## │ │## │## │### │ # │# │ │ │# │# │ │ │ │ │ │ │ │ │ │ └─────┴─────┴─────┴─────┴─────┴─────┴─────┴─────┴─────┴─────┴─────┴─────┘</lang>

Java

Translation of Haskell via D

Works with: Java version 8

<lang java>import java.awt.Point; import java.util.*; import java.util.function.Function; import static java.util.Comparator.comparing; import static java.util.stream.Collectors.toList;

public class FreePolyominoesEnum {

   static final List<Function<Point, Point>> transforms = new ArrayList<>();
   static {
       transforms.add(p -> new Point(p.y, -p.x));
       transforms.add(p -> new Point(-p.x, -p.y));
       transforms.add(p -> new Point(-p.y, p.x));
       transforms.add(p -> new Point(-p.x, p.y));
       transforms.add(p -> new Point(-p.y, -p.x));
       transforms.add(p -> new Point(p.x, -p.y));
       transforms.add(p -> new Point(p.y, p.x));
   }
   static Point findMinima(List<Point> poly) {
       return new Point(
               poly.stream().mapToInt(a -> a.x).min().getAsInt(),
               poly.stream().mapToInt(a -> a.y).min().getAsInt());
   }
   static List<Point> translateToOrigin(List<Point> poly) {
       final Point min = findMinima(poly);
       return poly.stream().map(p -> new Point(p.x - min.x, p.y - min.y))
               .collect(toList());
   }
   static List<List<Point>> rotationsAndReflections(List<Point> poly) {
       List<List<Point>> lst = new ArrayList<>();
       lst.add(poly);
       for (Function<Point, Point> t : transforms)
           lst.add(poly.stream().map(t).collect(toList()));
       return lst;
   }
   static Comparator<Point> byCoords = Comparator.<Point>comparingInt(p -> p.x)
           .thenComparingInt(p -> p.y);
   static List<Point> normalize(List<Point> poly) {
       return rotationsAndReflections(poly).stream()
               .map(lst -> translateToOrigin(lst))
               .map(lst -> lst.stream().sorted(byCoords).collect(toList()))
               .min(comparing(Object::toString)) // not efficient but simple
               .get();
   }
   static List<Point> neighborhoods(Point p) {
       return Arrays.asList(new Point[]{new Point(p.x - 1, p.y),
           new Point(p.x + 1, p.y), new Point(p.x, p.y - 1),
           new Point(p.x, p.y + 1)});
   }
   static List<Point> concat(List<Point> lst, Point p) {
       List<Point> r = lst.stream().map(pt -> new Point(pt)).collect(toList());
       r.add(new Point(p));
       return r;
   }
   static List<Point> newPoints(List<Point> poly) {
       return poly.stream()
               .flatMap(p -> neighborhoods(p).stream())
               .filter(p -> !poly.contains(p))
               .distinct()
               .collect(toList());
   }
   static List<List<Point>> constructNextRank(List<Point> poly) {
       return newPoints(poly).stream()
               .map(p -> normalize(concat(poly, p)))
               .distinct()
               .collect(toList());
   }
   static List<List<Point>> rank(int n) {
       if (n < 0)
           throw new IllegalArgumentException("n cannot be negative");
       if (n < 2) {
           List<List<Point>> r = new ArrayList<>();
           if (n == 1)
               r.add(Arrays.asList(new Point[]{new Point(0, 0)}));
           return r;
       }
       return rank(n - 1).stream()
               .flatMap(lst -> constructNextRank(lst).stream())
               .distinct()
               .collect(toList());
   }
   public static void main(String[] args) {
       for (List<Point> poly : rank(5)) {
           for (Point p : poly)
               System.out.printf("(%d,%d) ", p.x, p.y);
           System.out.println();
       }
   }

}</lang>

(0,0) (0,1) (1,1) (1,2) (2,1) 
(0,0) (0,1) (0,2) (1,0) (1,1) 
(0,0) (0,1) (0,2) (0,3) (1,1) 
(0,1) (1,0) (1,1) (1,2) (2,1) 
(0,0) (0,1) (0,2) (1,1) (2,1) 
(0,0) (0,1) (1,1) (1,2) (2,2) 
(0,0) (0,1) (0,2) (1,2) (1,3) 
(0,0) (0,1) (1,1) (2,1) (2,2) 
(0,0) (0,1) (0,2) (1,0) (1,2) 
(0,0) (0,1) (0,2) (0,3) (1,0) 
(0,0) (0,1) (0,2) (1,0) (2,0) 
(0,0) (0,1) (0,2) (0,3) (0,4)

Python

Translation of: Haskell

<lang python>from itertools import imap, imap, groupby, chain, imap from operator import itemgetter from sys import argv from array import array

def concat_map(func, it):

   return list(chain.from_iterable(imap(func, it)))

def minima(poly):

   """Finds the min x and y coordiate of a Polyomino."""
   return (min(pt[0] for pt in poly), min(pt[1] for pt in poly))

def translate_to_origin(poly):

   (minx, miny) = minima(poly)
   return [(x - minx, y - miny) for (x, y) in poly]

rotate90 = lambda (x, y): ( y, -x) rotate180 = lambda (x, y): (-x, -y) rotate270 = lambda (x, y): (-y, x) reflect = lambda (x, y): (-x, y)

def rotations_and_reflections(poly):

   """All the plane symmetries of a rectangular region."""
   return (poly,
           map(rotate90, poly),
           map(rotate180, poly),
           map(rotate270, poly),
           map(reflect, poly),
           [reflect(rotate90(pt)) for pt in poly],
           [reflect(rotate180(pt)) for pt in poly],
           [reflect(rotate270(pt)) for pt in poly])

def canonical(poly):

   return min(sorted(translate_to_origin(pl)) for pl in rotations_and_reflections(poly))

def unique(lst):

   lst.sort()
   return map(next, imap(itemgetter(1), groupby(lst)))
  1. All four points in Von Neumann neighborhood.

contiguous = lambda (x, y): [(x - 1, y), (x + 1, y), (x, y - 1), (x, y + 1)]

def new_points(poly):

   """Finds all distinct points that can be added to a Polyomino."""
   return unique([pt for pt in concat_map(contiguous, poly) if pt not in poly])

def new_polys(poly):

   return unique([canonical(poly + [pt]) for pt in new_points(poly)])

monomino = [(0, 0)] monominoes = [monomino]

def rank(n):

   """Generates polyominoes of rank n recursively."""
   assert n >= 0
   if n == 0: return []
   if n == 1: return monominoes
   return unique(concat_map(new_polys, rank(n - 1)))

def text_representation(poly):

   """Generates a textual representation of a Polyomino."""
   min_pt = minima(poly)
   max_pt = (max(p[0] for p in poly), max(p[1] for p in poly))
   table = [array('c', ' ') * (max_pt[1] - min_pt[1] + 1)
            for _ in xrange(max_pt[0] - min_pt[0] + 1)]
   for pt in poly:
       table[pt[0] - min_pt[0]][pt[1] - min_pt[1]] = '#'
   return "\n".join(row.tostring() for row in table)

def main():

   print [len(rank(n)) for n in xrange(1, 11)]
   n = int(argv[1]) if (len(argv) == 2) else 5
   print "\nAll free polyominoes of rank %d:" % n
   for poly in rank(n):
       print text_representation(poly), "\n"

main()</lang>

Output:
[1, 1, 2, 5, 12, 35, 108, 369, 1285, 4655]

All free polyominoes of rank 5:
##### 

####
#    

####
 #   

###
##  

###
# # 

###
#  
#   

###
 # 
 #  

### 
  ## 

## 
 ##
 #  

## 
 ##
  # 

## 
 # 
 ## 

 # 
###
 #  

Racket

Uses Racket's arbitrary length integers as bit fields. It's not as compact as it possible could be (all numbers are "square" in shape), but it is correct.

Implemented in typed/racket. Don't balk at all the type annotations. In the right environment (DrRacket), they allow the developer to keep types in check.

Some functionality might be vestigial, or used in testing (test scripts not included in code below). But I think it's interesting nonetheless.

<lang racket>#lang typed/racket

Inspired by C code in http://www.geocities.jp/tok12345/countomino.txt
but tries to take advantage of arbitrary width integers

(define-type Order Positive-Integer) (define-type Shape Nonnegative-Integer)

"shape" functions are abbreviated s-...

(define-type Shapes (Listof Shape)) (define-type Shapes+ (Pairof Shape Shapes))

polynomino
order
number of bits wide a row of the "shape" is
shape
bit map (integer). bits set where the "animal" is

(struct polynominoes ([order : Order] [shapes : Shapes])) (define-type shape-xform (Order Shape -> Shape)) (: s-reflect:y shape-xform) (: s-reflect:x shape-xform) (: s-reflect:xy shape-xform) (: s-reflect:x=y shape-xform) (: s-all-xforms (Order Shape #:bottom-mask Shape #:left-mask Shape -> Shapes)) (: s-grow+2 shape-xform) (: s-shrink-1 shape-xform) (: s-normalise (Order Shape #:bottom-mask Shape #:left-mask Shape -> Shape)) (: draw-shapes (Order Shapes -> Void)) (: draw-polynominoes (polynominoes -> Void)) (: polynominoes->string (polynominoes -> String)) (: order-1-polynominoes polynominoes) (: shape-add-bit (Order Shape Nonnegative-Integer -> Shape)) (: s-add-all-edges

  (Order (Shape -> Shape) Shape #:bottom-mask Shape #:left-mask Shape (#:seen? (Shape -> Boolean))
         (#:seen! (Option (Shape -> Void))) -> Shapes))

(: s-least-xform (Order Shape #:bottom-mask Shape #:left-mask Shape

                       (#:seen? (Option (Shape -> Boolean))) -> (Option Shape)))

(: polynominoes-add-new-order (-> polynominoes polynominoes)) (: nth-order-polynominoes (-> Positive-Integer polynominoes)) (: s-identity shape-xform) (: order->bottom-mask (Order -> Shape)) (: order->left-mask (Order -> Shape))

get in touch with your inner C programmer

(define << arithmetic-shift) (define bits bitwise-bit-field)

(define (draw-shapes o sss)

 (let: loop ((need-newline? : Boolean #f) (sss sss))
   (define 10-or-sss-len (min (length sss) 10))
   (define ss (take sss 10-or-sss-len))
   (for ((y (in-range 0 o)))
     (for ((s (in-list ss)) (n (in-naturals)) #:when #t (x (in-range 0 o)))
       (match* (n y x)
         [(0 0 _) (void)] [(0 _ 0) (newline)] [(_ _ 0) (write-char #\space)] [(_ _ _) (void)])
       (write-char (cond [(bitwise-bit-set? s (+ x (* y o))) #\#] [else #\.]))))
   (newline)
   (define sss- (drop sss 10-or-sss-len))
   (unless (null? sss-) (when need-newline? (newline)) (loop #t sss-))))

(define (draw-polynominoes p)

 (draw-shapes (polynominoes-order p) (polynominoes-shapes p)))

(define (polynominoes->string p)

 (with-output-to-string (λ () (draw-polynominoes p))))

(define order-1-polynominoes (polynominoes 1 '(1)))

(define (shape-add-bit o s b)

 (bitwise-ior s (<< 1 b)))

(define (s-reflect:y o s)

 (let: loop ((s : Shape s) (s+ : Shape 0))
   (if (zero? s) s+ (loop (<< s (- o)) (bitwise-ior (bits s 0 o) (<< s+ o))))))

(define (s-reflect:x o s)

 (let y-loop ((s+ : Shape 0) (y : Nonnegative-Integer (- o 1)))
   (let x-loop ((s+ : Shape s+) (x : Nonnegative-Integer 0) (b (* o y)))
     (cond [(= o x) (if (= y 0) s+ (y-loop s+ (- y 1)))]
           [else (x-loop (bitwise-ior (<< s+ 1) (bits s b (+ b 1))) (+ x 1) (+ b 1))]))))

(define (s-reflect:xy o s) (s-reflect:x o (s-reflect:y o s)))

(define (s-reflect:x=y o s)

 (define o-1 (sub1 o))
 (let b-loop ((s+ : Shape 0) (w-y o-1) (w-x o-1))
   (cond [(< w-y 0) s+]
         [else (define r-bit (+ (* w-x o) w-y))
               (b-loop (bitwise-ior (<< s+ 1) (bits s r-bit (+ r-bit 1)))
                       (if (zero? w-x) (sub1 w-y) w-y)
                       (if (zero? w-x) o-1 (sub1 w-x)))])))

(define (s-identity o s) s)

(define (order->bottom-mask o) (- (expt 2 o) 1))

(define (order->left-mask o) (for/fold ((m : Shape 0)) ((i (in-range 0 o))) (bitwise-ior 1 (<< m o))))

(define (s-least-xform o s #:bottom-mask bm #:left-mask lm #:seen? (seen? #f))

 (: ss1 (Option Shapes))
 (define ss1
   (let loop : (Option Shapes)
     ((rv : (Option Shapes) null)
      (xs : (Listof shape-xform)
          (list s-identity s-reflect:y s-reflect:x s-reflect:xy)))
     (cond
       [(null? xs) rv]
       [(not rv) #f] ; option assures rv's type in else clause
       [else
        (define s_ (s-normalise o ((car xs) o s) #:bottom-mask bm #:left-mask lm))
        (if (and seen? (seen? s_)) #f (loop (cons s_ rv) (cdr xs)))])))
 
 (and ss1
      (let loop : (Option Shape)
        ((rv : (Option Shape) (sub1 (expt 2 (sqr o))))
         (ss : Shapes ss1))
        (cond
          [(null? ss) rv]
          [else
           (define s0 (car ss))
           (define s_ (s-normalise o (s-reflect:x=y o s0) #:bottom-mask bm #:left-mask lm))
           (define least-s (min s0 s_))
           (cond [(and seen? (seen? s_)) #f]
                 [else (and rv (loop (min rv least-s) (cdr ss)))])]))))

(define (s-all-xforms o s #:bottom-mask bm #:left-mask lm)

 (: s1 Shapes)
 (: s2 Shapes)
 (define s1
   (for/list : Shapes
     ((x : shape-xform (in-list (list s-reflect:y s-reflect:x s-reflect:xy))))
     (x o s)))
 (define s2
   (for/list : Shapes ((s+ : Shape (in-list (cons s s1))))
     (s-reflect:x=y o s+)))
 
 (for/list : Shapes ((s (in-list (append s1 s2))))
   (s-normalise o s #:bottom-mask bm #:left-mask lm)))

(define (s-grow+2 o s)

 (define o+2 (+ o 2))
 (define -o (- o))
 (define s+
   (let: loop : Shape ((s : Shape s) (shft : Nonnegative-Integer 0) (rv : Shape 0))
     (if (zero? s) rv
         (loop (<< s -o)
               (+ shft o+2)
               (bitwise-ior rv (<< (bits s 0 o) shft))))))
 (<< s+ (+ o+2 1))) ; centre it

(define (s-shrink-1 o s)

 (define o-1 (sub1 o))
 (define -o (- o))
 (let: loop : Shape ((s- : Shape s) (shft : Nonnegative-Integer 0) (rv : Shape 0))
   (if (zero? s-) rv (loop (<< s- -o) (+ shft o-1) (bitwise-ior rv (<< (bits s- 0 o) shft))))))

(define (s-normalise o s #:bottom-mask bm #:left-mask lm)

 (cond [(zero? s) s]; stop an infinte loop!
       [else
        (define -o (- o))  
        ;; if there are no bits in a mask, we need to pull some in from...
        (: s-down Shape)
        (define s-down (let: loop : Shape ((s : Shape s))
                         (if (zero? (bitwise-and s bm)) (loop (<< s -o)) s)))
        (let loop : Shape ((s : Shape s-down)) (if (zero? (bitwise-and s lm)) (loop (<< s -1)) s))]))

(define (s-add-all-edges o shrink s

                        #:bottom-mask bm #:left-mask lm
                        #:seen! (seen! #f) #:seen? (seen? #f))
 (define o+2 (+ o 2))
 (define s+ (s-grow+2 o s))
 ;; it will be of a new order with edges all round -- so expand it into that
 (define blur (bitwise-ior s+ (<< s+ 1) (<< s+ -1) (<< s+ o+2) (<< s+ (- o+2))))
 (let: loop : Shapes
   ((b : Nonnegative-Integer 0)
    (e : Shape (bitwise-xor blur s+)) ; the edge is the blur, less the original s+
    (rv : Shapes null))
   (match e
     [0 rv] ; run out of bits
     [(? even?) (loop (+ b 1) (<< e -1) rv)] ; bit 0 isn't
     [_ (define lsx (s-least-xform o+2 (shape-add-bit o+2 s+ b)
                                   #:bottom-mask bm #:left-mask lm #:seen? seen?))
        (loop (+ b 1) (<< e -1) (if lsx (begin0 (cons (shrink lsx) rv)
                                                (when seen! (seen! lsx)))
                                    rv))])))

(define (polynominoes-add-new-order p)

 (match-define (polynominoes o ss) p)
 (: saae (Shape -> Shapes))
 (: seen? (Shape -> Boolean))
 (: seen! (Shape -> Void))
 
 (define bm (order->bottom-mask (+ 2 o)))
 (define lm (order->left-mask (+ 2 o)))
 (define shrink (curry s-shrink-1 (+ o 2)))
 (define (seen! s) (hash-set! all-seen-shapes s #t))
 (define (seen? s) (hash-ref all-seen-shapes s #f))
 (define (saae s) (s-add-all-edges o shrink s #:seen? seen? #:seen! seen!
                                   #:bottom-mask bm #:left-mask lm))
 (define all-seen-shapes #{(make-hash) :: (HashTable Shape Boolean)})
 (define all-new-shapes
   (for*/list : Shapes ((k : Shape (in-list ss)) (s : Shape (in-list (saae k)))) s))  
 (polynominoes (add1 o) all-new-shapes))

(define nth-order-polynominoes

 (let ((polynominoes-cache #{(make-hash) :: (HashTable Positive-Integer polynominoes)}))
   (hash-set! polynominoes-cache 1 order-1-polynominoes)
   (lambda (n)
     (hash-ref! polynominoes-cache n
                (λ () (polynominoes-add-new-order
                       (nth-order-polynominoes (cast (sub1 n) Positive-Integer))))))))

(module+ main

 (time
  (for ((n : Positive-Integer (in-range 1 (add1 12))))
    (define p (time (nth-order-polynominoes n)))
    (printf "n: ~a~%" n)
    (when (< n 6) (draw-polynominoes p))
    (printf "count: ~a~%~%" (length (polynominoes-shapes p)))
    (flush-output))))</lang>
Output:

Output is done up to 13 (on my clockwork laptop... tomorrow, better results on a competent machine)

cpu time: 0 real time: 0 gc time: 0
n: 1
#
count: 1

cpu time: 0 real time: 0 gc time: 0
n: 2
##
..
count: 1

cpu time: 0 real time: 0 gc time: 0
n: 3
### ##.
... #..
... ...
count: 2

cpu time: 0 real time: 0 gc time: 0
n: 4
#### ###. ###. ##.. .##.
.... .#.. #... ##.. ##..
.... .... .... .... ....
.... .... .... .... ....
count: 5

cpu time: 0 real time: 0 gc time: 0
n: 5
##### ####. ####. #.... ###.. .#... .#... ###.. ###.. .###.
..... .#... #.... ###.. ##... ###.. ###.. #.... #.#.. ##...
..... ..... ..... #.... ..... .#... #.... #.... ..... .....
..... ..... ..... ..... ..... ..... ..... ..... ..... .....
..... ..... ..... ..... ..... ..... ..... ..... ..... .....
..#.. .##..
###.. ##...
#.... #....
..... .....
..... .....
count: 12

cpu time: 0 real time: 0 gc time: 0
n: 6
count: 35

cpu time: 0 real time: 0 gc time: 0
n: 7
count: 108

cpu time: 63 real time: 31 gc time: 0
n: 8
count: 369

cpu time: 187 real time: 94 gc time: 0
n: 9
count: 1285

cpu time: 735 real time: 360 gc time: 0
n: 10
count: 4655

cpu time: 3172 real time: 2189 gc time: 142
n: 11
count: 17073

cpu time: 9047 real time: 9048 gc time: 343
n: 12
count: 63600

cpu time: 75125 real time: 75508 gc time: 3310
n: 13
count: 238591

cpu time: 88985 real time: 87683 gc time: 3983

Ruby

Translation of: Python

<lang ruby>require 'set'

def translate2origin(poly)

 # Finds the min x and y coordiate of a Polyomino.
 minx = poly.map(&:first).min
 miny = poly.map(&:last).min
 poly.map{|x,y| [x - minx, y - miny]}.sort

end

def rotate90(x,y) [y, -x] end def reflect(x,y) [-x, y] end

  1. All the plane symmetries of a rectangular region.

def rotations_and_reflections(poly)

 [poly,
  poly = poly.map{|x,y| rotate90(x,y)},
  poly = poly.map{|x,y| rotate90(x,y)},
  poly = poly.map{|x,y| rotate90(x,y)},
  poly = poly.map{|x,y| reflect(x,y)},
  poly = poly.map{|x,y| rotate90(x,y)},
  poly = poly.map{|x,y| rotate90(x,y)},
         poly.map{|x,y| rotate90(x,y)} ]

end

def canonical(poly)

 rotations_and_reflections(poly).map{|pl| translate2origin(pl)}

end

  1. All four points in Von Neumann neighborhood.

def contiguous(x,y)

 [[x - 1, y], [x + 1, y], [x, y - 1], [x, y + 1]]

end

  1. Finds all distinct points that can be added to a Polyomino.

def new_points(poly)

 points = []
 poly.each{|x,y| contiguous(x,y).each{|point| points << point}}
 (points - poly).uniq

end

def new_polys(polys)

 pattern = Set.new
 polys.each_with_object([]) do |poly, polyomino|
   new_points(poly).each do |point|
     next if pattern.include?(pl = translate2origin(poly + [point]))
     polyomino << canonical(pl).each{|p| pattern << p}.min
   end
 end

end

  1. Generates polyominoes of rank n recursively.

def rank(n)

 case n
 when 0 then [[]]
 when 1 then [[[0,0]]]
 else        new_polys(rank(n-1))
 end

end

  1. Generates a textual representation of a Polyomino.

def text_representation(poly)

 table = Hash.new(' ')
 poly.each{|x,y| tablex,y = '#'}
 maxx = poly.map(&:first).max
 maxy = poly.map(&:last).max
 (0..maxx).map{|x| (0..maxy).map{|y| tablex,y}.join}

end

p (0..10).map{|n| rank(n).size} n = ARGV[0] ? ARGV[0].to_i : 5 puts "\nAll free polyominoes of rank %d:" % n rank(n).sort.each{|poly| puts text_representation(poly),""}</lang>

Output:
[1, 1, 1, 2, 5, 12, 35, 108, 369, 1285, 4655]

All free polyominoes of rank 5:
#####

####
#   

####
 #  

###
## 

###
# #

###
#  
#  

###
 # 
 # 

### 
  ##

## 
 ##
 # 

## 
 ##
  #

## 
 # 
 ##

 # 
###
 #