(*********************************************************************** Mathematica-Compatible Notebook This notebook can be used on any computer system with Mathematica 4.0, MathReader 4.0, or any compatible application. The data for the notebook starts with the line containing stars above. To get the notebook into a Mathematica-compatible application, do one of the following: * Save the data starting with the line of stars above into a file with a name ending in .nb, then open the file inside the application; * Copy the data starting with the line of stars above to the clipboard, then use the Paste menu command inside the application. Data for notebooks contains only printable 7-bit ASCII and can be sent directly in email or through ftp in text mode. Newlines can be CR, LF or CRLF (Unix, Macintosh or MS-DOS style). NOTE: If you modify the data for this notebook not in a Mathematica- compatible application, you must delete the line below containing the word CacheID, otherwise Mathematica-compatible applications may try to use invalid cache data. For more information on notebooks and Mathematica-compatible applications, contact Wolfram Research: web: http://www.wolfram.com email: info@wolfram.com phone: +1-217-398-0700 (U.S.) Notebook reader applications are available free of charge from Wolfram Research. ***********************************************************************) (*CacheID: 232*) (*NotebookFileLineBreakTest NotebookFileLineBreakTest*) (*NotebookOptionsPosition[ 471783, 10353]*) (*NotebookOutlinePosition[ 472572, 10381]*) (* CellTagsIndexPosition[ 472528, 10377]*) (*WindowFrame->Normal*) Notebook[{ Cell[CellGroupData[{ Cell["Hadamard Search Package", "Title", TextAlignment->Center], Cell["\<\ Victor Alvarez Solano, Jose Andres Armario Sampalo, Maria Dolores \ Frau Garcia and Pedro Real Jurado Departamento de Matematica Aplicada I, University of Seville (Spain) 19 August 2006\ \>", "Subtitle"], Cell["valvarez@us.es", "Subsubtitle"], Cell[TextData[{ "Determining Hadamard matrices at a desired dimension is a very difficult \ task. Furthermore, the Hadamard conjecture about the existence of Hadamard \ matrices at every dimension multiple of 4 is still open. A new insight on the \ subject was provided by the tandem De Launey-Horadam in the early 90s, in \ terms of ", StyleBox["cocyclic", FontSlant->"Italic"], " Hadamard matrices. The term cocyclic refers to cocycles coming from the \ second group of cohomology. The main difficulty in this approximation is how \ to explicitly construct a basis for 2-cocycles. This question is \ significantly skipped with the use of the so-called ", StyleBox["homologial reduction method", FontSlant->"Italic"], ", provided a ", StyleBox["homological model", FontSlant->"Italic"], " for the given group is known. This package provides a means of explicitly \ constructing a basis for 2-cocycles on G from a homological model hG for G. \ Depending on the choice of the user, an exhaustive (which is only recommended \ for low dimensions) or heuristic search for cocyclic Hadamard matrices over G \ is then developed." }], "Text"], Cell[CellGroupData[{ Cell["Reference", "Section"], Cell[CellGroupData[{ Cell["Title", "Subsubsection"], Cell[TextData[StyleBox["Hadamard Search", FontSlant->"Italic"]], "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Author", "Subsubsection"], Cell["\<\ Victor Alvarez Solano, Jose Andres Armario Sampalo, Maria Dolores \ Frau Garcia and Pedro Real Jurado\ \>", "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Summary", "Subsubsection"], Cell["\<\ This package is designed to find out some cocyclic Hadamard \ matrices over a finite group G, provided a homological model for G is \ known.\ \>", "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Copyright", "Subsubsection"], Cell["\<\ Rights reserved by Victor Alvarez Solano et al, Departamento de \ Matematica Aplicada I, University of Seville (Spain).\ \>", "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Notebook Version", "Subsubsection"], Cell["2.0", "Text"] }, Open ]], Cell[CellGroupData[{ Cell[TextData[{ StyleBox["Mathematica", FontSlant->"Italic"], " Version" }], "Subsubsection"], Cell["4.0", "Text"] }, Open ]], Cell[CellGroupData[{ Cell["History", "Subsubsection"], Cell["\<\ This package is the implementation in practise of the homological \ reduction method for constructing a basis for 2-cocycles over a finite group \ for which a homological model is known. Furthermore, a routine for developing \ a heuristic search (in terms of a genetic algorithm) is also included. This \ tool is very useful when exhaustive search is not possible (usually for \ groups of order equal to or greater than 28).\ \>", "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Keywords", "Subsubsection"], Cell["\<\ Hadamard matrix, cocyclic Hadamard matrix, homological model, \ homological reduction method.\ \>", "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Limitation", "Subsubsection"], Cell[TextData[StyleBox["This package works only on finite groups for which \ some homological models are known.", FontSlant->"Italic"]], "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Discussion", "Subsubsection"], Cell[TextData[StyleBox["References:\nAn algorithm for computing cocyclic \ matrices developed over some semidirect products. V. Alvarez, J.A. Armario, \ M.D. Frau and P. Real, LNCS 2227, 287--296 (2001).\nA genetic algorithm for \ cocyclic Hadamard matrices. V. Alvarez, J.A. Armario, M.D. Frau and P. Real, \ LNCS 3857, 144--153 (2006).\nCalculating cocyclic Hadamard matrices in \ Mathematica: exhaustive and heuristic searches. V. Alvarez, J.A. Armario, \ M.D. Frau and P. Real, LNCS 4151, 119--122 (2006).\nHomological reduction \ method for constructing cocyclic Hadamard matrices. V. Alvarez, J.A. Armario, \ M.D. Frau and P. Real (in preparation).", FontSlant->"Italic"]], "Text"] }, Open ]], Cell[CellGroupData[{ Cell["Requirements", "Subsubsection"], Cell[TextData[{ StyleBox["Context`HadamardSearch`\nuses ", FontFamily->"Courier", FontWeight->"Bold", FontSlant->"Italic"], "IntegerSmithNormalForm, due to V. Alvarez et al, 2006;" }], "Text"] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell["Interface", "Section", InitializationCell->True], Cell["\<\ This part declares the publicly visible functions, options, and \ values.\ \>", "Text", InitializationCell->True], Cell[CellGroupData[{ Cell["Set up the package context, including public imports", "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell["BeginPackage[\"`HadamardSearch`\"]", "Input", InitializationCell->True], Cell[BoxData[ \("Global`HadamardSearch`"\)], "Output"] }, Open ]], Cell[CellGroupData[{ Cell[BoxData[ \($ContextPath\)], "Input"], Cell[BoxData[ \({"Global`HadamardSearch`", "System`"}\)], "Output"] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell["\<\ Usage messages for the exported functions and the context \ itself\ \>", "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell["\<\ HadamardSearch::usage=\"HadamardSearch[PR,M2,M3,F1,F2,method] \ searches for cocyclic Hadamard matrices over a finite group G of group law \ given by the square matrix PR. The notebook will assume the ordering implicit \ in PR for the elements in G. Special care must be taken so that the first \ element in G is the identity element. The search may be both exhaustive and \ heuristic, depending on whether method=1 or method !=1. The matrices M2 and \ M3 represent the differentials d2 and d3 on the homological model hG. The \ matrices F1 and F2 represent the projection maps from B_1(Z[G]) to hG_1 and \ B_2(Z[G]) to hG_2, respectively. Let denote the number of elements in G by \ _order_ (=Length[PR]). The _order_ elements in B_1(Z[G]) are ordered \ following the natural ordering induced by PR. The _order_^2 elements in \ B_2(Z[G]) are ordered as the elements of G x G, from the first row to the \ last one, from left to the right, as \ {1,1},{1,2},...,{1,_order_},{2,1},...,{2,_order_},...,{_order_,1},...{_order_,\ _order_}. Of course, the same basis for hG at each degree must be used for \ M2,M3,F1 and F2. There is an explicit example included as a comment at the \ end of the package.\"\ \>", "Input", InitializationCell->True], Cell[BoxData[ \("HadamardSearch[PR,M2,M3,F1,F2,method] searches for cocyclic Hadamard \ matrices over a finite group G of group law given by the square matrix PR. \ The notebook will assume the ordering implicit in PR for the elements in G. \ Special care must be taken so that the first element in G is the identity \ element. The search may be both exhaustive and heuristic, depending on \ whether method=1 or method !=1. The matrices M2 and M3 represent the \ differentials d2 and d3 on the homological model hG. The matrices F1 and F2 \ represent the projection maps from B_1(Z[G]) to hG_1 and B_2(Z[G]) to hG_2, \ respectively. Let denote the number of elements in G by _order_ \ (=Length[PR]). The _order_ elements in B_1(Z[G]) are ordered following the \ natural ordering induced by PR. The _order_^2 elements in B_2(Z[G]) are \ ordered as the elements of G x G, from the first row to the last one, from \ left to the right, as \ {1,1},{1,2},...,{1,_order_},{2,1},...,{2,_order_},...,{_order_,1},...{_order_,\ _order_}. Of course, the same basis for hG at each degree must be used for \ M2,M3,F1 and F2. There is an explicit example included as a comment at the \ end of the package."\)], "Output"] }, Open ]] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell["Implementation", "Section", InitializationCell->True], Cell["\<\ This part contains the actual definitions and any auxiliary \ functions that should not be visible outside.\ \>", "Text"], Cell[CellGroupData[{ Cell["Begin the private context (implementation part)", "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell["\<\ Begin[\"`Private`\"] {$Context,$ContextPath}\ \>", "Input", InitializationCell->True], Cell[BoxData[ \("Global`HadamardSearch`Private`"\)], "Output"], Cell[BoxData[ \({"Global`HadamardSearch`Private`", {"Global`HadamardSearch`", "System`"}}\)], "Output"] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell["\<\ Definition of auxiliary functions and local (static) \ variables\ \>", "Subsection", InitializationCell->True], Cell[BoxData[{ \( (*\[IndentingNewLine]\[IndentingNewLine]We\ use\ the\ \ IntegerSmithNormalForm\ package\ due\ to\ V . \ Alvarez\ et\ al, \ 2006. \[IndentingNewLine]\[IndentingNewLine]*) \n\(M[i_, j_, t_, k_] := ReplacePart[IdentityMatrix[k], t, {i, j}];\)\), "\[IndentingNewLine]", \(\(T[i_, j_, k_] := Module[{m, n}, m = IdentityMatrix[k]; n = m[\([i]\)]; m[\([i]\)] = m[\([j]\)]; m[\([j]\)] = n; m];\)\), "\[IndentingNewLine]", \(\(Completar[C_, m_, n_] := Module[{k, i, j, ii}, i = m - Length[C]; k = {}; Do[k = Append[k, Table[0, {ii, 1, n}]], {j, 1, i}]; Do[k = Append[k, Join[Table[0, {ii, 1, n - Length[C[\([1]\)]]}], C[\([j]\)]]], {j, 1, Length[C]}]; k];\)\), "\[IndentingNewLine]", \(\(ExtendedSmithForm[A_] := Module[{k, C, coli, colj, P, Q, m, n, H, i, it, control}, m = Length[A]; n = Length[A[\([1]\)]]; P = {IdentityMatrix[m]}; Q = {IdentityMatrix[n]}; C = A; i = 1; Fin = Max[Abs[Take[C, {i, m}, {i, n}]]] > 0; \[IndentingNewLine]While[ Fin, {coli, colj} = \(Position[ Completar[Take[Abs[C], {i, m}, {i, n}], m, n], Min[Select[ Flatten[ Take[Abs[C], {i, m}, {i, n}]], #1 > 0 &]]]\)[\([1]\)]; P = Prepend[P, T[i, coli, m]]; Q = Append[Q, T[i, colj, n]]; it = i + 1; C = First[P] . C . Last[Q]; control = True; \[IndentingNewLine]While[it \[LessEqual] n, If[IntegerQ[C[\([i, it]\)]/C[\([i, i]\)]], it = it + 1, Q = Append[Q, M[i, it, \(-Quotient[C[\([i, it]\)], C[\([i, i]\)]]\), n] . T[it, i, n]]; C = C . Last[Q]; control = False; it = n + 1]\[IndentingNewLine]]; If[control, Do[Q = Append[Q, M[i, it, \(-C[\([i, it]\)]\)/C[\([i, i]\)], n]]; C = C . Last[Q], {it, i + 1, n}]; it = i + 1; \[IndentingNewLine]While[it \[LessEqual] m, If[IntegerQ[C[\([it, i]\)]/C[\([i, i]\)]], it = it + 1, P = Prepend[P, T[it, i, m] . M[it, i, \(-Quotient[C[\([it, i]\)], C[\([i, i]\)]]\), m]]; C = First[P] . C; control = False; it = m + 1]\[IndentingNewLine]]; If[control, Do[P = Prepend[P, M[it, i, \(-C[\([it, i]\)]\)/C[\([i, i]\)], m]]; C = First[P] . C, {it, i + 1, m}]; \[IndentingNewLine]Catch[ Do[\[IndentingNewLine]Do[ If[IntegerQ[C[\([coli, colj]\)]/C[\([i, i]\)]], Null, P = Prepend[P, M[i, coli, 1, m]]; C = First[P] . C; control = False; Throw[False]], {colj, i + 1, n}], {coli, i + 1, m}]; Throw[True]]; If[\ control, P = Prepend[P, M[i, i, Sign[C[\([i, i]\)]], m]]; C = First[P] . C; i = i + 1; Fin = Max[Abs[Take[C, {i, m}, {i, n}]]] > 0]\[IndentingNewLine]];\[IndentingNewLine]];\ \[IndentingNewLine]]; \[IndentingNewLine]P = Fold[Dot, IdentityMatrix[m], P]; Q = Fold[Dot, IdentityMatrix[n], Q]; {C, {P, Q}}\[IndentingNewLine]];\)\[IndentingNewLine] \ (*\[IndentingNewLine]\[IndentingNewLine]\[IndentingNewLine]*) \)}], "Input", InitializationCell->True], Cell[BoxData[{ \( (*\ \[IndentingNewLine]\[IndentingNewLine]Auxiliary\ functions\ for\ \ constructing\ a\ basis\ for\ representative\ 2 - cocycles\ coming\ from\ \(\(inflation\)\(.\)\)\[IndentingNewLine]\ \[IndentingNewLine]*) \[IndentingNewLine]\(matrizdeunos[n_] := Table[Table[1, {j, n}], {i, n}];\)\), "\[IndentingNewLine]", \(\(matriznegaciclica[n_] := Table[Join[Table[1, {j1, n + 1 - j}], Table[\(-1\), {j2, n + 2 - j, n}]], {j, n}];\)\), "\[IndentingNewLine]", \(\(kronunosaizq[a_, n_] := Flatten[Table[ Table[Apply[Join, Table[Table[a[\([i, k]\)], {k2, n}], {k, Length[a[\([1]\)]]}]], {j, n}], {i, Length[a[\([1]\)]]}], 1];\)\), "\[IndentingNewLine]", \(\(kronunosader[a_, n_] := Flatten[Table[ Table[Apply[Join, Table[a[\([j]\)], {k, n}]], {j, Length[a[\([1]\)]]}], {i, n}], 1];\)\)}], "Input", InitializationCell->True], Cell[BoxData[ \(\(\( (*\[IndentingNewLine]Cocyclic\ Hadamard\ \(\(Test\)\(.\)\)\ \ \[IndentingNewLine]*) \)\(\[IndentingNewLine]\)\(testhadamard[ L_] := \n\t\tCatch[ Do[If[Apply[Plus, L[\([i]\)]] \[NotEqual] 0, Throw[False]], {i, 2, Length[L]}]; Throw[True]];\)\)\)], "Input", InitializationCell->True], Cell[BoxData[ \(\(\( (*\ \[IndentingNewLine]Hadamard\ pointwise\ \(\(product\)\(.\)\)\ \ \[IndentingNewLine]*) \)\(\[IndentingNewLine]\)\(prodhadamard[a_, b_] := Table[Table[ a[\([i, j]\)]*b[\([i, j]\)], {j, Length[a[\([1]\)]]}], {i, Length[a[\([1]\)]]}];\)\)\)], "Input", InitializationCell->True] }, Open ]], Cell[CellGroupData[{ Cell["Main program", "Subsection", InitializationCell->True], Cell[BoxData[ \(\(\( (*\[IndentingNewLine]\[IndentingNewLine]Main\ program\ \[IndentingNewLine]\[IndentingNewLine]*) \)\(\[IndentingNewLine]\)\(\ HadamardSearch[PR_, M2_, M3_, F1_, F2_, method_] := Module[{}, \[IndentingNewLine] (*\ \[IndentingNewLine]\ \[IndentingNewLine]Calculating\ H1\ and\ \(\(H2\)\(.\)\)\ \[IndentingNewLine]\ \[IndentingNewLine]*) \[IndentingNewLine] (*\ b1\ and\ b2\ denote\ the\ number\ of\ generators\ in\ the\ \ homological\ model\ at\ degrees\ 1\ and\ 2, \ \(\(respectively\)\(.\)\)\ \ *) \[IndentingNewLine]fnsa1 = ExtendedSmithForm[M2]; b1 = Length[M2[\([1]\)]]; b2 = Length[M2]; \[IndentingNewLine]abelianizado = Select[Table[ fnsa1[\([1, ji, ji]\)], {ji, b1}], #1 > 0 &]; \[IndentingNewLine]b1 = b2; b2 = Length[M3]; \[IndentingNewLine]fnsa2 = ExtendedSmithForm[M3]; \[IndentingNewLine]homologia = Select[Table[ fnsa2[\([1, ji, ji]\)], {ji, b1}], #1 > 0 &]; \[IndentingNewLine] (*\[IndentingNewLine]\ \ \[IndentingNewLine]Constructing\ a\ basis\ _base2cociclos _\ for\ normalized\ \ 2 - \(\(cocycles\)\(.\)\)\ \[IndentingNewLine]\[IndentingNewLine]\ *) \[IndentingNewLine]base2cociclos = {}; \ \[IndentingNewLine]Print["\"]; \ \[IndentingNewLine] (*\ \[IndentingNewLine]\[IndentingNewLine]Constructing\ a\ \ basis\ for\ 2 - \(\(coboundaries\)\(.\)\)\ \[IndentingNewLine]\ \[IndentingNewLine]*) \[IndentingNewLine]orden = Length[PR]; \[IndentingNewLine]cobordes = Table[Apply[Join, Table[Table[ Mod[KroneckerDelta[i, k] + KroneckerDelta[i, j] + KroneckerDelta[i, PR[\([k, j]\)]], 2], {j, orden}], {k, orden}]], {i, 2, orden}]; \[IndentingNewLine]m = cobordes; gen = {}; \[IndentingNewLine]i = 0; \[IndentingNewLine]While[ i < orden - 1, \[IndentingNewLine]n = Select[Range[i + 1, orden - 1], m[\([#1]\)] \[NotEqual] Table[0, {k, orden^2}] &, 1]; \[IndentingNewLine]If[n \[Equal] {}, i = orden - 1, gen = Join[gen, n]; i = n[\([1]\)]; \[IndentingNewLine]j = Position[m[\([i]\)], 1, 1, 1]; \[IndentingNewLine]filas = Select[Range[i + 1, orden - 1], m[\([#1, j[\([1, 1]\)]]\)] \[Equal] 1 &]; \[IndentingNewLine]Do[ m = ReplacePart[m, Mod[m[\([filas[\([k]\)]]\)] + m[\([i]\)], 2], filas[\([k]\)]], {k, Length[filas]}]];\[IndentingNewLine]]; \ \[IndentingNewLine]Do[ base2cociclos = Append[base2cociclos, Partition[ Replace[ Replace[cobordes[\([gen[\([i]\)]]\)], 1 \[Rule] \(-1\), 1], 0 \[Rule] 1, 1], orden]]; \[IndentingNewLine]Print["\", gen[\([i]\)] + 1, "\<-ith 2-coboundary is a generator:\>"]; Print[base2cociclos[\([i]\)] // MatrixForm], {i, Length[gen]}]; \[IndentingNewLine] (*\ \[IndentingNewLine]\ \[IndentingNewLine]Constructing\ a\ basis\ for\ representative\ 2 - cocycles\ coming\ from\ \(\(inflation\)\(.\)\)\ \[IndentingNewLine]\[IndentingNewLine]*) \[IndentingNewLine]Print["\<\ Calculating a system of generators for 2-cocycles coming from \ inflation...\>"]; \[IndentingNewLine]k = Select[Range[Length[abelianizado]], EvenQ[abelianizado[\([#1]\)]] &]; Do[col = Select[Range[Length[M2[\([1]\)]]], Mod[fnsa1[\([2, 2, #1, k[\([m1]\)]]\)], abelianizado[\([k[\([m1]\)]]\)]] \[NotEqual] 0 &]; matriz = {Table[1, {i, orden}]}; m2 = 2^\(FactorInteger[abelianizado[\([k[\([m1]\)]]\)]]\)[\([1, 2]\)]; Do[matriz = Append[matriz, {1}]; Do[mi = F1[\([i]\)]; mj = F1[\([j]\)]; n = Mod[ Apply[Plus, Table[fnsa1[\([2, 2, col[\([m3]\)], k[\([m1]\)]]\)]* mi[\([col[\([m3]\)]]\)], {m3, Length[col]}]], m2] + Mod[ Apply[Plus, Table[fnsa1[\([2, 2, col[\([m3]\)], k[\([m1]\)]]\)]* mj[\([col[\([m3]\)]]\)], {m3, Length[col]}]], m2]; matriz[\([i]\)] = Append[matriz[\([i]\)], \((\(-1\))\)^Floor[n/m2]], {j, 2, orden}], {i, 2, orden}]; base2cociclos = Append[base2cociclos, matriz]; Print[matriz // MatrixForm], {m1, Length[k]}]; \[IndentingNewLine] (*\ \[IndentingNewLine]\ \[IndentingNewLine]Constructing\ a\ basis\ for\ representative\ 2 - cocycles\ coming\ from\ \(\(transgression\)\(.\)\)\ \[IndentingNewLine]\[IndentingNewLine]*) \[IndentingNewLine]Print["\<\ Calculating a system of generators for 2-cocycles coming from \ transgression...\>"]; \[IndentingNewLine]k = Select[Range[Length[homologia]], EvenQ[homologia[\([#1]\)]] &]; Do[col = Select[Range[b1], OddQ[fnsa2[\([2, 2, #1, k[\([m1]\)]]\)]] &]; matriz = {Table[1, {i, orden}]}; Do[matriz = Append[matriz, {1}]; Do[m = F2[\([\((i - 1)\)*orden + j]\)]; m2 = Mod[ Apply[Plus, Table[m[\([col[\([m3]\)]]\)], {m3, Length[col]}]], 2]; matriz[\([i]\)] = Append[matriz[\([i]\)], \((\(-1\))\)^m2], {j, 2, orden}], {i, 2, orden}]; base2cociclos = Append[base2cociclos, matriz]; Print[matriz // MatrixForm], {m1, Length[k]}]; \[IndentingNewLine] (*\[IndentingNewLine]\ \ \[IndentingNewLine]Searching\ for\ Hadamard\ cocyclic\ matrices\ \[IndentingNewLine]\[IndentingNewLine]*) \[IndentingNewLine]If[ method \[Equal] 1, \[IndentingNewLine] (*\[IndentingNewLine]\ \ \[IndentingNewLine]Exhaustive\ search\[IndentingNewLine]\[IndentingNewLine]\ *) \[IndentingNewLine]had = {}; \[IndentingNewLine]Print["\"]; \[IndentingNewLine]Do[ ele = Position[Reverse[IntegerDigits[i, 2]], 1]; \[IndentingNewLine]m = Fold[prodhadamard, matrizdeunos[orden], Extract[base2cociclos, ele]]; \[IndentingNewLine]If[ testhadamard[ m], \[IndentingNewLine]Print["\", Flatten[ele, 1], "\< gives raise to a Hadamard matrix\>"]; (*\(Print[ m // MatrixForm];\)*) \[IndentingNewLine]had = Append[had, m]]\[IndentingNewLine], {i, 2^Length[base2cociclos] - 1}]; \[IndentingNewLine]Print["\", Length[had], "\< Hadamard matrices coming from normalized \ 2-cocycles.\>"], \[IndentingNewLine] (*\[IndentingNewLine]\ \ \[IndentingNewLine]Heuristic\ \(search : \ a\ genetic\ algorithm\)\[IndentingNewLine]\ \[IndentingNewLine]*) \[IndentingNewLine]t = orden/4; \[IndentingNewLine]RandomPermutation[ n_Integer?Positive] := Block[{t}, t = Array[{Random[], #} &, n]; \[IndentingNewLine]t = Sort[t]; Map[#[\([2]\)] &, t]]; \[IndentingNewLine]Print["\"]; \[IndentingNewLine] (*\ La\ poblaci\[OAcute]n\ constar\[AAcute]\ siempre\ de\ 4 t\ individuos, \ que\ se\ reproducir\[AAcute]n\ mediante\ cruces\ simples . \ La\ probabilidad\ de\ mutaci\[OAcute]n\ ser\[AAcute]\ del\ \ 1\ por\ ciento . \ Se\ permite\ la\ existencia\ de\ \(\(gemelos\)\(.\)\)\ \ *) \[IndentingNewLine]adaptacion[p_] := Map[adaptacion1, p]; \[IndentingNewLine]adaptacion1[l_] := Module[{k, n}, k = Position[l, 1]; k = Fold[prodhadamard, matrizdeunos[4*t], Extract[base2cociclos, k]]; n = 0; Do[If[Apply[Plus, k[\([i]\)]] \[Equal] 0, n = n + 1], {i, 4*t}]; n]; \[IndentingNewLine]cruces[p_] := Module[{k, l, n}, n = 2*Floor[Length[p]/2]; l = RandomPermutation[n]; k = {}; Do[k = Join[k, cruces1[p[\([l[\([2*i - 1]\)]]\)], p[\([l[\([2*i]\)]]\)]]], {i, n/2}]; k]; \[IndentingNewLine]cruces1[k_, l_] := Module[{m, n}, n = Random[Integer, {1, Length[base2cociclos] - 1}]; {Join[ Take[k, n], Take[l, \(-\((Length[base2cociclos] - n)\)\)]], Join[Take[k, \(-\((Length[base2cociclos] - n)\)\)], Take[l, n]]}]; \[IndentingNewLine]mutacion[p_] := Module[{n, k}, k = Table[Random[Integer, {1, 100}], {i, Length[p]}]; n = Select[Range[Length[p]], k[\([#1]\)] \[LessEqual] 10 &]; k = {}; Do[k = Append[k, mutacion1[p[\([n[\([i]\)]]\)]]], {i, Length[n]}]; k]; \[IndentingNewLine]mutacion1[l_] := Module[{n, k}, n = Random[Integer, {1, Length[base2cociclos]}]; k = l; ReplacePart[k, 1 - l[\([n]\)], n]]; \[IndentingNewLine]pob = {}; iter = 0; \[IndentingNewLine]Do[ pob = Append[pob, Table[Random[Integer], {j, Length[base2cociclos]}]], {i, 4*t}]; \[IndentingNewLine]mathad = adaptacion[pob]; pos = Flatten[Position[mathad, 4*t - 1], 1]; \[IndentingNewLine]While[Length[pos] \[Equal] 0, iter = iter + 1; Print["\", iter]; descen = mutacion[pob]; pob = Join[pob, descen]; mathad = Join[mathad, adaptacion[descen]]; descen = Union[cruces[pob]]; Print["\"]; mathad = Join[mathad, adaptacion[descen]]; Print["\"]; pob = Join[pob, descen]; ind = 1; pob2 = {}; numero = 0; mathad2 = {}; \[IndentingNewLine]While[numero \[LessEqual] 4*t, natalidad = Flatten[Position[mathad, 4*t - ind], 1]; Print["\", ind - 1, "\< rows to be Hadamard\>"]; config = Union[Table[ pob[\([natalidad[\([i]\)]]\)], {i, Length[natalidad]}]]; pob2 = Join[pob2, config]; mathad2 = Join[mathad2, Table[4*t - ind, {i, Length[config]}]]; numero = numero + Length[config]; Print[Length[config], "\< individuals\>"]; ind = ind + 1]; \[IndentingNewLine]Print["\"]; \[IndentingNewLine]pob = pob2; mathad = mathad2; \[IndentingNewLine]If[ind \[NotEqual] 3, mathad = Take[mathad2, 4*t]; auxiliar = Table[Random[ Integer, {numero - Length[config] + 1, numero + 1 - i}], {i, numero - 4*t}]; Do[pob = Delete[pob, auxiliar[\([i]\)]], {i, Length[auxiliar]}]]; \[IndentingNewLine]Do[ pob = Append[pob, Table[Random[Integer], {j, Length[base2cociclos]}]], {i, t}]; mathad = Join[mathad, adaptacion[Take[pob, \(-t\)]]]; pos = Flatten[Position[mathad, 4*t - 1], 1]]; \[IndentingNewLine]Print["\", iter, "\< generations...\>"]; \[IndentingNewLine]Do[ Print[pob[\([pos[\([i]\)]]\)]], {i, Length[pos]}];\[IndentingNewLine]]];\)\)\)], "Input", InitializationCell->True] }, Open ]], Cell[CellGroupData[{ Cell["End the private context", "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell["End[ ]", "Input", InitializationCell->True], Cell[BoxData[ \("Global`HadamardSearch`Private`"\)], "Output"] }, Open ]] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell["Epilog", "Section", InitializationCell->True], Cell["This section ends the package.", "Text"], Cell[CellGroupData[{ Cell["End the package context", "Subsection", InitializationCell->True], Cell["EndPackage[ ]", "Input", InitializationCell->True] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell["Examples, Tests", "Section"], Cell[TextData[StyleBox["Examples, tests for the use of the package can go \ here.", FontSlant->"Italic"]], "Text"], Cell["\<\ All the calculations about the homological model have been provided \ by the package \"HomologyIteratedGroups\" which has been developed by the \ author as well.\ \>", "Text"], Cell["\<\ Let consider the dihedral group D_4t = Z_2t x_chi Z_2, for the \ dihedral action chi:Z_2 x Z_2t--\[Rule]Z_2t given by chi[1,a]= 2t-a and _a_ \ otherwise. We consider the following ordering in D_4t: {0, \ 0},{0,1},{1,0},{1,1},{2,0},{2,1},...,{2t-1,0},{2t-1,1}. Attending to this \ ordering, a matrix PR representing the group law in D_4t for t=4 is given by \ \ \>", "Text"], Cell[BoxData[ RowBox[{ RowBox[{"PR", "=", TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "2", "3", "4", "5", "6", "7", "8", "9", "10", "11", "12", "13", "14", "15", "16"}, {"2", "1", "16", "15", "14", "13", "12", "11", "10", "9", "8", "7", "6", "5", "4", "3"}, {"3", "4", "5", "6", "7", "8", "9", "10", "11", "12", "13", "14", "15", "16", "1", "2"}, {"4", "3", "2", "1", "16", "15", "14", "13", "12", "11", "10", "9", "8", "7", "6", "5"}, {"5", "6", "7", "8", "9", "10", "11", "12", "13", "14", "15", "16", "1", "2", "3", "4"}, {"6", "5", "4", "3", "2", "1", "16", "15", "14", "13", "12", "11", "10", "9", "8", "7"}, {"7", "8", "9", "10", "11", "12", "13", "14", "15", "16", "1", "2", "3", "4", "5", "6"}, {"8", "7", "6", "5", "4", "3", "2", "1", "16", "15", "14", "13", "12", "11", "10", "9"}, {"9", "10", "11", "12", "13", "14", "15", "16", "1", "2", "3", "4", "5", "6", "7", "8"}, {"10", "9", "8", "7", "6", "5", "4", "3", "2", "1", "16", "15", "14", "13", "12", "11"}, {"11", "12", "13", "14", "15", "16", "1", "2", "3", "4", "5", "6", "7", "8", "9", "10"}, {"12", "11", "10", "9", "8", "7", "6", "5", "4", "3", "2", "1", "16", "15", "14", "13"}, {"13", "14", "15", "16", "1", "2", "3", "4", "5", "6", "7", "8", "9", "10", "11", "12"}, {"14", "13", "12", "11", "10", "9", "8", "7", "6", "5", "4", "3", "2", "1", "16", "15"}, {"15", "16", "1", "2", "3", "4", "5", "6", "7", "8", "9", "10", "11", "12", "13", "14"}, {"16", "15", "14", "13", "12", "11", "10", "9", "8", "7", "6", "5", "4", "3", "2", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]}], ";"}]], "Input"], Cell["\<\ Assume that a basis for hG_1 is {{1,0},{0,1}}, a basis for hG_2 is \ {{2,0},{1,1},{0,2}} and a basis for hG_3 is {{3,0},{2,1},{1,2},{0,3}}. In \ these circumstances, a matrix representing F1 is \ \>", "Text"], Cell[BoxData[ RowBox[{ RowBox[{"F1", "=", RowBox[{"(", "\[NoBreak]", GridBox[{ {"0", "0"}, {"0", "1"}, {"1", "0"}, {"1", "1"}, {"2", "0"}, {"2", "1"}, {"3", "0"}, {"3", "1"}, {"4", "0"}, {"4", "1"}, {"5", "0"}, {"5", "1"}, {"6", "0"}, {"6", "1"}, {"7", "0"}, {"7", "1"} }], "\[NoBreak]", ")"}]}], ";"}]], "Input"], Cell[TextData[Cell[BoxData[ \(\(\(A\)\(\ \)\(matrix\)\(\ \)\(representing\)\(\ \)\(F2\)\(\ \)\(is\)\(\ \ \)\)\)]]], "Text"], Cell[BoxData[ RowBox[{ RowBox[{"F2", "=", RowBox[{"(", "\[NoBreak]", GridBox[{ {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"0", "1", "0"}, {"0", "1", "1"}, {"1", "2", "0"}, {"1", "2", "1"}, {"2", "3", "0"}, {"2", "3", "1"}, {"3", "4", "0"}, {"3", "4", "1"}, {"4", "5", "0"}, {"4", "5", "1"}, {"5", "6", "0"}, {"5", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"1", "2", "0"}, {"1", "2", "1"}, {"2", "3", "0"}, {"2", "3", "1"}, {"3", "4", "0"}, {"3", "4", "1"}, {"4", "5", "0"}, {"4", "5", "1"}, {"5", "6", "0"}, {"5", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"2", "2", "0"}, {"2", "2", "1"}, {"2", "3", "0"}, {"2", "3", "1"}, {"3", "4", "0"}, {"3", "4", "1"}, {"4", "5", "0"}, {"4", "5", "1"}, {"5", "6", "0"}, {"5", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"2", "2", "0"}, {"2", "2", "1"}, {"3", "3", "0"}, {"3", "3", "1"}, {"3", "4", "0"}, {"3", "4", "1"}, {"4", "5", "0"}, {"4", "5", "1"}, {"5", "6", "0"}, {"5", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"2", "2", "0"}, {"2", "2", "1"}, {"3", "3", "0"}, {"3", "3", "1"}, {"4", "4", "0"}, {"4", "4", "1"}, {"4", "5", "0"}, {"4", "5", "1"}, {"5", "6", "0"}, {"5", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"2", "2", "0"}, {"2", "2", "1"}, {"3", "3", "0"}, {"3", "3", "1"}, {"4", "4", "0"}, {"4", "4", "1"}, {"5", "5", "0"}, {"5", "5", "1"}, {"5", "6", "0"}, {"5", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"2", "2", "0"}, {"2", "2", "1"}, {"3", "3", "0"}, {"3", "3", "1"}, {"4", "4", "0"}, {"4", "4", "1"}, {"5", "5", "0"}, {"5", "5", "1"}, {"6", "6", "0"}, {"6", "6", "1"}, {"6", "7", "0"}, {"6", "7", "1"}, {"0", "0", "0"}, {"0", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"1", "0", "0"}, {"0", "0", "0"}, {"0", "0", "1"}, {"1", "1", "0"}, {"1", "1", "1"}, {"2", "2", "0"}, {"2", "2", "1"}, {"3", "3", "0"}, {"3", "3", "1"}, {"4", "4", "0"}, {"4", "4", "1"}, {"5", "5", "0"}, {"5", "5", "1"}, {"6", "6", "0"}, {"6", "6", "1"}, {"7", "7", "0"}, {"7", "7", "1"} }], "\[NoBreak]", ")"}]}], ";"}]], "Input"], Cell[TextData[{ "\n\n", Cell[BoxData[ \(\(\(A\)\(\ \)\(matrix\)\(\ \)\(representing\)\(\ \)\(M2\)\(\ \)\((d2)\ \)\(\ \)\(is\)\(\ \)\)\)]] }], "Text"], Cell[BoxData[ RowBox[{ TagBox[ RowBox[{"M2", "=", RowBox[{"(", "\[NoBreak]", GridBox[{ {"8", "0"}, {\(-6\), "0"}, {"0", "2"} }], "\[NoBreak]", ")"}]}], (MatrixForm[ #]&)], ";"}]], "Input"], Cell["\<\ A matrix representing M3 (d3) is \ \>", "Text"], Cell[BoxData[ RowBox[{ RowBox[{"M3", "=", RowBox[{"(", "\[NoBreak]", GridBox[{ {"0", "0", "0"}, {"6", "8", "0"}, {\(-6\), \(-8\), "0"}, {"0", "0", "0"} }], "\[NoBreak]", ")"}]}], ";"}]], "Input"], Cell["\<\ Now we may proceed to develope an exahustive search (this is only \ feasible for groups of low order, up to order 28).\ \>", "Text"], Cell[CellGroupData[{ Cell[BoxData[ \(\(HadamardSearch[PR, M2, M3, F1, F2, 1];\)\)], "Input"], Cell[BoxData[ \("Calculating a basis for 2-coboundaries..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]2\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 2, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]3\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 3, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]4\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 4, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]5\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 5, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]6\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 6, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]7\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 7, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]8\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 8, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]9\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 9, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]10\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 10, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]11\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 11, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\)}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]12\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 12, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]13\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 13, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\)}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]14\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 14, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ \("Calculating a system of generators for 2-cocycles coming from \ inflation..."\)], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ \("Calculating a system of generators for 2-cocycles coming from \ transgression..."\)], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ \("Searching for cocyclic Hadamard matrices..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 7, 9, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 7, 9, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 8, 9, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 8, 9, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 8, 9, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 8, 9, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 9, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 9, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 7, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 7, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 8, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 8, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 7, 8, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 7, 8, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 7, 8, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 7, 8, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 9, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 9, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 9, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 9, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 9, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 9, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 8, 9, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 8, 9, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 6, 8, 9, 10, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 6, 8, 9, 10, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 7, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 7, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 8, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 8, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 8, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 8, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 8, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 8, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 7, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 7, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 8, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 8, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 8, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 8, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 7, 8, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 7, 8, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 7, 8, 9, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 7, 8, 9, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 8, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 8, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 8, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 8, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 9, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 9, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 7, 9, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 7, 9, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 7, 9, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 7, 9, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 8, 9, 10, 11, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 8, 9, 10, 11, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 7, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 7, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 8, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 8, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 8, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 8, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 7, 8, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 7, 8, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 7, 8, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 7, 8, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 8, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 8, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 9, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 9, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 7, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 7, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 7, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 7, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 8, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 8, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 7, 8, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 7, 8, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 7, 8, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 7, 8, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 9, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 9, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 7, 9, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 7, 9, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 8, 9, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 8, 9, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 8, 9, 10, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 8, 9, 10, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 8, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 8, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 8, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 8, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 8, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 8, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 7, 9, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 7, 9, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 7, 9, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 7, 9, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 7, 8, 9, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 7, 8, 9, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 7, 8, 9, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 7, 8, 9, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 7, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 7, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 8, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 8, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 8, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 8, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 7, 8, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 7, 8, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 8, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 8, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 9, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 9, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 9, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 9, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 7, 9, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 7, 9, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 8, 9, 10, 11, 12, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 8, 9, 10, 11, 12, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 7, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 7, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 7, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 7, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 8, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 8, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 8, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 8, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 8, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 8, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 6, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 6, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 7, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 7, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 7, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 7, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 8, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 8, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 8, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 8, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 7, 8, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 7, 8, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 7, 8, 9, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 7, 8, 9, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 8, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 8, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 6, 8, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 6, 8, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 7, 8, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 7, 8, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 7, 8, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 7, 8, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 7, 9, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 7, 9, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 8, 9, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 8, 9, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 7, 8, 9, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 7, 8, 9, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 7, 8, 9, 10, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 7, 8, 9, 10, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 7, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 7, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 7, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 7, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 7, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 7, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 8, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 8, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 8, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 8, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 7, 8, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 7, 8, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 7, 8, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 7, 8, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 6, 9, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 6, 9, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 8, 9, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 8, 9, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 8, 9, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 8, 9, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 8, 9, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 8, 9, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 7, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 7, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 7, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 7, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 8, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 8, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 7, 8, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 7, 8, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 7, 8, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 7, 8, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 9, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 9, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 9, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 9, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 9, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 9, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 8, 9, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 8, 9, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 7, 8, 9, 10, 11, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 7, 8, 9, 10, 11, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 8, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 8, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 8, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 8, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 7, 8, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 7, 8, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 9, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 9, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 7, 9, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 7, 9, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 7, 9, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 7, 9, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 7, 9, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 7, 9, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 7, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 7, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 8, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 8, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 8, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 8, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 8, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 8, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 8, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 8, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 7, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 7, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 7, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 7, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 8, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 8, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 8, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 8, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 8, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 8, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 7, 8, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 7, 8, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 7, 8, 9, 10, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 7, 8, 9, 10, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 8, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 8, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 7, 8, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 7, 8, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 7, 8, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 7, 8, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 8, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 8, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 8, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 8, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 7, 8, 9, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 7, 8, 9, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 7, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 7, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 8, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 8, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 7, 8, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 7, 8, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 7, 8, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 7, 8, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 7, 9, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 7, 9, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 7, 9, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 7, 9, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 8, 9, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 8, 9, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 9, 10, 11, 12, 13, 14}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 9, 10, 11, 12, 13, 14}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 8, 9, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 8, 9, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 7, 8, 10, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 7, 8, 10, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 11, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 11, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 9, 11, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 9, 11, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 7, 8, 9, 11, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 7, 8, 9, 11, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 10, 11, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 10, 11, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 10, 11, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 10, 11, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 9, 10, 11, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 9, 10, 11, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 9, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 9, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 9, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 9, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 10, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 10, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 7, 8, 10, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 7, 8, 10, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 9, 10, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 9, 10, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 7, 8, 9, 11, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 7, 8, 9, 11, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 7, 8, 10, 11, 12, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 7, 8, 10, 11, 12, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 8, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 8, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 7, 8, 9, 10, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 7, 8, 9, 10, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 11, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 11, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 7, 8, 11, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 7, 8, 11, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 6, 9, 11, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 6, 9, 11, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 10, 11, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 10, 11, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 9, 10, 11, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 9, 10, 11, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 8, 9, 10, 11, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 8, 9, 10, 11, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 8, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 8, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 9, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 9, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 10, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 10, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 9, 10, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 9, 10, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 7, 8, 9, 10, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 7, 8, 9, 10, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 7, 8, 11, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 7, 8, 11, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 9, 10, 11, 12, 13, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 9, 10, 11, 12, 13, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 7, 9, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 7, 9, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 8, 10, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 8, 10, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 10, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 10, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 8, 9, 10, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 8, 9, 10, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 8, 11, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 8, 11, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 7, 9, 11, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 7, 9, 11, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 8, 9, 11, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 8, 9, 11, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 7, 9, 10, 11, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 7, 9, 10, 11, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 7, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 7, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 7, 10, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 7, 10, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 8, 10, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 8, 10, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 8, 9, 10, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 8, 9, 10, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 11, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 11, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 8, 11, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 8, 11, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 11, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 11, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 7, 10, 11, 12, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 7, 10, 11, 12, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 7, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 7, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 10, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 10, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 8, 10, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 8, 10, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 10, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 10, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 7, 11, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 7, 11, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 8, 11, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 8, 11, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 8, 9, 11, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 8, 9, 11, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 7, 10, 11, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 7, 10, 11, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 7, 9, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 7, 9, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 8, 10, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 8, 10, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 7, 9, 10, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 7, 9, 10, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 8, 9, 10, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 8, 9, 10, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 8, 11, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 8, 11, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 11, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 11, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 8, 9, 11, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 8, 9, 11, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 7, 9, 10, 11, 12, 13, 14, 15}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 7, 9, 10, 11, 12, 13, 14, 15}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 6, 7, 8, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 6, 7, 8, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 7, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 7, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 7, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 7, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 7, 8, 9, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 7, 8, 9, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 7, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 7, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 7, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 7, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 8, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 8, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 8, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 8, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 7, 8, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 7, 8, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 6, 7, 8, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 6, 7, 8, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 7, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 7, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 8, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 8, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 8, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 8, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 6, 7, 8, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 6, 7, 8, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 7, 8, 9, 10, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 7, 8, 9, 10, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 7, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 7, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 8, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 8, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 7, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 7, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 7, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 7, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 7, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 7, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 7, 8, 9, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 7, 8, 9, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 7, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 7, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 8, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 8, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 8, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 8, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 8, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 8, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 7, 8, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 7, 8, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 7, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 7, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 7, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 7, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 8, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 8, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 8, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 8, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 7, 8, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 7, 8, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 6, 7, 8, 9, 10, 11, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 6, 7, 8, 9, 10, 11, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 6, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 6, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 7, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 7, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 7, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 7, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 7, 8, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 7, 8, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 8, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 8, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 8, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 8, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 8, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 8, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 7, 8, 9, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 7, 8, 9, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 7, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 7, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 7, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 7, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 8, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 8, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 7, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 7, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 7, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 7, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 7, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 7, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 7, 8, 9, 10, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 7, 8, 9, 10, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 8, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 8, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 8, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 8, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 8, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 8, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 8, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 8, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 8, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 8, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 8, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 8, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 8, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 8, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 6, 7, 8, 9, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 6, 7, 8, 9, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 7, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 7, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 6, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 6, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 7, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 7, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 7, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 7, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 7, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 7, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 8, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 8, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 7, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 7, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 5, 7, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 5, 7, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 7, 8, 9, 10, 11, 12, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 7, 8, 9, 10, 11, 12, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 7, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 7, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 7, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 7, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 7, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 7, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 7, 8, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 7, 8, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 7, 8, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 7, 8, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 8, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 8, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 8, 9, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 8, 9, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 7, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 7, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 6, 8, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 6, 8, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 8, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 8, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 7, 8, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 7, 8, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 8, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 8, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 7, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 7, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 8, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 8, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 8, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 8, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 8, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 8, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 7, 8, 9, 10, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 7, 8, 9, 10, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 7, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 7, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 7, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 7, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 7, 8, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 7, 8, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 5, 6, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 5, 6, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 6, 7, 8, 9, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 6, 7, 8, 9, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 7, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 7, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 6, 8, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 6, 8, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 8, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 8, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 8, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 8, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 6, 7, 8, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 6, 7, 8, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 7, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 7, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 7, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 7, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 7, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 7, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 3, 4, 6, 8, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 3, 4, 6, 8, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 8, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 8, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 6, 7, 8, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 6, 7, 8, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 6, 7, 8, 9, 10, 11, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 6, 7, 8, 9, 10, 11, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 6, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 6, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 7, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 7, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 7, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 7, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 6, 8, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 6, 8, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 8, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 8, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 7, 8, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 7, 8, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 7, 8, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 7, 8, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 7, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 7, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 6, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 6, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 7, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 7, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 5, 6, 7, 8, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 5, 6, 7, 8, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 7, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 7, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 6, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 6, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 7, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 7, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 7, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 7, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 7, 8, 9, 10, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 7, 8, 9, 10, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 7, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 7, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 7, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 7, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 8, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 8, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 6, 8, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 6, 8, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 7, 8, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 7, 8, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 6, 7, 8, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 6, 7, 8, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 5, 6, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 5, 6, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 4, 5, 6, 7, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 4, 5, 6, 7, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 7, 8, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 7, 8, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 6, 7, 8, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 6, 7, 8, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 5, 6, 7, 8, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 5, 6, 7, 8, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 7, 8, 9, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 7, 8, 9, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 7, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 7, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 7, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 7, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{7, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {7, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 7, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 7, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 5, 7, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 5, 7, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 6, 7, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 6, 7, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 7, 8, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 7, 8, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 5, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 5, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 5, 6, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 5, 6, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 6, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 6, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 7, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 7, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{6, 7, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {6, 7, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 6, 7, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 6, 7, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 6, 7, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 6, 7, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 6, 7, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 6, 7, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 5, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 5, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 5, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 5, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 4, 6, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 4, 6, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{5, 6, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {5, 6, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{3, 5, 6, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {3, 5, 6, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 4, 5, 6, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 4, 5, 6, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{4, 7, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {4, 7, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 4, 7, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 4, 7, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 3, 4, 7, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 3, 4, 7, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 3, 4, 7, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 3, 4, 7, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{2, 5, 7, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {2, 5, 7, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("The 2-cocycle generated by the Hadamard product of \ the following generators "\[InvisibleSpace]{1, 2, 5, 7, 8, 9, 10, 11, 12, 13, 14, 16}\[InvisibleSpace]" gives raise to a Hadamard matrix"\), SequenceForm[ "The 2-cocycle generated by the Hadamard product of the following \ generators ", {1, 2, 5, 7, 8, 9, 10, 11, 12, 13, 14, 16}, " gives raise to a Hadamard matrix"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("There are "\[InvisibleSpace]768\[InvisibleSpace]" \ Hadamard matrices coming from normalized 2-cocycles."\), SequenceForm[ "There are ", 768, " Hadamard matrices coming from normalized 2-cocycles."], Editable->False]], "Print"] }, Open ]], Cell["\<\ Now we develope a heuristic search, which will output a few \ (posibly one) cocyclic Hadamard matrices over the group.\ \>", "Text"], Cell[CellGroupData[{ Cell[BoxData[ \(\(HadamardSearch[PR, M2, M3, F1, F2, 2];\)\)], "Input"], Cell[BoxData[ \("Calculating a basis for 2-coboundaries..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]2\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 2, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]3\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 3, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]4\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 4, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]5\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 5, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]6\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 6, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]7\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 7, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]8\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 8, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]9\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 9, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\)}, {"1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]10\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 10, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]11\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 11, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\)}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]12\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 12, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]13\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 13, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1"}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\)}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\), \(-1\)}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ InterpretationBox[\("The "\[InvisibleSpace]14\[InvisibleSpace]"-ith \ 2-coboundary is a generator:"\), SequenceForm[ "The ", 14, "-ith 2-coboundary is a generator:"], Editable->False]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1", "1"}, {"1", "1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), "1"}, {"1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"}, { "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", \(-1\)}, {"1", "1", \(-1\), "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ \("Calculating a system of generators for 2-cocycles coming from \ inflation..."\)], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\), "1", \(-1\)} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\), "1", "1", \(-1\), \(-1\)} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ \("Calculating a system of generators for 2-cocycles coming from \ transgression..."\)], "Print"], Cell[BoxData[ TagBox[ RowBox[{"(", "\[NoBreak]", GridBox[{ {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"}, {"1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\)}, {"1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", \(-1\), \(-1\)}, {"1", "1", \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \ \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\), \(-1\)}, {"1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1", "1"} }], "\[NoBreak]", ")"}], (MatrixForm[ #]&)]], "Print"], Cell[BoxData[ \("Generating the initial population..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("Searching in the generation "\[InvisibleSpace]1\), SequenceForm[ "Searching in the generation ", 1], Editable->False]], "Print"], Cell[BoxData[ \("Crossover and mutation finished..."\)], "Print"], Cell[BoxData[ \("Evaluation of fitness finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]0\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 0, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(0\[InvisibleSpace]" individuals"\), SequenceForm[ 0, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]1\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 1, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]2\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 2, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(4\[InvisibleSpace]" individuals"\), SequenceForm[ 4, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]3\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 3, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]4\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 4, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(4\[InvisibleSpace]" individuals"\), SequenceForm[ 4, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]5\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 5, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(4\[InvisibleSpace]" individuals"\), SequenceForm[ 4, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]6\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 6, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]7\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 7, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(6\[InvisibleSpace]" individuals"\), SequenceForm[ 6, " individuals"], Editable->False]], "Print"], Cell[BoxData[ \("Natural selection finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("Searching in the generation "\[InvisibleSpace]2\), SequenceForm[ "Searching in the generation ", 2], Editable->False]], "Print"], Cell[BoxData[ \("Crossover and mutation finished..."\)], "Print"], Cell[BoxData[ \("Evaluation of fitness finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]0\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 0, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(0\[InvisibleSpace]" individuals"\), SequenceForm[ 0, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]1\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 1, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]2\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 2, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(7\[InvisibleSpace]" individuals"\), SequenceForm[ 7, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]3\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 3, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(3\[InvisibleSpace]" individuals"\), SequenceForm[ 3, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]4\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 4, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(6\[InvisibleSpace]" individuals"\), SequenceForm[ 6, " individuals"], Editable->False]], "Print"], Cell[BoxData[ \("Natural selection finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("Searching in the generation "\[InvisibleSpace]3\), SequenceForm[ "Searching in the generation ", 3], Editable->False]], "Print"], Cell[BoxData[ \("Crossover and mutation finished..."\)], "Print"], Cell[BoxData[ \("Evaluation of fitness finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]0\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 0, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(0\[InvisibleSpace]" individuals"\), SequenceForm[ 0, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]1\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 1, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]2\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 2, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(9\[InvisibleSpace]" individuals"\), SequenceForm[ 9, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]3\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 3, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(5\[InvisibleSpace]" individuals"\), SequenceForm[ 5, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]4\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 4, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(7\[InvisibleSpace]" individuals"\), SequenceForm[ 7, " individuals"], Editable->False]], "Print"], Cell[BoxData[ \("Natural selection finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("Searching in the generation "\[InvisibleSpace]4\), SequenceForm[ "Searching in the generation ", 4], Editable->False]], "Print"], Cell[BoxData[ \("Crossover and mutation finished..."\)], "Print"], Cell[BoxData[ \("Evaluation of fitness finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]0\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 0, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(0\[InvisibleSpace]" individuals"\), SequenceForm[ 0, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]1\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 1, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]2\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 2, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(11\[InvisibleSpace]" individuals"\), SequenceForm[ 11, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]3\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 3, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(5\[InvisibleSpace]" individuals"\), SequenceForm[ 5, " individuals"], Editable->False]], "Print"], Cell[BoxData[ \("Natural selection finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("Searching in the generation "\[InvisibleSpace]5\), SequenceForm[ "Searching in the generation ", 5], Editable->False]], "Print"], Cell[BoxData[ \("Crossover and mutation finished..."\)], "Print"], Cell[BoxData[ \("Evaluation of fitness finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]0\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 0, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(2\[InvisibleSpace]" individuals"\), SequenceForm[ 2, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]1\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 1, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(1\[InvisibleSpace]" individuals"\), SequenceForm[ 1, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]2\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 2, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(12\[InvisibleSpace]" individuals"\), SequenceForm[ 12, " individuals"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\("With a lack of "\[InvisibleSpace]3\[InvisibleSpace]" \ rows to be Hadamard"\), SequenceForm[ "With a lack of ", 3, " rows to be Hadamard"], Editable->False]], "Print"], Cell[BoxData[ InterpretationBox[\(5\[InvisibleSpace]" individuals"\), SequenceForm[ 5, " individuals"], Editable->False]], "Print"], Cell[BoxData[ \("Natural selection finished..."\)], "Print"], Cell[BoxData[ InterpretationBox[\("We have found the following Hadamard matrices in "\ \[InvisibleSpace]5\[InvisibleSpace]" generations..."\), SequenceForm[ "We have found the following Hadamard matrices in ", 5, " generations..."], Editable->False]], "Print"], Cell[BoxData[ \({1, 0, 0, 1, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 0, 1}\)], "Print"], Cell[BoxData[ \({1, 1, 0, 0, 0, 0, 1, 0, 0, 1, 0, 1, 0, 1, 0, 1}\)], "Print"] }, Open ]] }, Open ]] }, Open ]] }, FrontEndVersion->"4.0 for Microsoft Windows", ScreenRectangle->{{0, 1280}, {0, 727}}, AutoGeneratedPackage->Automatic, WindowToolbars->"EditBar", WindowSize->{1272, 700}, WindowMargins->{{0, Automatic}, {Automatic, 0}}, PrintingCopies->1, PrintingPageRange->{1, Automatic}, ShowSelection->True ] (*********************************************************************** Cached data follows. If you edit this Notebook file directly, not using Mathematica, you must remove the line containing CacheID at the top of the file. The cache data will then be recreated when you save this file from within Mathematica. ***********************************************************************) (*CellTagsOutline CellTagsIndex->{} *) (*CellTagsIndex CellTagsIndex->{} *) (*NotebookFileOutline Notebook[{ Cell[CellGroupData[{ Cell[1739, 51, 65, 1, 105, "Title"], Cell[1807, 54, 213, 5, 122, "Subtitle"], Cell[2023, 61, 37, 0, 53, "Subsubtitle"], Cell[2063, 63, 1161, 22, 90, "Text"], Cell[CellGroupData[{ Cell[3249, 89, 28, 0, 53, "Section"], Cell[CellGroupData[{ Cell[3302, 93, 30, 0, 43, "Subsubsection"], Cell[3335, 95, 74, 1, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[3446, 101, 31, 0, 43, "Subsubsection"], Cell[3480, 103, 125, 3, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[3642, 111, 32, 0, 43, "Subsubsection"], Cell[3677, 113, 164, 4, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[3878, 122, 34, 0, 43, "Subsubsection"], Cell[3915, 124, 143, 3, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[4095, 132, 41, 0, 43, "Subsubsection"], Cell[4139, 134, 19, 0, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[4195, 139, 101, 4, 43, "Subsubsection"], Cell[4299, 145, 19, 0, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[4355, 150, 32, 0, 43, "Subsubsection"], Cell[4390, 152, 448, 7, 52, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[4875, 164, 33, 0, 43, "Subsubsection"], Cell[4911, 166, 117, 3, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[5065, 174, 35, 0, 43, "Subsubsection"], Cell[5103, 176, 146, 2, 33, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[5286, 183, 35, 0, 43, "Subsubsection"], Cell[5324, 185, 689, 9, 109, "Text"] }, Open ]], Cell[CellGroupData[{ Cell[6050, 199, 37, 0, 43, "Subsubsection"], Cell[6090, 201, 208, 6, 54, "Text"] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell[6347, 213, 56, 1, 53, "Section", InitializationCell->True], Cell[6406, 216, 125, 4, 33, "Text", InitializationCell->True], Cell[CellGroupData[{ Cell[6556, 224, 102, 1, 47, "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell[6683, 229, 79, 1, 30, "Input", InitializationCell->True], Cell[6765, 232, 58, 1, 29, "Output"] }, Open ]], Cell[CellGroupData[{ Cell[6860, 238, 45, 1, 30, "Input"], Cell[6908, 241, 71, 1, 29, "Output"] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell[7028, 248, 124, 4, 47, "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell[7177, 256, 1252, 19, 156, "Input", InitializationCell->True], Cell[8432, 277, 1209, 17, 162, "Output"] }, Open ]] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell[9702, 301, 61, 1, 53, "Section", InitializationCell->True], Cell[9766, 304, 131, 3, 33, "Text"], Cell[CellGroupData[{ Cell[9922, 311, 97, 1, 47, "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell[10044, 316, 97, 4, 48, "Input", InitializationCell->True], Cell[10144, 322, 66, 1, 29, "Output"], Cell[10213, 325, 116, 2, 29, "Output"] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell[10378, 333, 122, 4, 47, "Subsection", InitializationCell->True], Cell[10503, 339, 3685, 67, 630, "Input", InitializationCell->True], Cell[14191, 408, 1012, 20, 190, "Input", InitializationCell->True], Cell[15206, 430, 343, 6, 110, "Input", InitializationCell->True], Cell[15552, 438, 338, 6, 90, "Input", InitializationCell->True] }, Open ]], Cell[CellGroupData[{ Cell[15927, 449, 62, 1, 47, "Subsection", InitializationCell->True], Cell[15992, 452, 12529, 223, 2510, "Input", InitializationCell->True] }, Open ]], Cell[CellGroupData[{ Cell[28558, 680, 73, 1, 47, "Subsection", InitializationCell->True], Cell[CellGroupData[{ Cell[28656, 685, 51, 1, 30, "Input", InitializationCell->True], Cell[28710, 688, 66, 1, 29, "Output"] }, Open ]] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell[28837, 696, 53, 1, 53, "Section", InitializationCell->True], Cell[28893, 699, 46, 0, 33, "Text"], Cell[CellGroupData[{ Cell[28964, 703, 73, 1, 47, "Subsection", InitializationCell->True], Cell[29040, 706, 58, 1, 30, "Input", InitializationCell->True] }, Open ]] }, Open ]], Cell[CellGroupData[{ Cell[29147, 713, 34, 0, 53, "Section"], Cell[29184, 715, 116, 2, 33, "Text"], Cell[29303, 719, 185, 4, 33, "Text"], Cell[29491, 725, 389, 7, 52, "Text"], Cell[29883, 734, 2188, 38, 265, "Input"], Cell[32074, 774, 220, 6, 71, "Text"], Cell[32297, 782, 570, 20, 265, "Input"], Cell[32870, 804, 127, 2, 29, "Text"], Cell[33000, 808, 8090, 260, 4105, "Input"], Cell[41093, 1070, 159, 5, 67, "Text"], Cell[41255, 1077, 289, 9, 57, "Input"], Cell[41547, 1088, 57, 2, 33, "Text"], Cell[41607, 1092, 284, 8, 73, "Input"], Cell[41894, 1102, 142, 3, 33, "Text"], Cell[CellGroupData[{ Cell[42061, 1109, 75, 1, 30, "Input"], Cell[42139, 1112, 76, 1, 25, "Print"], Cell[42218, 1115, 222, 4, 25, "Print"], Cell[42443, 1121, 2012, 37, 261, "Print"], Cell[44458, 1160, 222, 4, 25, "Print"], Cell[44683, 1166, 2012, 37, 261, "Print"], Cell[46698, 1205, 222, 4, 25, "Print"], Cell[46923, 1211, 2012, 37, 261, "Print"], Cell[48938, 1250, 222, 4, 25, "Print"], Cell[49163, 1256, 2012, 37, 261, "Print"], Cell[51178, 1295, 222, 4, 25, "Print"], Cell[51403, 1301, 2012, 37, 261, "Print"], Cell[53418, 1340, 222, 4, 25, "Print"], Cell[53643, 1346, 2012, 37, 261, "Print"], Cell[55658, 1385, 222, 4, 25, "Print"], Cell[55883, 1391, 2012, 37, 261, "Print"], Cell[57898, 1430, 222, 4, 25, "Print"], Cell[58123, 1436, 2010, 36, 261, "Print"], Cell[60136, 1474, 224, 4, 25, "Print"], Cell[60363, 1480, 2012, 37, 261, "Print"], Cell[62378, 1519, 224, 4, 25, "Print"], Cell[62605, 1525, 2012, 37, 261, "Print"], Cell[64620, 1564, 224, 4, 25, "Print"], Cell[64847, 1570, 2012, 37, 261, "Print"], Cell[66862, 1609, 224, 4, 25, "Print"], Cell[67089, 1615, 2012, 37, 261, "Print"], Cell[69104, 1654, 224, 4, 25, "Print"], Cell[69331, 1660, 2012, 37, 261, "Print"], Cell[71346, 1699, 111, 2, 25, "Print"], Cell[71460, 1703, 2076, 36, 261, "Print"], Cell[73539, 1741, 2076, 36, 261, "Print"], Cell[75618, 1779, 115, 2, 25, "Print"], Cell[75736, 1783, 2236, 44, 261, "Print"], Cell[77975, 1829, 78, 1, 25, "Print"], Cell[78056, 1832, 428, 7, 25, "Print"], Cell[78487, 1841, 428, 7, 25, "Print"], Cell[78918, 1850, 428, 7, 25, "Print"], Cell[79349, 1859, 428, 7, 25, "Print"], Cell[79780, 1868, 430, 7, 25, "Print"], Cell[80213, 1877, 430, 7, 25, "Print"], Cell[80646, 1886, 430, 7, 25, "Print"], Cell[81079, 1895, 430, 7, 25, "Print"], Cell[81512, 1904, 430, 7, 25, "Print"], Cell[81945, 1913, 430, 7, 25, "Print"], Cell[82378, 1922, 430, 7, 25, "Print"], Cell[82811, 1931, 430, 7, 25, "Print"], Cell[83244, 1940, 430, 7, 25, "Print"], Cell[83677, 1949, 430, 7, 25, "Print"], Cell[84110, 1958, 430, 7, 25, "Print"], Cell[84543, 1967, 430, 7, 25, "Print"], Cell[84976, 1976, 430, 7, 25, "Print"], Cell[85409, 1985, 430, 7, 25, "Print"], Cell[85842, 1994, 430, 7, 25, "Print"], Cell[86275, 2003, 430, 7, 25, "Print"], Cell[86708, 2012, 430, 7, 25, "Print"], Cell[87141, 2021, 430, 7, 25, "Print"], Cell[87574, 2030, 430, 7, 25, "Print"], Cell[88007, 2039, 430, 7, 25, "Print"], Cell[88440, 2048, 430, 7, 25, "Print"], Cell[88873, 2057, 430, 7, 25, "Print"], Cell[89306, 2066, 430, 7, 25, "Print"], Cell[89739, 2075, 430, 7, 25, "Print"], Cell[90172, 2084, 432, 7, 25, "Print"], Cell[90607, 2093, 432, 7, 25, "Print"], Cell[91042, 2102, 432, 7, 25, "Print"], Cell[91477, 2111, 432, 7, 25, "Print"], Cell[91912, 2120, 432, 7, 25, "Print"], Cell[92347, 2129, 432, 7, 25, "Print"], Cell[92782, 2138, 432, 7, 25, "Print"], Cell[93217, 2147, 432, 7, 25, "Print"], Cell[93652, 2156, 432, 7, 25, "Print"], Cell[94087, 2165, 432, 7, 25, "Print"], Cell[94522, 2174, 432, 7, 25, "Print"], Cell[94957, 2183, 432, 7, 25, "Print"], Cell[95392, 2192, 430, 7, 25, "Print"], Cell[95825, 2201, 430, 7, 25, "Print"], Cell[96258, 2210, 430, 7, 25, "Print"], Cell[96691, 2219, 430, 7, 25, "Print"], Cell[97124, 2228, 430, 7, 25, "Print"], Cell[97557, 2237, 430, 7, 25, "Print"], Cell[97990, 2246, 430, 7, 25, "Print"], Cell[98423, 2255, 430, 7, 25, "Print"], Cell[98856, 2264, 430, 7, 25, "Print"], Cell[99289, 2273, 430, 7, 25, "Print"], Cell[99722, 2282, 430, 7, 25, "Print"], Cell[100155, 2291, 430, 7, 25, "Print"], Cell[100588, 2300, 430, 7, 25, "Print"], Cell[101021, 2309, 430, 7, 25, "Print"], Cell[101454, 2318, 432, 7, 25, "Print"], Cell[101889, 2327, 432, 7, 25, "Print"], Cell[102324, 2336, 432, 7, 25, "Print"], Cell[102759, 2345, 432, 7, 25, "Print"], Cell[103194, 2354, 432, 7, 25, "Print"], Cell[103629, 2363, 432, 7, 25, "Print"], Cell[104064, 2372, 432, 7, 25, "Print"], Cell[104499, 2381, 432, 7, 25, "Print"], Cell[104934, 2390, 432, 7, 25, "Print"], Cell[105369, 2399, 432, 7, 25, "Print"], Cell[105804, 2408, 432, 7, 25, "Print"], Cell[106239, 2417, 432, 7, 25, "Print"], Cell[106674, 2426, 432, 7, 25, "Print"], Cell[107109, 2435, 432, 7, 25, "Print"], Cell[107544, 2444, 432, 7, 25, "Print"], Cell[107979, 2453, 432, 7, 25, "Print"], Cell[108414, 2462, 432, 7, 25, "Print"], Cell[108849, 2471, 432, 7, 25, "Print"], Cell[109284, 2480, 432, 7, 25, "Print"], Cell[109719, 2489, 432, 7, 25, "Print"], Cell[110154, 2498, 432, 7, 25, "Print"], Cell[110589, 2507, 432, 7, 25, "Print"], Cell[111024, 2516, 432, 7, 25, "Print"], Cell[111459, 2525, 465, 8, 25, "Print"], Cell[111927, 2535, 441, 8, 25, "Print"], Cell[112371, 2545, 441, 8, 25, "Print"], Cell[112815, 2555, 441, 8, 25, "Print"], Cell[113259, 2565, 441, 8, 25, "Print"], Cell[113703, 2575, 441, 8, 25, "Print"], Cell[114147, 2585, 467, 8, 25, "Print"], Cell[114617, 2595, 441, 8, 25, "Print"], Cell[115061, 2605, 441, 8, 25, "Print"], Cell[115505, 2615, 467, 8, 25, "Print"], Cell[115975, 2625, 467, 8, 25, "Print"], Cell[116445, 2635, 430, 7, 25, "Print"], Cell[116878, 2644, 430, 7, 25, "Print"], Cell[117311, 2653, 430, 7, 25, "Print"], Cell[117744, 2662, 430, 7, 25, "Print"], Cell[118177, 2671, 430, 7, 25, "Print"], Cell[118610, 2680, 430, 7, 25, "Print"], Cell[119043, 2689, 430, 7, 25, "Print"], Cell[119476, 2698, 430, 7, 25, "Print"], Cell[119909, 2707, 430, 7, 25, "Print"], Cell[120342, 2716, 430, 7, 25, "Print"], Cell[120775, 2725, 430, 7, 25, "Print"], Cell[121208, 2734, 430, 7, 25, "Print"], Cell[121641, 2743, 430, 7, 25, "Print"], Cell[122074, 2752, 430, 7, 25, "Print"], Cell[122507, 2761, 430, 7, 25, "Print"], Cell[122940, 2770, 430, 7, 25, "Print"], Cell[123373, 2779, 432, 7, 25, "Print"], Cell[123808, 2788, 432, 7, 25, "Print"], Cell[124243, 2797, 432, 7, 25, "Print"], Cell[124678, 2806, 432, 7, 25, "Print"], Cell[125113, 2815, 432, 7, 25, "Print"], Cell[125548, 2824, 432, 7, 25, "Print"], Cell[125983, 2833, 432, 7, 25, "Print"], Cell[126418, 2842, 432, 7, 25, "Print"], Cell[126853, 2851, 432, 7, 25, "Print"], Cell[127288, 2860, 432, 7, 25, "Print"], Cell[127723, 2869, 432, 7, 25, "Print"], Cell[128158, 2878, 432, 7, 25, "Print"], Cell[128593, 2887, 432, 7, 25, "Print"], Cell[129028, 2896, 465, 8, 25, "Print"], Cell[129496, 2906, 432, 7, 25, "Print"], Cell[129931, 2915, 432, 7, 25, "Print"], Cell[130366, 2924, 432, 7, 25, "Print"], Cell[130801, 2933, 432, 7, 25, "Print"], Cell[131236, 2942, 432, 7, 25, "Print"], Cell[131671, 2951, 432, 7, 25, "Print"], Cell[132106, 2960, 432, 7, 25, "Print"], Cell[132541, 2969, 432, 7, 25, "Print"], Cell[132976, 2978, 432, 7, 25, "Print"], Cell[133411, 2987, 432, 7, 25, "Print"], Cell[133846, 2996, 432, 7, 25, "Print"], Cell[134281, 3005, 432, 7, 25, "Print"], Cell[134716, 3014, 432, 7, 25, "Print"], Cell[135151, 3023, 432, 7, 25, "Print"], Cell[135586, 3032, 441, 8, 25, "Print"], Cell[136030, 3042, 441, 8, 25, "Print"], Cell[136474, 3052, 467, 8, 25, "Print"], Cell[136944, 3062, 441, 8, 25, "Print"], Cell[137388, 3072, 441, 8, 25, "Print"], Cell[137832, 3082, 467, 8, 25, "Print"], Cell[138302, 3092, 441, 8, 25, "Print"], Cell[138746, 3102, 441, 8, 25, "Print"], Cell[139190, 3112, 441, 8, 25, "Print"], Cell[139634, 3122, 467, 8, 25, "Print"], Cell[140104, 3132, 467, 8, 25, "Print"], Cell[140574, 3142, 467, 8, 25, "Print"], Cell[141044, 3152, 432, 7, 25, "Print"], Cell[141479, 3161, 432, 7, 25, "Print"], Cell[141914, 3170, 432, 7, 25, "Print"], Cell[142349, 3179, 432, 7, 25, "Print"], Cell[142784, 3188, 432, 7, 25, "Print"], Cell[143219, 3197, 432, 7, 25, "Print"], Cell[143654, 3206, 432, 7, 25, "Print"], Cell[144089, 3215, 432, 7, 25, "Print"], Cell[144524, 3224, 432, 7, 25, "Print"], Cell[144959, 3233, 465, 8, 25, "Print"], Cell[145427, 3243, 441, 8, 25, "Print"], Cell[145871, 3253, 441, 8, 25, "Print"], Cell[146315, 3263, 441, 8, 25, "Print"], Cell[146759, 3273, 441, 8, 25, "Print"], Cell[147203, 3283, 441, 8, 25, "Print"], Cell[147647, 3293, 467, 8, 25, "Print"], Cell[148117, 3303, 441, 8, 25, "Print"], Cell[148561, 3313, 441, 8, 25, "Print"], Cell[149005, 3323, 441, 8, 25, "Print"], Cell[149449, 3333, 441, 8, 25, "Print"], Cell[149893, 3343, 467, 8, 25, "Print"], Cell[150363, 3353, 441, 8, 25, "Print"], Cell[150807, 3363, 467, 8, 25, "Print"], Cell[151277, 3373, 467, 8, 25, "Print"], Cell[151747, 3383, 467, 8, 25, "Print"], Cell[152217, 3393, 467, 8, 25, "Print"], Cell[152687, 3403, 441, 8, 25, "Print"], Cell[153131, 3413, 441, 8, 25, "Print"], Cell[153575, 3423, 441, 8, 25, "Print"], Cell[154019, 3433, 467, 8, 25, "Print"], Cell[154489, 3443, 441, 8, 25, "Print"], Cell[154933, 3453, 441, 8, 25, "Print"], Cell[155377, 3463, 441, 8, 25, "Print"], Cell[155821, 3473, 441, 8, 25, "Print"], Cell[156265, 3483, 467, 8, 25, "Print"], Cell[156735, 3493, 441, 8, 25, "Print"], Cell[157179, 3503, 467, 8, 25, "Print"], Cell[157649, 3513, 467, 8, 25, "Print"], Cell[158119, 3523, 445, 8, 25, "Print"], Cell[158567, 3533, 445, 8, 25, "Print"], Cell[159015, 3543, 445, 8, 25, "Print"], Cell[159463, 3553, 469, 8, 25, "Print"], Cell[159935, 3563, 469, 8, 25, "Print"], Cell[160407, 3573, 469, 8, 25, "Print"], Cell[160879, 3583, 469, 8, 25, "Print"], Cell[161351, 3593, 469, 8, 25, "Print"], Cell[161823, 3603, 469, 8, 25, "Print"], Cell[162295, 3613, 469, 8, 25, "Print"], Cell[162767, 3623, 428, 7, 25, "Print"], Cell[163198, 3632, 430, 7, 25, "Print"], Cell[163631, 3641, 430, 7, 25, "Print"], Cell[164064, 3650, 430, 7, 25, "Print"], Cell[164497, 3659, 430, 7, 25, "Print"], Cell[164930, 3668, 432, 7, 25, "Print"], Cell[165365, 3677, 432, 7, 25, "Print"], Cell[165800, 3686, 432, 7, 25, "Print"], Cell[166235, 3695, 430, 7, 25, "Print"], Cell[166668, 3704, 430, 7, 25, "Print"], Cell[167101, 3713, 430, 7, 25, "Print"], Cell[167534, 3722, 432, 7, 25, "Print"], Cell[167969, 3731, 432, 7, 25, "Print"], Cell[168404, 3740, 432, 7, 25, "Print"], Cell[168839, 3749, 432, 7, 25, "Print"], Cell[169274, 3758, 441, 8, 25, "Print"], Cell[169718, 3768, 430, 7, 25, "Print"], Cell[170151, 3777, 465, 8, 25, "Print"], Cell[170619, 3787, 432, 7, 25, "Print"], Cell[171054, 3796, 432, 7, 25, "Print"], Cell[171489, 3805, 432, 7, 25, "Print"], Cell[171924, 3814, 441, 8, 25, "Print"], Cell[172368, 3824, 441, 8, 25, "Print"], Cell[172812, 3834, 467, 8, 25, "Print"], Cell[173282, 3844, 432, 7, 25, "Print"], Cell[173717, 3853, 432, 7, 25, "Print"], Cell[174152, 3862, 432, 7, 25, "Print"], Cell[174587, 3871, 441, 8, 25, "Print"], Cell[175031, 3881, 441, 8, 25, "Print"], Cell[175475, 3891, 467, 8, 25, "Print"], Cell[175945, 3901, 441, 8, 25, "Print"], Cell[176389, 3911, 469, 8, 25, "Print"], Cell[176861, 3921, 445, 8, 25, "Print"], Cell[177309, 3931, 447, 8, 25, "Print"], Cell[177759, 3941, 447, 8, 25, "Print"], Cell[178209, 3951, 447, 8, 25, "Print"], Cell[178659, 3961, 447, 8, 25, "Print"], Cell[179109, 3971, 447, 8, 25, "Print"], Cell[179559, 3981, 447, 8, 25, "Print"], Cell[180009, 3991, 449, 8, 25, "Print"], Cell[180461, 4001, 447, 8, 25, "Print"], Cell[180911, 4011, 449, 8, 25, "Print"], Cell[181363, 4021, 449, 8, 25, "Print"], Cell[181815, 4031, 449, 8, 25, "Print"], Cell[182267, 4041, 449, 8, 25, "Print"], Cell[182719, 4051, 449, 8, 25, "Print"], Cell[183171, 4061, 449, 8, 25, "Print"], Cell[183623, 4071, 451, 8, 25, "Print"], Cell[184077, 4081, 447, 8, 25, "Print"], Cell[184527, 4091, 449, 8, 25, "Print"], Cell[184979, 4101, 449, 8, 25, "Print"], Cell[185431, 4111, 449, 8, 25, "Print"], Cell[185883, 4121, 449, 8, 25, "Print"], Cell[186335, 4131, 449, 8, 25, "Print"], Cell[186787, 4141, 449, 8, 25, "Print"], Cell[187239, 4151, 451, 8, 25, "Print"], Cell[187693, 4161, 473, 8, 25, "Print"], Cell[188169, 4171, 451, 8, 25, "Print"], Cell[188623, 4181, 475, 8, 25, "Print"], Cell[189101, 4191, 451, 8, 25, "Print"], Cell[189555, 4201, 451, 8, 25, "Print"], Cell[190009, 4211, 475, 8, 25, "Print"], Cell[190487, 4221, 451, 8, 25, "Print"], Cell[190941, 4231, 477, 8, 25, "Print"], Cell[191421, 4241, 418, 7, 25, "Print"], Cell[191842, 4250, 424, 7, 25, "Print"], Cell[192269, 4259, 424, 7, 25, "Print"], Cell[192696, 4268, 430, 7, 25, "Print"], Cell[193129, 4277, 418, 7, 25, "Print"], Cell[193550, 4286, 424, 7, 25, "Print"], Cell[193977, 4295, 424, 7, 25, "Print"], Cell[194404, 4304, 430, 7, 25, "Print"], Cell[194837, 4313, 430, 7, 25, "Print"], Cell[195270, 4322, 445, 8, 25, "Print"], Cell[195718, 4332, 430, 7, 25, "Print"], Cell[196151, 4341, 445, 8, 25, "Print"], Cell[196599, 4351, 418, 7, 25, "Print"], Cell[197020, 4360, 424, 7, 25, "Print"], Cell[197447, 4369, 418, 7, 25, "Print"], Cell[197868, 4378, 430, 7, 25, "Print"], Cell[198301, 4387, 424, 7, 25, "Print"], Cell[198728, 4396, 445, 8, 25, "Print"], Cell[199176, 4406, 424, 7, 25, "Print"], Cell[199603, 4415, 430, 7, 25, "Print"], Cell[200036, 4424, 418, 7, 25, "Print"], Cell[200457, 4433, 424, 7, 25, "Print"], Cell[200884, 4442, 418, 7, 25, "Print"], Cell[201305, 4451, 424, 7, 25, "Print"], Cell[201732, 4460, 430, 7, 25, "Print"], Cell[202165, 4469, 430, 7, 25, "Print"], Cell[202598, 4478, 424, 7, 25, "Print"], Cell[203025, 4487, 445, 8, 25, "Print"], Cell[203473, 4497, 445, 8, 25, "Print"], Cell[203921, 4507, 451, 8, 25, "Print"], Cell[204375, 4517, 445, 8, 25, "Print"], Cell[204823, 4527, 445, 8, 25, "Print"], Cell[205271, 4537, 445, 8, 25, "Print"], Cell[205719, 4547, 451, 8, 25, "Print"], Cell[206173, 4557, 451, 8, 25, "Print"], Cell[206627, 4567, 451, 8, 25, "Print"], Cell[207081, 4577, 420, 7, 25, "Print"], Cell[207504, 4586, 426, 7, 25, "Print"], Cell[207933, 4595, 420, 7, 25, "Print"], Cell[208356, 4604, 432, 7, 25, "Print"], Cell[208791, 4613, 426, 7, 25, "Print"], Cell[209220, 4622, 432, 7, 25, "Print"], Cell[209655, 4631, 432, 7, 25, "Print"], Cell[210090, 4640, 453, 8, 25, "Print"], Cell[210546, 4650, 432, 7, 25, "Print"], Cell[210981, 4659, 447, 8, 25, "Print"], Cell[211431, 4669, 447, 8, 25, "Print"], Cell[211881, 4679, 453, 8, 25, "Print"], Cell[212337, 4689, 420, 7, 25, "Print"], Cell[212760, 4698, 426, 7, 25, "Print"], Cell[213189, 4707, 420, 7, 25, "Print"], Cell[213612, 4716, 432, 7, 25, "Print"], Cell[214047, 4725, 432, 7, 25, "Print"], Cell[214482, 4734, 447, 8, 25, "Print"], Cell[214932, 4744, 426, 7, 25, "Print"], Cell[215361, 4753, 447, 8, 25, "Print"], Cell[215811, 4763, 447, 8, 25, "Print"], Cell[216261, 4773, 447, 8, 25, "Print"], Cell[216711, 4783, 459, 8, 25, "Print"], Cell[217173, 4793, 459, 8, 25, "Print"], Cell[217635, 4803, 453, 8, 25, "Print"], Cell[218091, 4813, 453, 8, 25, "Print"], Cell[218547, 4823, 459, 8, 25, "Print"], Cell[219009, 4833, 459, 8, 25, "Print"], Cell[219471, 4843, 420, 7, 25, "Print"], Cell[219894, 4852, 432, 7, 25, "Print"], Cell[220329, 4861, 426, 7, 25, "Print"], Cell[220758, 4870, 447, 8, 25, "Print"], Cell[221208, 4880, 420, 7, 25, "Print"], Cell[221631, 4889, 426, 7, 25, "Print"], Cell[222060, 4898, 426, 7, 25, "Print"], Cell[222489, 4907, 432, 7, 25, "Print"], Cell[222924, 4916, 432, 7, 25, "Print"], Cell[223359, 4925, 432, 7, 25, "Print"], Cell[223794, 4934, 453, 8, 25, "Print"], Cell[224250, 4944, 453, 8, 25, "Print"], Cell[224706, 4954, 426, 7, 25, "Print"], Cell[225135, 4963, 420, 7, 25, "Print"], Cell[225558, 4972, 432, 7, 25, "Print"], Cell[225993, 4981, 420, 7, 25, "Print"], Cell[226416, 4990, 432, 7, 25, "Print"], Cell[226851, 4999, 447, 8, 25, "Print"], Cell[227301, 5009, 426, 7, 25, "Print"], Cell[227730, 5018, 447, 8, 25, "Print"], Cell[228180, 5028, 426, 7, 25, "Print"], Cell[228609, 5037, 447, 8, 25, "Print"], Cell[229059, 5047, 453, 8, 25, "Print"], Cell[229515, 5057, 453, 8, 25, "Print"], Cell[229971, 5067, 432, 7, 25, "Print"], Cell[230406, 5076, 432, 7, 25, "Print"], Cell[230841, 5085, 459, 8, 25, "Print"], Cell[231303, 5095, 459, 8, 25, "Print"], Cell[231765, 5105, 432, 7, 25, "Print"], Cell[232200, 5114, 447, 8, 25, "Print"], Cell[232650, 5124, 432, 7, 25, "Print"], Cell[233085, 5133, 447, 8, 25, "Print"], Cell[233535, 5143, 453, 8, 25, "Print"], Cell[233991, 5153, 459, 8, 25, "Print"], Cell[234453, 5163, 453, 8, 25, "Print"], Cell[234909, 5173, 459, 8, 25, "Print"], Cell[235371, 5183, 453, 8, 25, "Print"], Cell[235827, 5193, 459, 8, 25, "Print"], Cell[236289, 5203, 453, 8, 25, "Print"], Cell[236745, 5213, 459, 8, 25, "Print"], Cell[237207, 5223, 428, 7, 25, "Print"], Cell[237638, 5232, 441, 8, 25, "Print"], Cell[238082, 5242, 422, 7, 25, "Print"], Cell[238507, 5251, 449, 8, 25, "Print"], Cell[238959, 5261, 455, 8, 25, "Print"], Cell[239417, 5271, 449, 8, 25, "Print"], Cell[239869, 5281, 422, 7, 25, "Print"], Cell[240294, 5290, 428, 7, 25, "Print"], Cell[240725, 5299, 441, 8, 25, "Print"], Cell[241169, 5309, 461, 8, 25, "Print"], Cell[241633, 5319, 455, 8, 25, "Print"], Cell[242091, 5329, 461, 8, 25, "Print"], Cell[242555, 5339, 441, 8, 25, "Print"], Cell[242999, 5349, 455, 8, 25, "Print"], Cell[243457, 5359, 441, 8, 25, "Print"], Cell[243901, 5369, 455, 8, 25, "Print"], Cell[244359, 5379, 455, 8, 25, "Print"], Cell[244817, 5389, 467, 8, 25, "Print"], Cell[245287, 5399, 455, 8, 25, "Print"], Cell[245745, 5409, 467, 8, 25, "Print"], Cell[246215, 5419, 467, 8, 25, "Print"], Cell[246685, 5429, 467, 8, 25, "Print"], Cell[247155, 5439, 467, 8, 25, "Print"], Cell[247625, 5449, 467, 8, 25, "Print"], Cell[248095, 5459, 426, 7, 25, "Print"], Cell[248524, 5468, 432, 7, 25, "Print"], Cell[248959, 5477, 432, 7, 25, "Print"], Cell[249394, 5486, 447, 8, 25, "Print"], Cell[249844, 5496, 420, 7, 25, "Print"], Cell[250267, 5505, 432, 7, 25, "Print"], Cell[250702, 5514, 447, 8, 25, "Print"], Cell[251152, 5524, 432, 7, 25, "Print"], Cell[251587, 5533, 420, 7, 25, "Print"], Cell[252010, 5542, 447, 8, 25, "Print"], Cell[252460, 5552, 432, 7, 25, "Print"], Cell[252895, 5561, 453, 8, 25, "Print"], Cell[253351, 5571, 426, 7, 25, "Print"], Cell[253780, 5580, 432, 7, 25, "Print"], Cell[254215, 5589, 432, 7, 25, "Print"], Cell[254650, 5598, 447, 8, 25, "Print"], Cell[255100, 5608, 432, 7, 25, "Print"], Cell[255535, 5617, 447, 8, 25, "Print"], Cell[255985, 5627, 447, 8, 25, "Print"], Cell[256435, 5637, 453, 8, 25, "Print"], Cell[256891, 5647, 420, 7, 25, "Print"], Cell[257314, 5656, 426, 7, 25, "Print"], Cell[257743, 5665, 447, 8, 25, "Print"], Cell[258193, 5675, 420, 7, 25, "Print"], Cell[258616, 5684, 426, 7, 25, "Print"], Cell[259045, 5693, 453, 8, 25, "Print"], Cell[259501, 5703, 453, 8, 25, "Print"], Cell[259957, 5713, 447, 8, 25, "Print"], Cell[260407, 5723, 447, 8, 25, "Print"], Cell[260857, 5733, 459, 8, 25, "Print"], Cell[261319, 5743, 447, 8, 25, "Print"], Cell[261769, 5753, 447, 8, 25, "Print"], Cell[262219, 5763, 447, 8, 25, "Print"], Cell[262669, 5773, 453, 8, 25, "Print"], Cell[263125, 5783, 453, 8, 25, "Print"], Cell[263581, 5793, 459, 8, 25, "Print"], Cell[264043, 5803, 428, 7, 25, "Print"], Cell[264474, 5812, 441, 8, 25, "Print"], Cell[264918, 5822, 441, 8, 25, "Print"], Cell[265362, 5832, 449, 8, 25, "Print"], Cell[265814, 5842, 428, 7, 25, "Print"], Cell[266245, 5851, 449, 8, 25, "Print"], Cell[266697, 5861, 449, 8, 25, "Print"], Cell[267149, 5871, 461, 8, 25, "Print"], Cell[267613, 5881, 441, 8, 25, "Print"], Cell[268057, 5891, 449, 8, 25, "Print"], Cell[268509, 5901, 449, 8, 25, "Print"], Cell[268961, 5911, 441, 8, 25, "Print"], Cell[269405, 5921, 449, 8, 25, "Print"], Cell[269857, 5931, 455, 8, 25, "Print"], Cell[270315, 5941, 455, 8, 25, "Print"], Cell[270773, 5951, 461, 8, 25, "Print"], Cell[271237, 5961, 449, 8, 25, "Print"], Cell[271689, 5971, 428, 7, 25, "Print"], Cell[272120, 5980, 428, 7, 25, "Print"], Cell[272551, 5989, 441, 8, 25, "Print"], Cell[272995, 5999, 449, 8, 25, "Print"], Cell[273447, 6009, 455, 8, 25, "Print"], Cell[273905, 6019, 441, 8, 25, "Print"], Cell[274349, 6029, 455, 8, 25, "Print"], Cell[274807, 6039, 455, 8, 25, "Print"], Cell[275265, 6049, 455, 8, 25, "Print"], Cell[275723, 6059, 467, 8, 25, "Print"], Cell[276193, 6069, 467, 8, 25, "Print"], Cell[276663, 6079, 441, 8, 25, "Print"], Cell[277107, 6089, 455, 8, 25, "Print"], Cell[277565, 6099, 441, 8, 25, "Print"], Cell[278009, 6109, 449, 8, 25, "Print"], Cell[278461, 6119, 449, 8, 25, "Print"], Cell[278913, 6129, 455, 8, 25, "Print"], Cell[279371, 6139, 449, 8, 25, "Print"], Cell[279823, 6149, 449, 8, 25, "Print"], Cell[280275, 6159, 455, 8, 25, "Print"], Cell[280733, 6169, 455, 8, 25, "Print"], Cell[281191, 6179, 461, 8, 25, "Print"], Cell[281655, 6189, 461, 8, 25, "Print"], Cell[282119, 6199, 467, 8, 25, "Print"], Cell[282589, 6209, 461, 8, 25, "Print"], Cell[283053, 6219, 467, 8, 25, "Print"], Cell[283523, 6229, 461, 8, 25, "Print"], Cell[283987, 6239, 428, 7, 25, "Print"], Cell[284418, 6248, 428, 7, 25, "Print"], Cell[284849, 6257, 441, 8, 25, "Print"], Cell[285293, 6267, 455, 8, 25, "Print"], Cell[285751, 6277, 428, 7, 25, "Print"], Cell[286182, 6286, 441, 8, 25, "Print"], Cell[286626, 6296, 441, 8, 25, "Print"], Cell[287070, 6306, 461, 8, 25, "Print"], Cell[287534, 6316, 428, 7, 25, "Print"], Cell[287965, 6325, 441, 8, 25, "Print"], Cell[288409, 6335, 455, 8, 25, "Print"], Cell[288867, 6345, 461, 8, 25, "Print"], Cell[289331, 6355, 461, 8, 25, "Print"], Cell[289795, 6365, 467, 8, 25, "Print"], Cell[290265, 6375, 455, 8, 25, "Print"], Cell[290723, 6385, 455, 8, 25, "Print"], Cell[291181, 6395, 461, 8, 25, "Print"], Cell[291645, 6405, 455, 8, 25, "Print"], Cell[292103, 6415, 455, 8, 25, "Print"], Cell[292561, 6425, 467, 8, 25, "Print"], Cell[293031, 6435, 461, 8, 25, "Print"], Cell[293495, 6445, 467, 8, 25, "Print"], Cell[293965, 6455, 461, 8, 25, "Print"], Cell[294429, 6465, 467, 8, 25, "Print"], Cell[294899, 6475, 430, 7, 25, "Print"], Cell[295332, 6484, 457, 8, 25, "Print"], Cell[295792, 6494, 445, 8, 25, "Print"], Cell[296240, 6504, 451, 8, 25, "Print"], Cell[296694, 6514, 457, 8, 25, "Print"], Cell[297154, 6524, 463, 8, 25, "Print"], Cell[297620, 6534, 430, 7, 25, "Print"], Cell[298053, 6543, 445, 8, 25, "Print"], Cell[298501, 6553, 445, 8, 25, "Print"], Cell[298949, 6563, 445, 8, 25, "Print"], Cell[299397, 6573, 451, 8, 25, "Print"], Cell[299851, 6583, 457, 8, 25, "Print"], Cell[300311, 6593, 457, 8, 25, "Print"], Cell[300771, 6603, 463, 8, 25, "Print"], Cell[301237, 6613, 451, 8, 25, "Print"], Cell[301691, 6623, 463, 8, 25, "Print"], Cell[302157, 6633, 451, 8, 25, "Print"], Cell[302611, 6643, 457, 8, 25, "Print"], Cell[303071, 6653, 457, 8, 25, "Print"], Cell[303531, 6663, 457, 8, 25, "Print"], Cell[303991, 6673, 457, 8, 25, "Print"], Cell[304451, 6683, 463, 8, 25, "Print"], Cell[304917, 6693, 463, 8, 25, "Print"], Cell[305383, 6703, 463, 8, 25, "Print"], Cell[305849, 6713, 451, 8, 25, "Print"], Cell[306303, 6723, 463, 8, 25, "Print"], Cell[306769, 6733, 451, 8, 25, "Print"], Cell[307223, 6743, 463, 8, 25, "Print"], Cell[307689, 6753, 463, 8, 25, "Print"], Cell[308155, 6763, 475, 8, 25, "Print"], Cell[308633, 6773, 463, 8, 25, "Print"], Cell[309099, 6783, 475, 8, 25, "Print"], Cell[309577, 6793, 469, 8, 25, "Print"], Cell[310049, 6803, 469, 8, 25, "Print"], Cell[310521, 6813, 469, 8, 25, "Print"], Cell[310993, 6823, 475, 8, 25, "Print"], Cell[311471, 6833, 469, 8, 25, "Print"], Cell[311943, 6843, 469, 8, 25, "Print"], Cell[312415, 6853, 475, 8, 25, "Print"], Cell[312893, 6863, 469, 8, 25, "Print"], Cell[313365, 6873, 426, 7, 25, "Print"], Cell[313794, 6882, 432, 7, 25, "Print"], Cell[314229, 6891, 420, 7, 25, "Print"], Cell[314652, 6900, 426, 7, 25, "Print"], Cell[315081, 6909, 432, 7, 25, "Print"], Cell[315516, 6918, 447, 8, 25, "Print"], Cell[315966, 6928, 432, 7, 25, "Print"], Cell[316401, 6937, 447, 8, 25, "Print"], Cell[316851, 6947, 420, 7, 25, "Print"], Cell[317274, 6956, 432, 7, 25, "Print"], Cell[317709, 6965, 432, 7, 25, "Print"], Cell[318144, 6974, 453, 8, 25, "Print"], Cell[318600, 6984, 432, 7, 25, "Print"], Cell[319035, 6993, 426, 7, 25, "Print"], Cell[319464, 7002, 447, 8, 25, "Print"], Cell[319914, 7012, 420, 7, 25, "Print"], Cell[320337, 7021, 426, 7, 25, "Print"], Cell[320766, 7030, 447, 8, 25, "Print"], Cell[321216, 7040, 453, 8, 25, "Print"], Cell[321672, 7050, 432, 7, 25, "Print"], Cell[322107, 7059, 447, 8, 25, "Print"], Cell[322557, 7069, 453, 8, 25, "Print"], Cell[323013, 7079, 420, 7, 25, "Print"], Cell[323436, 7088, 432, 7, 25, "Print"], Cell[323871, 7097, 453, 8, 25, "Print"], Cell[324327, 7107, 447, 8, 25, "Print"], Cell[324777, 7117, 459, 8, 25, "Print"], Cell[325239, 7127, 459, 8, 25, "Print"], Cell[325701, 7137, 426, 7, 25, "Print"], Cell[326130, 7146, 432, 7, 25, "Print"], Cell[326565, 7155, 432, 7, 25, "Print"], Cell[327000, 7164, 447, 8, 25, "Print"], Cell[327450, 7174, 426, 7, 25, "Print"], Cell[327879, 7183, 432, 7, 25, "Print"], Cell[328314, 7192, 432, 7, 25, "Print"], Cell[328749, 7201, 447, 8, 25, "Print"], Cell[329199, 7211, 447, 8, 25, "Print"], Cell[329649, 7221, 459, 8, 25, "Print"], Cell[330111, 7231, 447, 8, 25, "Print"], Cell[330561, 7241, 459, 8, 25, "Print"], Cell[331023, 7251, 447, 8, 25, "Print"], Cell[331473, 7261, 447, 8, 25, "Print"], Cell[331923, 7271, 465, 8, 25, "Print"], Cell[332391, 7281, 465, 8, 25, "Print"], Cell[332859, 7291, 441, 8, 25, "Print"], Cell[333303, 7301, 428, 7, 25, "Print"], Cell[333734, 7310, 449, 8, 25, "Print"], Cell[334186, 7320, 428, 7, 25, "Print"], Cell[334617, 7329, 455, 8, 25, "Print"], Cell[335075, 7339, 461, 8, 25, "Print"], Cell[335539, 7349, 441, 8, 25, "Print"], Cell[335983, 7359, 455, 8, 25, "Print"], Cell[336441, 7369, 449, 8, 25, "Print"], Cell[336893, 7379, 461, 8, 25, "Print"], Cell[337357, 7389, 467, 8, 25, "Print"], Cell[337827, 7399, 467, 8, 25, "Print"], Cell[338297, 7409, 428, 7, 25, "Print"], Cell[338728, 7418, 441, 8, 25, "Print"], Cell[339172, 7428, 428, 7, 25, "Print"], Cell[339603, 7437, 441, 8, 25, "Print"], Cell[340047, 7447, 461, 8, 25, "Print"], Cell[340511, 7457, 467, 8, 25, "Print"], Cell[340981, 7467, 461, 8, 25, "Print"], Cell[341445, 7477, 467, 8, 25, "Print"], Cell[341915, 7487, 428, 7, 25, "Print"], Cell[342346, 7496, 441, 8, 25, "Print"], Cell[342790, 7506, 449, 8, 25, "Print"], Cell[343242, 7516, 455, 8, 25, "Print"], Cell[343700, 7526, 428, 7, 25, "Print"], Cell[344131, 7535, 449, 8, 25, "Print"], Cell[344583, 7545, 449, 8, 25, "Print"], Cell[345035, 7555, 461, 8, 25, "Print"], Cell[345499, 7565, 428, 7, 25, "Print"], Cell[345930, 7574, 441, 8, 25, "Print"], Cell[346374, 7584, 428, 7, 25, "Print"], Cell[346805, 7593, 449, 8, 25, "Print"], Cell[347257, 7603, 461, 8, 25, "Print"], Cell[347721, 7613, 455, 8, 25, "Print"], Cell[348179, 7623, 467, 8, 25, "Print"], Cell[348649, 7633, 467, 8, 25, "Print"], Cell[349119, 7643, 441, 8, 25, "Print"], Cell[349563, 7653, 449, 8, 25, "Print"], Cell[350015, 7663, 449, 8, 25, "Print"], Cell[350467, 7673, 455, 8, 25, "Print"], Cell[350925, 7683, 441, 8, 25, "Print"], Cell[351369, 7693, 449, 8, 25, "Print"], Cell[351821, 7703, 455, 8, 25, "Print"], Cell[352279, 7713, 461, 8, 25, "Print"], Cell[352743, 7723, 441, 8, 25, "Print"], Cell[353187, 7733, 449, 8, 25, "Print"], Cell[353639, 7743, 441, 8, 25, "Print"], Cell[354083, 7753, 449, 8, 25, "Print"], Cell[354535, 7763, 461, 8, 25, "Print"], Cell[354999, 7773, 467, 8, 25, "Print"], Cell[355469, 7783, 461, 8, 25, "Print"], Cell[355933, 7793, 467, 8, 25, "Print"], Cell[356403, 7803, 449, 8, 25, "Print"], Cell[356855, 7813, 461, 8, 25, "Print"], Cell[357319, 7823, 455, 8, 25, "Print"], Cell[357777, 7833, 467, 8, 25, "Print"], Cell[358247, 7843, 455, 8, 25, "Print"], Cell[358705, 7853, 461, 8, 25, "Print"], Cell[359169, 7863, 461, 8, 25, "Print"], Cell[359633, 7873, 467, 8, 25, "Print"], Cell[360103, 7883, 430, 7, 25, "Print"], Cell[360536, 7892, 430, 7, 25, "Print"], Cell[360969, 7901, 451, 8, 25, "Print"], Cell[361423, 7911, 463, 8, 25, "Print"], Cell[361889, 7921, 451, 8, 25, "Print"], Cell[362343, 7931, 463, 8, 25, "Print"], Cell[362809, 7941, 475, 8, 25, "Print"], Cell[363287, 7951, 475, 8, 25, "Print"], Cell[363765, 7961, 445, 8, 25, "Print"], Cell[364213, 7971, 445, 8, 25, "Print"], Cell[364661, 7981, 451, 8, 25, "Print"], Cell[365115, 7991, 463, 8, 25, "Print"], Cell[365581, 8001, 457, 8, 25, "Print"], Cell[366041, 8011, 475, 8, 25, "Print"], Cell[366519, 8021, 451, 8, 25, "Print"], Cell[366973, 8031, 463, 8, 25, "Print"], Cell[367439, 8041, 463, 8, 25, "Print"], Cell[367905, 8051, 475, 8, 25, "Print"], Cell[368383, 8061, 457, 8, 25, "Print"], Cell[368843, 8071, 463, 8, 25, "Print"], Cell[369309, 8081, 469, 8, 25, "Print"], Cell[369781, 8091, 475, 8, 25, "Print"], Cell[370259, 8101, 469, 8, 25, "Print"], Cell[370731, 8111, 475, 8, 25, "Print"], Cell[371209, 8121, 441, 8, 25, "Print"], Cell[371653, 8131, 441, 8, 25, "Print"], Cell[372097, 8141, 449, 8, 25, "Print"], Cell[372549, 8151, 441, 8, 25, "Print"], Cell[372993, 8161, 449, 8, 25, "Print"], Cell[373445, 8171, 449, 8, 25, "Print"], Cell[373897, 8181, 461, 8, 25, "Print"], Cell[374361, 8191, 467, 8, 25, "Print"], Cell[374831, 8201, 441, 8, 25, "Print"], Cell[375275, 8211, 449, 8, 25, "Print"], Cell[375727, 8221, 461, 8, 25, "Print"], Cell[376191, 8231, 467, 8, 25, "Print"], Cell[376661, 8241, 445, 8, 25, "Print"], Cell[377109, 8251, 445, 8, 25, "Print"], Cell[377557, 8261, 451, 8, 25, "Print"], Cell[378011, 8271, 463, 8, 25, "Print"], Cell[378477, 8281, 457, 8, 25, "Print"], Cell[378937, 8291, 469, 8, 25, "Print"], Cell[379409, 8301, 451, 8, 25, "Print"], Cell[379863, 8311, 463, 8, 25, "Print"], Cell[380329, 8321, 451, 8, 25, "Print"], Cell[380783, 8331, 457, 8, 25, "Print"], Cell[381243, 8341, 463, 8, 25, "Print"], Cell[381709, 8351, 445, 8, 25, "Print"], Cell[382157, 8361, 451, 8, 25, "Print"], Cell[382611, 8371, 463, 8, 25, "Print"], Cell[383077, 8381, 469, 8, 25, "Print"], Cell[383549, 8391, 451, 8, 25, "Print"], Cell[384003, 8401, 457, 8, 25, "Print"], Cell[384463, 8411, 463, 8, 25, "Print"], Cell[384929, 8421, 445, 8, 25, "Print"], Cell[385377, 8431, 457, 8, 25, "Print"], Cell[385837, 8441, 469, 8, 25, "Print"], Cell[386309, 8451, 451, 8, 25, "Print"], Cell[386763, 8461, 463, 8, 25, "Print"], Cell[387229, 8471, 469, 8, 25, "Print"], Cell[387701, 8481, 445, 8, 25, "Print"], Cell[388149, 8491, 451, 8, 25, "Print"], Cell[388603, 8501, 445, 8, 25, "Print"], Cell[389051, 8511, 451, 8, 25, "Print"], Cell[389505, 8521, 463, 8, 25, "Print"], Cell[389971, 8531, 469, 8, 25, "Print"], Cell[390443, 8541, 463, 8, 25, "Print"], Cell[390909, 8551, 463, 8, 25, "Print"], Cell[391375, 8561, 469, 8, 25, "Print"], Cell[391847, 8571, 463, 8, 25, "Print"], Cell[392313, 8581, 469, 8, 25, "Print"], Cell[392785, 8591, 469, 8, 25, "Print"], Cell[393257, 8601, 445, 8, 25, "Print"], Cell[393705, 8611, 451, 8, 25, "Print"], Cell[394159, 8621, 469, 8, 25, "Print"], Cell[394631, 8631, 475, 8, 25, "Print"], Cell[395109, 8641, 445, 8, 25, "Print"], Cell[395557, 8651, 451, 8, 25, "Print"], Cell[396011, 8661, 469, 8, 25, "Print"], Cell[396483, 8671, 475, 8, 25, "Print"], Cell[396961, 8681, 445, 8, 25, "Print"], Cell[397409, 8691, 463, 8, 25, "Print"], Cell[397875, 8701, 445, 8, 25, "Print"], Cell[398323, 8711, 463, 8, 25, "Print"], Cell[398789, 8721, 451, 8, 25, "Print"], Cell[399243, 8731, 463, 8, 25, "Print"], Cell[399709, 8741, 463, 8, 25, "Print"], Cell[400175, 8751, 469, 8, 25, "Print"], Cell[400647, 8761, 451, 8, 25, "Print"], Cell[401101, 8771, 463, 8, 25, "Print"], Cell[401567, 8781, 469, 8, 25, "Print"], Cell[402039, 8791, 475, 8, 25, "Print"], Cell[402517, 8801, 463, 8, 25, "Print"], Cell[402983, 8811, 469, 8, 25, "Print"], Cell[403455, 8821, 469, 8, 25, "Print"], Cell[403927, 8831, 475, 8, 25, "Print"], Cell[404405, 8841, 447, 8, 25, "Print"], Cell[404855, 8851, 447, 8, 25, "Print"], Cell[405305, 8861, 459, 8, 25, "Print"], Cell[405767, 8871, 471, 8, 25, "Print"], Cell[406241, 8881, 453, 8, 25, "Print"], Cell[406697, 8891, 465, 8, 25, "Print"], Cell[407165, 8901, 453, 8, 25, "Print"], Cell[407621, 8911, 465, 8, 25, "Print"], Cell[408089, 8921, 477, 8, 25, "Print"], Cell[408569, 8931, 459, 8, 25, "Print"], Cell[409031, 8941, 477, 8, 25, "Print"], Cell[409511, 8951, 471, 8, 25, "Print"], Cell[409985, 8961, 453, 8, 25, "Print"], Cell[410441, 8971, 459, 8, 25, "Print"], Cell[410903, 8981, 453, 8, 25, "Print"], Cell[411359, 8991, 465, 8, 25, "Print"], Cell[411827, 9001, 471, 8, 25, "Print"], Cell[412301, 9011, 483, 8, 25, "Print"], Cell[412787, 9021, 465, 8, 25, "Print"], Cell[413255, 9031, 471, 8, 25, "Print"], Cell[413729, 9041, 459, 8, 25, "Print"], Cell[414191, 9051, 471, 8, 25, "Print"], Cell[414665, 9061, 471, 8, 25, "Print"], Cell[415139, 9071, 483, 8, 25, "Print"], Cell[415625, 9081, 459, 8, 25, "Print"], Cell[416087, 9091, 465, 8, 25, "Print"], Cell[416555, 9101, 459, 8, 25, "Print"], Cell[417017, 9111, 465, 8, 25, "Print"], Cell[417485, 9121, 477, 8, 25, "Print"], Cell[417965, 9131, 483, 8, 25, "Print"], Cell[418451, 9141, 471, 8, 25, "Print"], Cell[418925, 9151, 465, 8, 25, "Print"], Cell[419393, 9161, 471, 8, 25, "Print"], Cell[419867, 9171, 477, 8, 25, "Print"], Cell[420347, 9181, 465, 8, 25, "Print"], Cell[420815, 9191, 471, 8, 25, "Print"], Cell[421289, 9201, 477, 8, 25, "Print"], Cell[421769, 9211, 483, 8, 25, "Print"], Cell[422255, 9221, 471, 8, 25, "Print"], Cell[422729, 9231, 477, 8, 25, "Print"], Cell[423209, 9241, 294, 6, 25, "Print"] }, Open ]], Cell[423518, 9250, 142, 3, 33, "Text"], Cell[CellGroupData[{ Cell[423685, 9257, 75, 1, 30, "Input"], Cell[423763, 9260, 76, 1, 25, "Print"], Cell[423842, 9263, 222, 4, 25, "Print"], Cell[424067, 9269, 2012, 37, 261, "Print"], Cell[426082, 9308, 222, 4, 25, "Print"], Cell[426307, 9314, 2012, 37, 261, "Print"], Cell[428322, 9353, 222, 4, 25, "Print"], Cell[428547, 9359, 2012, 37, 261, "Print"], Cell[430562, 9398, 222, 4, 25, "Print"], Cell[430787, 9404, 2012, 37, 261, "Print"], Cell[432802, 9443, 222, 4, 25, "Print"], Cell[433027, 9449, 2012, 37, 261, "Print"], Cell[435042, 9488, 222, 4, 25, "Print"], Cell[435267, 9494, 2012, 37, 261, "Print"], Cell[437282, 9533, 222, 4, 25, "Print"], Cell[437507, 9539, 2012, 37, 261, "Print"], Cell[439522, 9578, 222, 4, 25, "Print"], Cell[439747, 9584, 2010, 36, 261, "Print"], Cell[441760, 9622, 224, 4, 25, "Print"], Cell[441987, 9628, 2012, 37, 261, "Print"], Cell[444002, 9667, 224, 4, 25, "Print"], Cell[444229, 9673, 2012, 37, 261, "Print"], Cell[446244, 9712, 224, 4, 25, "Print"], Cell[446471, 9718, 2012, 37, 261, "Print"], Cell[448486, 9757, 224, 4, 25, "Print"], Cell[448713, 9763, 2012, 37, 261, "Print"], Cell[450728, 9802, 224, 4, 25, "Print"], Cell[450955, 9808, 2012, 37, 261, "Print"], Cell[452970, 9847, 111, 2, 25, "Print"], Cell[453084, 9851, 2076, 36, 261, "Print"], Cell[455163, 9889, 2076, 36, 261, "Print"], Cell[457242, 9927, 115, 2, 25, "Print"], Cell[457360, 9931, 2236, 44, 261, "Print"], Cell[459599, 9977, 71, 1, 25, "Print"], Cell[459673, 9980, 179, 3, 25, "Print"], Cell[459855, 9985, 69, 1, 25, "Print"], Cell[459927, 9988, 68, 1, 25, "Print"], Cell[459998, 9991, 218, 4, 25, "Print"], Cell[460219, 9997, 147, 3, 25, "Print"], Cell[460369, 10002, 218, 4, 25, "Print"], Cell[460590, 10008, 147, 3, 25, "Print"], Cell[460740, 10013, 218, 4, 25, "Print"], Cell[460961, 10019, 147, 3, 25, "Print"], Cell[461111, 10024, 218, 4, 25, "Print"], Cell[461332, 10030, 147, 3, 25, "Print"], Cell[461482, 10035, 218, 4, 25, "Print"], Cell[461703, 10041, 147, 3, 25, "Print"], Cell[461853, 10046, 218, 4, 25, "Print"], Cell[462074, 10052, 147, 3, 25, "Print"], Cell[462224, 10057, 218, 4, 25, "Print"], Cell[462445, 10063, 147, 3, 25, "Print"], Cell[462595, 10068, 218, 4, 25, "Print"], Cell[462816, 10074, 147, 3, 25, "Print"], Cell[462966, 10079, 64, 1, 25, "Print"], Cell[463033, 10082, 179, 3, 25, "Print"], Cell[463215, 10087, 69, 1, 25, "Print"], Cell[463287, 10090, 68, 1, 25, "Print"], Cell[463358, 10093, 218, 4, 25, "Print"], Cell[463579, 10099, 147, 3, 25, "Print"], Cell[463729, 10104, 218, 4, 25, "Print"], Cell[463950, 10110, 147, 3, 25, "Print"], Cell[464100, 10115, 218, 4, 25, "Print"], Cell[464321, 10121, 147, 3, 25, "Print"], Cell[464471, 10126, 218, 4, 25, "Print"], Cell[464692, 10132, 147, 3, 25, "Print"], Cell[464842, 10137, 218, 4, 25, "Print"], Cell[465063, 10143, 147, 3, 25, "Print"], Cell[465213, 10148, 64, 1, 25, "Print"], Cell[465280, 10151, 179, 3, 25, "Print"], Cell[465462, 10156, 69, 1, 25, "Print"], Cell[465534, 10159, 68, 1, 25, "Print"], Cell[465605, 10162, 218, 4, 25, "Print"], Cell[465826, 10168, 147, 3, 25, "Print"], Cell[465976, 10173, 218, 4, 25, "Print"], Cell[466197, 10179, 147, 3, 25, "Print"], Cell[466347, 10184, 218, 4, 25, "Print"], Cell[466568, 10190, 147, 3, 25, "Print"], Cell[466718, 10195, 218, 4, 25, "Print"], Cell[466939, 10201, 147, 3, 25, "Print"], Cell[467089, 10206, 218, 4, 25, "Print"], Cell[467310, 10212, 147, 3, 25, "Print"], Cell[467460, 10217, 64, 1, 25, "Print"], Cell[467527, 10220, 179, 3, 25, "Print"], Cell[467709, 10225, 69, 1, 25, "Print"], Cell[467781, 10228, 68, 1, 25, "Print"], Cell[467852, 10231, 218, 4, 25, "Print"], Cell[468073, 10237, 147, 3, 25, "Print"], Cell[468223, 10242, 218, 4, 25, "Print"], Cell[468444, 10248, 147, 3, 25, "Print"], Cell[468594, 10253, 218, 4, 25, "Print"], Cell[468815, 10259, 149, 3, 25, "Print"], Cell[468967, 10264, 218, 4, 25, "Print"], Cell[469188, 10270, 147, 3, 25, "Print"], Cell[469338, 10275, 64, 1, 25, "Print"], Cell[469405, 10278, 179, 3, 25, "Print"], Cell[469587, 10283, 69, 1, 25, "Print"], Cell[469659, 10286, 68, 1, 25, "Print"], Cell[469730, 10289, 218, 4, 25, "Print"], Cell[469951, 10295, 147, 3, 25, "Print"], Cell[470101, 10300, 218, 4, 25, "Print"], Cell[470322, 10306, 147, 3, 25, "Print"], Cell[470472, 10311, 218, 4, 25, "Print"], Cell[470693, 10317, 149, 3, 25, "Print"], Cell[470845, 10322, 218, 4, 25, "Print"], Cell[471066, 10328, 147, 3, 25, "Print"], Cell[471216, 10333, 64, 1, 25, "Print"], Cell[471283, 10336, 292, 6, 25, "Print"], Cell[471578, 10344, 81, 1, 25, "Print"], Cell[471662, 10347, 81, 1, 25, "Print"] }, Open ]] }, Open ]] }, Open ]] } ] *) (*********************************************************************** End of Mathematica Notebook file. ***********************************************************************)