ASCII?
Try it yourself at the microsite here.
Creating an image processing function for Wolfram Mathematica
Supports all Image files and GIF animations. Different alphabets are available. You can choose between you output image to be colored.
So, how does this work?
Buckle your seat-belts, grab your popcorn, because in twenty seven variables I'm going to teach you something that I only learned two weeks ago. So sit down, open your kernels and enjoy the experience of my 4 pm last minute pepsi fueled writing extravaganza. [[Dariia's censorship]]
The program substitutes groups of pixels with a character that
Input form for the function:
ASCIIfy[graphicchoice_, charchoice_, cbasic_, grainchoice_, coloredchoice_, fontfam_, fontsize_, blackbg_] :=
This function declares multiple variables inside of itself, so you need to use Module.
Module[{graphic, charsbasic, auto, setchars, chars, charsmean, truecharwidth, truecharheight, charwidth, charheight, pic, picwc, width, height, charpic, giftable, picmeans, graphicframe},
graphicchoice is the image or GIF. They are processed the same, so images will be converted to a list)
If[ListQ[graphicchoice], graphic = graphicchoice, graphic = List[graphicchoice]];
charchoice specifies the charset to be used.
The default Auto uses automatic location and outputs the alphabet used in your country.
auto = EntityValue[$GeoLocationCountry, "Languages"][[1]];
If cbasic =True the program will add numbers and symbols to the characters used.
If[cbasic,
charsbasic = {"$", "&", "'", ",", ".", "0", "1", "2", "3", "4", "5", "6", "7", "8", "9", ":", ";", "?"},
charsbasic = List[]];
Finally, a list of chars to be used is created.
setchars[lang_] := If[lang == "Auto",
Join[Alphabet[auto], Capitalize[Alphabet[auto]], charsbasic],
Join[Alphabet[lang], Capitalize[Alphabet[lang]], charsbasic]];
chars = setchars[charchoice];
The next step is finding out the average brightnesses of these characters. First their dimensions are established.
truecharwidth =
Max[Table[Length[ImageData[Rasterize[Style[chars[[c]], FontFamily -> fontfam]]][[1]]], {c, 1, Length[chars]}]];
truecharheight =
Max[Table[Length[ImageData[Rasterize[Style[chars[[c]], FontFamily -> fontfam]]]], {c, 1, Length[chars]}]];
Now to get the average brightness (or mean).
Table[ImageMeasurements[
ColorConvert[
Rasterize[
Pane[Style[chars[[a]], FontFamily -> fontfam], {truecharwidth,
truecharheight}, Alignment -> Center], ImageSize -> 50],
"Grayscale"], "Mean"], {a, 1, Length[chars]}];
grainchoice specifies how many pixels wide should the fragment replaced by one character be.
If[grainchoice == "Auto", charwidth = truecharwidth;
charheight = truecharheight, charwidth = grainchoice;
charheight = Round[grainchoice*truecharheight/truecharwidth]];
Dark images will not be well represented by chars, as they have a white background, so before applying the program the image brightness is scaled up accordingly.
bleach[im_] := im*(1 - Min[charsmean]) + Min[charsmean];
The main part is a function that creates the ASCIIfied images (when dealing with Image files, just one)
It is surrounded by a Monitor - a function used to indicate progress. This is useful when converting large images or GIFs.
Monitor[(giftable = Table[(...),{frame, 1, Length[graphic]}]),{(testy - 1)/height*1. + (frame - 1), Length[graphic]}]
If blackbg is chosen as True, the program will run in almost the same manner. Almost. It first creates a color negative of the wanted image, then creates its asciified version, and then negates it.
If[blackbg, graphicframe = ColorNegate[graphic[[frame]]], graphicframe = graphic[[frame]]];
As mentioned before, this program will compare image fragments and letters. To do that, it first partitions the image, which is first "bleached" and grayscale.
pic = ImagePartition[ImageApply[bleach,
{ColorConvert[graphicframe, "Grayscale"]}], {charwidth,
charheight}];
Checks the amount of fragments.
{height, width} = Dimensions[pic];
And calculates the average brightness of each fragment.
picmeans =
Table[ImageMeasurements[pic[[y, x]], "Mean"], {x, 1, width}, {y, 1,
height}];
It then names a function that calculates the differences between a piece of \ the image and all chars.
diffs[rownumber_, placeinrow_] :=
Table[charsmean[[a]] - picmeans[[rownumber, placeinrow]], {a, 1, Length[chars]}]^2;
And a function that picks the character whose difference is the smallest.
best[x_, y_] := chars[[Position[diffs[x, y], Min[diffs[x, y]]][[1, 1]]]];
The most important part: Creating an array (actually a column of rows) of best fitting letters. If you want to reuse this code and would prefer to output letters and not an image output charpic.
If[coloredchoice,
charpic = TableForm[Table[Style[best[testx, testy],
FontColor -> RGBColor[ImageMeasurements[picwc[[testy, testx]], "Mean"]]], {testy, 1, height}, {testx, 1, width}], TableSpacing -> {0, 0}],
charpic = TableForm[Table[Style[best[testx, testy], FontColor -> Black], {testy, 1, height}, {testx, 1, width}], TableSpacing -> {0, 0}]];
This rasterizes the array (inverts it for black background, as previously mentioned).
If[blackbg, ColorNegate[Rasterize[Style[TableForm[Map[
Pane[#, {truecharwidth, truecharheight}, Alignment -> Center] &,
charpic, {3}], TableSpacing -> {0, 1}],
FontFamily -> fontfam]]],
Rasterize[Style[TableForm[Map[
Pane[#, {truecharwidth, truecharheight}, Alignment -> Center] &,
charpic, {3}], TableSpacing -> {0, 1}], FontFamily -> fontfam]]],
Frame's ending: repetition settings and monitored value.
{frame, 1, Length[graphic]}],{(testy - 1)/height*1. + (frame - 1), Length[graphic]}];
This is the export form for cloud deployment.
If[ListQ[graphicchoice],
ExportForm[giftable, "GIF", "AnimationRepetitions" -> \[Infinity]],
ExportForm[giftable[[1]], "PNG"]]
If you're using the function locally use this instead:
If[ListQ[graphicchoice],
Export["giftable.gif", giftable,
"AnimationRepetitions" -> \[Infinity]],
Export["giftable.jpg", giftable[[1]]]];
If[ListQ[graphicchoice],
SystemOpen["giftable.gif"],
SystemOpen["giftable.jpg"]]
And of course... :)
]
To CloudDeploy:
CloudDeploy[
FormFunction[{
"ImageOrGIF" -> "GIF" | "Image",
"Alphabet" -> alphalist,
"FontFamily" -> CloudEvaluate[$FontFamilies] -> "Times New Roman",
"FontSize" -> <|"Interpreter" -> Restricted["Integer", {3, 60, 3}],
"Control" -> Slider, "Default" -> 30|>,
"Grain" -> <|"Interpreter" -> Restricted["Integer", {1, 20}],
"Control" -> Slider, "Default" -> 10|>,
"BasicChars" -> "Boolean",
"Color" -> "Boolean",
"BlackBackground" -> "Boolean"},
ASCIIfy[#ImageOrGIF, #Alphabet, #BasicChars, #Grain, #Color, \
#FontFamily, #FontSize, #BlackBackground] &,
AppearanceRules -> <|"Title" -> "ascii\[CurlyPhi]",
"Description" ->
(*Your Discription - maybe Import[] an Image*)|>, PageTheme -> "Blue"], "AsciiArt",
Permissions -> "Public"]
alphalist is a list of possible alphabets
alphalist =
ToString /@ {Auto, Arabic, Belarusian, BosnianCyrillic, BosnianLatin,
Bulgarian, Croatian, Cyrillic, Danish, Devanagari, Dutch, English,
Estonian, Finnish, French, German, Greek, Hebrew, Hindi, Hiragana,
Hungarian, Italian, Katakana, Latin, MalayLatin,
MongolianCyrillic, MongolianLatin, Norwegian, Polish, Portuguese,
Romanian, Russian, Slovak, Spanish, Swedish, Turkish, Ukrainian,
Urdu}
Some Examples
Attachments: