Julia set

From Rosetta Code
Task
Julia set
You are encouraged to solve this task according to the task description, using any language you may know.
Task

Generate and draw a Julia set.

Related tasks



Ada

Library: SDLAda
with Ada.Numerics.Generic_Complex_Types;

with SDL.Video.Windows.Makers;
with SDL.Video.Renderers.Makers;
with SDL.Video.Palettes;
with SDL.Events.Events;

procedure Julia_Set is

   Width      : constant := 1_200;
   Height     : constant := 900;

   type Real is new Float;
   package Complex_Real is
      new Ada.Numerics.Generic_Complex_Types (Real);
   use Complex_Real;

   Iter   : constant         := 100;
   C      : constant Complex := (Re => -0.70000, Im => 0.27015);
   Move   : constant Complex := (Re => 0.000,    Im => 0.000);
   Zoom   : constant         := 0.800;

   Window   : SDL.Video.Windows.Window;
   Renderer : SDL.Video.Renderers.Renderer;
   Event    : SDL.Events.Events.Events;

   function Map (Width, Height : in Integer;
                 X, Y          : in Integer) return Complex
   is
      C : Complex;
      L : constant Real := Real (Integer'Max (Width, Height));
   begin
      C := (2.0 * Real (X - Width  / 2) / (L * Zoom),
            2.0 * Real (Y - Height / 2) / (L * Zoom));
      return C + Move;
   end Map;

   procedure Draw_Julia_Set is
      use type SDL.C.int;
      use SDL.Video.Palettes;
      Z : Complex;
   begin
      for Y in 0 .. Height loop
         for X in 0 .. Width loop
            Z := Map (Width, Height, X, Y);
            for N in 1 .. Iter loop
               Z := Z ** 2 + C;
               if abs (Z) > 2.0 then
                  Renderer.Set_Draw_Colour ((Red   => 2 * Colour_Component (N),
                                             Green => 255 - 2 * Colour_Component (N),
                                             Blue  => 150, Alpha => 255));
                  Renderer.Draw (Point => (X => SDL.C.int (X),
                                           Y => SDL.C.int (Y)));
                  exit;
               end if;
            end loop;
         end loop;
      end loop;
   end Draw_Julia_Set;

   procedure Wait is
      use type SDL.Events.Event_Types;
   begin
      loop
         while SDL.Events.Events.Poll (Event) loop
            if Event.Common.Event_Type = SDL.Events.Quit then
               return;
            end if;
         end loop;
      end loop;
   end Wait;

begin
   if not SDL.Initialise (Flags => SDL.Enable_Screen) then
      return;
   end if;

   SDL.Video.Windows.Makers.Create (Win      => Window,
                                    Title    => "Julia set",
                                    Position => SDL.Natural_Coordinates'(X => 10, Y => 10),
                                    Size     => SDL.Positive_Sizes'(Width, Height),
                                    Flags    => 0);
   SDL.Video.Renderers.Makers.Create  (Renderer, Window.Get_Surface);
   Renderer.Set_Draw_Colour ((0, 0, 0, 255));
   Renderer.Fill (Rectangle => (0, 0, Width, Height));

   Draw_Julia_Set;
   Window.Update_Surface;

   Wait;
   Window.Finalize;
   SDL.Finalise;
end Julia_Set;

ALGOL 68

Works with: ALGOL 68G version Any - tested with release 2.8.3.win32
Translation of: AWK
(which is itself a translation of COBOL).


Uses the Algol 68G specific argc and argv procedures. Note argv( 1 ) is the path of the Algol 68G interpreter and argv( 2 ) is the source being executed.

BEGIN
    REAL c real, c imaginary;
    STRING real and imaginary := IF argc < 3 THEN "-0.8"  ELSE argv( 3 ) FI
                               + " "
                               + IF argc < 4 THEN "0.156" ELSE argv( 4 ) FI
                               + " "
                               ;
    FILE numbers;
    associate( numbers, real and imaginary );
    get( numbers, ( c real, c imaginary ) );
    print( ( fixed( c real, -8, 4 ), fixed( c imaginary, -8, 4 ), newline ) );
    FOR v FROM -100 BY 10 TO 100 DO
        FOR h FROM -280 BY 10 TO 280 DO
            REAL x := h / 200;
            REAL y := v / 100;
            CHAR plot char := "#";
            FOR i TO 50
            WHILE
                REAL z real      = ( x * x ) - ( y * y ) + c real;
                REAL z imaginary = ( x * y * 2 ) + c imaginary;
                IF z real * z real <= 10000
                THEN TRUE
                ELSE
                    plot char := " ";
                    FALSE
                FI
            DO
                x := z real;
                y := z imaginary
            OD;
            print( ( plot char ) )
        OD;
        print( ( newline ) )
    OD
END
Output:
 -0.8000  0.1560



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



Amazing Hopper

Program made with the Basic-Hopper embedded version, using the tag "#hl {}". The generated file is binary, and the graph can be made with Matlab's "imshow" function.

Caption
 
#!/usr/bin/hopper

#include <hopper.h>

main:

    hxres = 500           // horizontal resolution
    hyres = 500           // vertical resolution

    itermax = 100         // maximum iters to do

    brk_out = 64          // |z|^2 greater than this is a breakout
    magnify = 1           // 10 is standard magnification, but if > 2, resolution should be greater than 500

    cr = -0.8             // real part of c in z^2=z^2+c
    ci = 0.156            // imaginary part of c in z^2=z^2+c

    julia=0,{hxres,hyres}nanarray(julia)

    {","}toksep
#hl{        // tag "high-level", Basic language embebed in Hopper

    hy=1
    while(hy<=hyres)
       hx=1
       while(hx<=hxres)
       
          y = 4*((((hyres+1-hy-0.5)/hyres)-0.5)/magnify)
          x = 4*((((hx-0.5)/hxres)-0.5)/magnify)
          zm = 0
       
          iter=1

          while(iter<=(itermax-1))
             xx = sqrdiff(x,y)+cr   //(x*x)-(y*y)+cr
             y = (2.0*x*y)+ci
             x = xx
             zsq = sqradd(x,y)      //(x*x)+(y*y)

             if (zsq>zm) 
                zm=zsq
             endif
             if (zsq>brk_out)
                break
             endif
             iter += 1
          wend

          if (iter>=itermax)
             julia[hy,hx]=1

          else
             julia[hy,hx]=0

          endif

          hx+=1
       wend
       hy+=1
    wend
   }
   toc(t1,t2)
   {julia,"julia.dat"}save
exit(0)
Versión 2.
Versión basada en Lua, escrita en Hopper-Jambo:
Caption
 
#include <jambo.h>

Main
   Set stack 15
   Cls
   map = {}
   Set '" ", ".", ":", "-", "=", "+", "*", "#", "%", "$", "@"', Apnd list 'map'

   Loop for ( y= -1.0, Less equal (y,1.0), Let ( y:=Add(y,0.05)) )
       Loop for ( x= -1.5, Less equal (x,1.5), Let ( x:=Add(x,0.025)) )
           zr = x, zi = y, i = 0, br = 0
           Loop
               Let ( br := Sqr diff(zr,zi) Minus '0.8' )
               Let ( zi := Mul(Mul(zr, zi), 2), Plus '0.156' )
               zr = br
               Break if ( Greater ( Sqr add (zr, zi), 4 ) )
               ++i
           While ( Less equal (i, 100) )
           Colorfore( Int div(i,11) Plus '91' )
           Print ( [ Intdiv(i,11) Plus(1)] Get 'map' )
       Next
       Prnl
   Next
   Prnl
End

AWK

Translation of: COBOL
# syntax: GAWK -f JULIA_SET.AWK [real imaginary]
BEGIN {
    c_real      = (ARGV[1] != "") ? ARGV[1] : -0.8
    c_imaginary = (ARGV[2] != "") ? ARGV[2] : 0.156
    printf("%s %s\n",c_real,c_imaginary)
    for (v=-100; v<=100; v+=10) {
      for (h=-280; h<=280; h+=10) {
        x = h / 200
        y = v / 100
        plot_char = "#"
        for (i=1; i<=50; i++) {
          z_real = x * x - y * y + c_real
          z_imaginary = x * y * 2 + c_imaginary
          if (z_real ^ 2 > 10000) {
            plot_char = " "
            break
          }
          x = z_real
          y = z_imaginary
        }
        printf("%1s",plot_char)
      }
      printf("\n")
    }
    exit(0)
}
Output:
-0.8 0.156



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

BASIC

BBC BASIC

Translation of: VBScript
      DIM Pix&(11)
      $^Pix&(0)="@$%#*+=-:. " : REM Let's inverse :-)
      FOR Y=-1.0 TO 1.0 STEP 1/15
        FOR X=-1.5 TO 1.5 STEP 3/100
          ZR=X
          ZI=Y
          I%=0
          WHILE I% < 100
            ZR1=ZR * ZR - ZI * ZI - .79
            ZI=ZR * ZI * 2 + .15
            ZR=ZR1
            IF ZR * ZR + ZI * ZI > 4 EXIT WHILE
            I%+=1
          ENDWHILE
          VDU Pix&(I% / 10)
        NEXT
        PRINT
      NEXT
Output:
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@$*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%-*= %*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@$$%% #@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%+ #%++#:@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@*% $ = %%%%%$$$#+*#* **%%@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@:%%%. +%%%%%%     :* %$$$@@@@@@@@@@@@@@@@@@%@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ #  :**=- *=+# =  = :   .  %*+@@@@@@@@@%$ .+=%@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@+.+@@@@@@@@@@@@@@@@@$= += = :.:**   =#**-+% +. =:-+@@@@@$%  # %%$$#$@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@$+#$@-$ : @@@@@@@@@@$-      :   :   +% +%%%%%%%%%+=+$@@$#    -* :  +**@@@@@@@@@@@@
@@@@@@@@@@@@@@@$@ .%%$%   #=  +%$$@@@@@$%+.    :=-***  %%%%%%%%%%%%%%#+ $$$    = - =%%%%+ @@=% *@@@@@
@@@@@@@@@@@@@@@$ ==  * =**-#*##+ +-+$$$$$% - +:  *##*:#:%%$$$%%%+ --+##=$$$$%#-  #*%%%%% # $- : +$@@@
@@@@@@-$@@@@@@@%-  =   -%%%%%%%%%%#  $$$$$$%##=+   .#%%%$$$$$$%:*#  =** %$$$%%-    =$$ ##:%%*# $ % $
@@@@@  %- **+$$$* .= **%%%%%%%#=*###*#%$$$$$%%*       *%%$$$$$%#*###*=#%%%%%%%** =. *$$$+** -%  @@@@@
 $ % $ #*%%:## $$=    -%%$$$% **=  #*:%$$$$$$%%%#.   +=##%$$$$$$  #%%%%%%%%%%-   =  -%@@@@@@@$-@@@@@@
@@@$+ : -$ # %%%%%*#  -#%$$$$=##+-- +%%%$$$%%:#:*##*  :+ - %$$$$$+-+ +##*#-**= *  == $@@@@@@@@@@@@@@@
@@@@@* %=@@ +%%%%= - =    $$$ +#%%%%%%%%%%%%%%  ***-=:    .+%$@@@@@$$%+  =#   %$%%. @$@@@@@@@@@@@@@@@
@@@@@@@@@@@@**+  : *-    #$@@$+=+%%%%%%%%%+ %+   :   :      -$@@@@@@@@@@ : $-@$#+$@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@$#$$%% #  %$@@@@@+-:= .+ %+-**#=   **:.: = =+ =$@@@@@@@@@@@@@@@@@+.+@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@%=+. $%@@@@@@@@@+*%  .   : =  = #+=* -=**:  # @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@%@@@@@@@@@@@@@@@@@@$$$% *:     %%%%%%+ .%%%:@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%%** *#*+#$$$%%%%% = $ %*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@:#++%# +%@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@# %%$$@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@*% =*-%@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@*$@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

FreeBASIC

#define pix 1./120
#define zero_x 320
#define zero_y 240
#define maxiter 250

type complex
    r as double
    i as double
end type

operator + (x as complex, y as complex) as complex
    dim as complex ret
    ret.r = x.r + y.r
    ret.i = x.i + y.i
    return ret
end operator

operator * (x as complex, y as complex) as complex
    dim as complex ret
    ret.r = x.r*y.r - x.i*y.i
    ret.i = x.r*y.i + x.i*y.r
    return ret
end operator

operator abs ( x as complex ) as double
    return sqr(x.r*x.r + x.i*x.i)
end operator

dim as complex c, z
dim as integer x, y, iter

input "Real part of c? ", c.r
input "Imaginary part of c? ", c.i

screen 12

for x=0 to 639
   for y=0 to 479
      z.r = (x-zero_x)*pix
      z.i = (y-zero_y)*pix
      for iter=0 to maxiter
          z = z*z + c
          if abs(z)>2 then
              pset(x,y),iter mod 16
              goto cont
          end if
       next iter
       pset(x,y),1
       cont:
    next y
next x

while inkey=""
wend
end


GW-BASIC

10 SCALE# = 1/81 : ZEROX = 160
20 ZEROY = 100 : MAXIT = 32
30 CR# = -.798 : CI# = .1618
40 SCREEN 1
50 FOR X = 0 TO 2*ZEROX - 1
60 FOR Y = 0 TO 2*ZEROY - 1
70 ZR# = (X-ZEROX)*SCALE#
80 ZI# = (ZEROY-Y)*SCALE#
90 FOR I = 1 TO MAXIT
100 BR# = CR# + ZR#*ZR# - ZI#*ZI#
110 ZI# = CI# + 2*ZR#*ZI#
120 ZR# = BR#
130 IF ZR#*ZR# + ZI#*ZI# > 4! THEN GOTO 160
140 NEXT I
150 GOTO 170
160 PSET (X, Y), 1 + (I MOD 3)
170 NEXT Y
180 NEXT X

Liberty BASIC

Translation of: Locomotive Basic

Shades of gray proportional to numbers of iteration are used (differently from the original version).

Works with: Just BASIC
rem Julia set
WindowWidth = 640: WindowHeight = 400
graphicbox #julset.gbox, 0, 0, 639, 399
open "Julia set" for window as #julset
print #julset.gbox, "down"
x0 = -0.512511498387847167 : y0 = 0.521295573094847167
for xp = 0 TO 639
  for yp = 0 TO 399
    x = xp / 213 - 1.5: y = yp / 200 - 1
    iteration = 0
    maxIteration = 100
    while x * x + y * y <= 4 and iteration < maxIteration
      xtemp = x * x - y * y + x0
      y = 2 * x * y + y0
      x = xtemp
      iteration = iteration + 1
    wend
    if iteration <> maxIteration then c = int(iteration * 255 / maxIteration + .5) else c = 0
    print #julset.gbox, "color "; c; " "; c; " "; c
    print #julset.gbox, "set "; xp; " "; yp
  next yp
next xp
wait

Locomotive Basic

Adapted from the Mandelbrot Locomotive Basic program. This program is meant for use in CPCBasic specifically, where it draws a 16-color 640x400 image in less than a minute. (Real CPC hardware would take far longer than that and has lower resolution.)

1 MODE 3    ' Note the CPCBasic-only screen mode!
2 FOR xp = 0 TO 639
3 FOR yp = 0 TO 399
4 x0 = -0.512511498387847167 : y0 = 0.521295573094847167
5 x = xp / 213 - 1.5 : y = yp / 200 - 1
6 iteration = 0
7 maxIteration = 100
8 WHILE (x * x + y * y <= (2 * 2) AND iteration < maxIteration)
9 xtemp = x * x - y * y + x0
10 y = 2 * x * y + y0
11 x = xtemp
12 iteration = iteration + 1
13 WEND
14 IF iteration <> maxIteration THEN c = iteration ELSE c = 0
15 PLOT xp, yp, c MOD 16
16 NEXT
17 NEXT

QBasic

Works with: QBasic
escala = 1 / 81
zeroX = 160
zeroY = 100
maxiter = 32

CR = -.798
CI = .1618

SCREEN 13
FOR x = 0 TO 2 * zeroX - 1
    FOR y = 0 TO 2 * zeroY - 1
        zreal = (x - zeroX) * escala
        zimag = (zeroY - y) * escala
        FOR iter = 1 TO maxiter
            BR = CR + zreal * zreal - zimag * zimag
            zimag = CI + 2 * zreal * zimag
            zreal = BR
            IF zreal * zreal + zimag * zimag > 4 THEN
                PSET (x, y), 1 + (iter MOD 16)
                EXIT FOR
            END IF
        NEXT iter
    NEXT y
NEXT x
END

RapidQ

Translation of: Liberty BASIC
'Julia set
DECLARE SUB PaintCanvas

CREATE Form AS QForm
  ClientWidth  = 640
  ClientHeight = 400
  Caption = "Julia set"
  CREATE Canvas AS QCanvas
    Height = Form.ClientHeight
    Width  = Form.ClientWidth
    OnPaint = PaintCanvas
  END CREATE
END CREATE

SUB PaintCanvas
  X0 = -0.512511498387847167: Y0 = 0.521295573094847167
  FOR XP = 0 TO 639
    FOR YP = 0 TO 399
      X = XP / 213 - 1.5: Y = YP / 200 - 1
      Iteration = 0
      MaxIteration = 100
      WHILE X * X + Y * Y <= 4 AND Iteration < MaxIteration
        XTemp = X * X - Y * Y + X0
        Y = 2 * X * Y + Y0
        X = XTemp
        Iteration = Iteration + 1
      WEND
      IF Iteration <> MaxIteration THEN C = ROUND(Iteration * 255 / MaxIteration) ELSE C = 0
      Canvas.Pset(XP, YP, RGB(C, C, C))
    NEXT YP
  NEXT XP
END SUB

Form.ShowModal

Sinclair ZX81 BASIC

I don't know exactly how long this takes to run; but I left it for about three and a half hours and when I came back it had already finished. If you can't wait to see the results, I've posted a screenshot here. I also haven't tested it with only 1k of RAM—but I suspect it needs at least 2k.

You can try changing lines 10 and 20 to run the program with different values of the complex constant C+D, or lines 50 and 60 to zoom in.

 10 LET C=-.8
 20 LET D=.156
 30 FOR V=43 TO 0 STEP -1
 40 FOR H=0 TO 63
 50 LET X=(H-32)/21
 60 LET Y=(V-22)/21
 70 FOR A=1 TO 50
 80 LET R=X*X-Y*Y+C
 90 LET I=2*X*Y+D
100 IF R*R>1000 THEN GOTO 150
110 LET X=R
120 LET Y=I
130 NEXT A
140 PLOT H,V
150 NEXT H
160 NEXT V

True BASIC

Translation of: QBasic
LIBRARY "GraphLib.tru"

LET escala = 1/81
LET zerox = 160
LET zeroy = 100
LET maxiter = 32
LET cr = -.798
LET ci = .1618

SET WINDOW -10, 640, -10, 320
FOR x = 0 TO 2*zerox-1
    FOR y = 0 TO 2*zeroy-1
        LET zreal = (x-zerox)*escala
        LET zimag = (zeroy-y)*escala
        FOR iter = 1 TO maxiter
            LET br = cr+zreal*zreal-zimag*zimag
            LET zimag = ci+2*zreal*zimag
            LET zreal = br
            IF zreal*zreal+zimag*zimag > 4 THEN
               SET COLOR 4*t_palette+(REMAINDER(iter,16))
               PLOT POINTS: x,y
               EXIT FOR
            END IF
        NEXT iter
    NEXT y
NEXT x
END

VBScript

'ASCII Julia set. Translated from lua. Run with CScript
'Console should be 135x50 to avoid wrapping and scroll

cmap=array(" ", ".", ":", "-", "=", "+", "*", "#", "%", "$", "@" )
for y = -1.0 to 1.0 step 0.05
  for x = -1.5 to 1.5 step 0.025
    zr=x
    zi=y
    i=0
    do while i < 100
       zr1 = zr*zr - zi*zi - 0.79 
       zi=zr * zi * 2 + 0.15
       zr=zr1
      if (zr*zr + zi*zi) > 4. then exit do
      i = i + 1 
    loop 
    wscript.stdout.write cmap(i\10)
  next
  wscript.stdout.write vbcrlf
next
Output:
                                                             .:
                                                          =@=:.#:
                                                           %@=:@%@
                                                           ..::::#.
                                                       :.+=-:+@--%
                                                 =+- .#+@@::::@-....--@:.@..$@
                                                 .@*:.**=@=::::...=@@@*@@::@-#
                                                 :-:::*@@@-:::::--@@%@*+=+::%+:.                   -@+
                                              %@-=@@@==*@**=*@:%#*@@%@@@@@@@*@@#:-.          @:.@@@+:-
                       -                       .$-==@%**@@==--*@@@@====@@@-#=@@@%@:        -@+:%@@:::.
                      @@:@.     .@            @*:=*@%@@@@*++@%@@@@#-#*-::::=:::*@@#+.    .+%@%*@$=+:%%@@=--
                      $-$-..@@#*:@... +        .:=#@@@@@%@@@@@*$#@=:::@::::::::::-+%@.....%@@@@*+##@@=*@@@#
                  ..:@=:::.*@%@=@#%*+:.@.     ..:@@$@@@@%**%==+=*$:::::::::::::::::-+@....@@$@#*@+@@:=::::=-   +:@=
                  .::@@#-:%*@=*@@-=@@=*@@@.......@-@+@*@@*+@=--==:::::::::::::@$=*---@=....=@=@@=-*=:::::::-@.-@@*#@.
                  -+@*@@=+@@@*%::::::::@+*$@......@=+@+@@@@@@--@=@::......:-@@===+*--#@....::@@@@@::...:@=@=+.:@@:::-.%@
        : .+.     =#@@@@@+#@:::::::::::::-=@-.......:*==*#@@@#@@:::.......:-+=-=+%===@::...:::-#%#@+:...@-:::::##@$.@$-
      @@-$=@==@+...-+@@+@==@::::::::-#@@----@=.......::=%@@@@@@@%=::.......=@----@@#-::::::::@==@+@@+-...+@==@=$-@@
  -$@.$@##:::::-@...:+@#%#-:::...::@===%+=-=+-:.......:::@@#@@@#*==*:.......-@=-:::::::::::::@#+@@@@@#=     .+. :
 @%.-:::@@:.+=@=@:...::@@@@@::....@#--*+===@@-:......::@=@--@@@@@@+@+=@......@$*+@::::::::%*@@@+=@@*@+-
    .@#*@@-.@-:::::::=*-=@@=@=....=@---*=$@:::::::::::::==--=@+*@@*@+@-@.......@@@*=@@=-@@*=@*%:-#@@::.
      =@:+   -=::::=:@@+@*#@$@@....@+-:::::::::::::::::$*=+==%**%@@@@$@@:..     .@.:+*%#@=@%@*.:::=@:..
              #@@@*=@@##+*@@@@%.....@%+-::::::::::@:::=@#$*@@@@@%@@@@@#=:.        + ...@:*#@@..-$-$
              --=@@%%:+=$@*%@%+.    .+#@@*:::=::::-*#-#@@@@%@++*@@@@%@*=:*@            @.     .@:@@
                   .:::@@%:+@-        :@%@@@=#-@@@====@@@@*--==@@**%@==-$.                       -
                   -:+@@@.:@          .-:#@@*@@@@@@@%@@*#%:@*=**@*==@@@=-@%
                   +@-                   .:+%::+=+*@%@@--:::::-@@@*:::-:
                                           #-@::@@*@@@=...::::=@=**.:*@.
                                           @$..@.:@--....-@::::@@+#. -+=
                                                       %--@+:-=+.:
                                                      .#::::..
                                                       @%@:=@%
                                                        :#.:=@=
                                                          :.

Yabasic

escala = 1/120
zeroX = 320
zeroY = 240 
maxiter = 32

CR = -.798 
CI = .1618

clear screen 
open window 640, 480
for x = 0 to 2*zeroX - 1
    for y = 0 to 2*zeroY - 1
        zreal = (x - zeroX) * escala
        zimag = (zeroY - y) * escala
        for iter = 1 to maxiter
            BR = CR + zreal*zreal - zimag*zimag
            zimag = CI + 2*zreal*zimag
            zreal = BR
            if zreal*zreal + zimag*zimag > 4 then 
                dot x, y
                break
            end if
        next iter
    next y
next x
end

ZX Spectrum Basic

Translation of: Sinclair ZX81 BASIC

Higher resolution is obtainable, if you have the time to wait for it.

 10 LET creal=-0.8
 20 LET cimag=0.156
 30 FOR v=-16 TO 16
 40 FOR h=-64 TO 64
 50 LET x=h/40
 60 LET y=v/20
 70 FOR i=1 TO 50
 80 LET zreal=x*x-y*y+creal
 90 LET zimag=x*y*2+cimag
100 IF zreal*zreal>1000 THEN GO TO 150
110 LET x=zreal
120 LET y=zimag
130 NEXT i
140 PLOT h+100,150-v
150 NEXT h
160 NEXT v
Output:

Screenshot here.

C

Interactive implementation which takes the following 6 parameters as input :

<executable name> <width of graphics window> <height of graphics window> <real part of complex number> <imag part of complex number> <limiting radius> <Number of iterations to be tested>

Prints out usage on incorrect invocation. Requires the WinBGIm library.

#include<graphics.h>
#include<stdlib.h>
#include<math.h>

typedef struct{
	double x,y;
}complex;

complex add(complex a,complex b){
	complex c;
	c.x = a.x + b.x;
	c.y = a.y + b.y;
	return c;
}

complex sqr(complex a){
	complex c;
	c.x = a.x*a.x - a.y*a.y;
	c.y = 2*a.x*a.y;
	return c;
}

double mod(complex a){
	return sqrt(a.x*a.x + a.y*a.y);
}

complex mapPoint(int width,int height,double radius,int x,int y){
	complex c;
	int l = (width<height)?width:height;
	
	c.x = 2*radius*(x - width/2.0)/l;
	c.y = 2*radius*(y - height/2.0)/l;
	
	return c;
}

void juliaSet(int width,int height,complex c,double radius,int n){
	int x,y,i;
	complex z0,z1;
	
	for(x=0;x<=width;x++)
		for(y=0;y<=height;y++){
			z0 = mapPoint(width,height,radius,x,y);
			for(i=1;i<=n;i++){
				z1 = add(sqr(z0),c);
				if(mod(z1)>radius){
					putpixel(x,y,i%15+1);
					break;
				}
				z0 = z1;
			}
			if(i>n)
				putpixel(x,y,0);
		}
}

int main(int argC, char* argV[])
{
	int width, height;
	complex c;
	
	if(argC != 7)
		printf("Usage : %s <width and height of screen, real and imaginary parts of c, limit radius and iterations>");
	else{
		width = atoi(argV[1]);
		height = atoi(argV[2]);
		
		c.x = atof(argV[3]);
		c.y = atof(argV[4]);
		
		initwindow(width,height,"Julia Set");
		juliaSet(width,height,c,atof(argV[5]),atoi(argV[6]));
		
		getch();
	}
	
	return 0;
}

C#

Translation of: Python
using System.Drawing;
// Note: You have to add the System.Drawing assembly 
//  (right-click "references," Add Reference, Assemblies, Framework,
//    System.Drawing, OK)
using System.Linq;

namespace RosettaJuliaSet
{
    class Program
    {
        static void Main(string[] args)
        {
            const int w = 800;
            const int h = 600;
            const int zoom = 1;
            const int maxiter = 255;
            const int moveX = 0;
            const int moveY = 0;
            const double cX = -0.7;
            const double cY = 0.27015;
            double zx, zy, tmp;
            int i;

            var colors = (from c in Enumerable.Range(0, 256)
                          select Color.FromArgb((c >> 5) * 36, (c >> 3 & 7) * 36, (c & 3) * 85)).ToArray();

            var bitmap = new Bitmap(w, h);
            for (int x = 0; x < w; x++)
            {
                for (int y = 0; y < h; y++)
                {
                    zx = 1.5 * (x - w / 2) / (0.5 * zoom * w) + moveX;
                    zy = 1.0 * (y - h / 2) / (0.5 * zoom * h) + moveY;
                    i = maxiter;
                    while (zx * zx + zy * zy < 4 && i > 1)
                    {
                        tmp = zx * zx - zy * zy + cX;
                        zy = 2.0 * zx * zy + cY;
                        zx = tmp;
                        i -= 1;
                    }
                    bitmap.SetPixel(x, y, colors[i]);
                }
            }
            bitmap.Save("julia-set.png");
        }
    }
}

C# also makes it relatively easy to do a multi-threaded version, which should run faster than the above:

        public struct CalculatedPoint
        {
            public int x;
            public int y;
            public int i;
        }

        static void MultiThreaded()
        {
            const int w = 800;
            const int h = 600;
            const int zoom = 1;
            const int maxiter = 255;
            const int moveX = 0;
            const int moveY = 0;
            const double cX = -0.7;
            const double cY = 0.27015;

            // Precalculate a pallette of 256 colors
            var colors = (from c in Enumerable.Range(0, 256)
                          select Color.FromArgb((c >> 5) * 36, (c >> 3 & 7) * 36, (c & 3) * 85)).ToArray();

            // The "AsParallel" below invokes PLINQ, making evaluation parallel using as many cores as
            // are available.
            var calculatedPoints = Enumerable.Range(0, w * h).AsParallel().Select(xy =>
              {
                  double zx, zy, tmp;
                  int x, y;
                  int i = maxiter;
                  y = xy / w;
                  x = xy % w;
                  zx = 1.5 * (x - w / 2) / (0.5 * zoom * w) + moveX;
                  zy = 1.0 * (y - h / 2) / (0.5 * zoom * h) + moveY;
                  while (zx * zx + zy * zy < 4 && i > 1)
                  {
                      tmp = zx * zx - zy * zy + cX;
                      zy = 2.0 * zx * zy + cY;
                      zx = tmp;
                      i -= 1;
                  }
                  return new CalculatedPoint { x = x, y = y, i = i };
              });

            // Bitmap is not multi-threaded, so main thread needs to read in the results as they
            // come in and plot the pixels.
            var bitmap = new Bitmap(w, h);
            foreach (CalculatedPoint cp in calculatedPoints)
                bitmap.SetPixel(cp.x, cp.y, colors[cp.i]);
            bitmap.Save("julia-set-multi.png");
        }

C++

Version 1 (windows.h)

Note: Will only run on Windows. For the cross-platform version that can be run on different OSes, see Version 2.

#include <windows.h>
#include <string>
#include <complex>

const int BMP_SIZE = 600, ITERATIONS = 512;
const long double FCT = 2.85, hFCT = FCT / 2.0;

class myBitmap {
public:
    myBitmap() : pen( NULL ), brush( NULL ), clr( 0 ), wid( 1 ) {}
    ~myBitmap() {
        DeleteObject( pen ); DeleteObject( brush );
        DeleteDC( hdc ); DeleteObject( bmp );
    }
    bool create( int w, int h ) {
        BITMAPINFO bi;
        ZeroMemory( &bi, sizeof( bi ) );
        bi.bmiHeader.biSize        = sizeof( bi.bmiHeader );
        bi.bmiHeader.biBitCount    = sizeof( DWORD ) * 8;
        bi.bmiHeader.biCompression = BI_RGB;
        bi.bmiHeader.biPlanes      = 1;
        bi.bmiHeader.biWidth       =  w;
        bi.bmiHeader.biHeight      = -h;
        HDC dc = GetDC( GetConsoleWindow() );
        bmp = CreateDIBSection( dc, &bi, DIB_RGB_COLORS, &pBits, NULL, 0 );
        if( !bmp ) return false;
        hdc = CreateCompatibleDC( dc );
        SelectObject( hdc, bmp );
        ReleaseDC( GetConsoleWindow(), dc );
        width = w; height = h;
        return true;
    }
    void clear( BYTE clr = 0 ) {
        memset( pBits, clr, width * height * sizeof( DWORD ) );
    }
    void setBrushColor( DWORD bClr ) {
        if( brush ) DeleteObject( brush );
        brush = CreateSolidBrush( bClr );
        SelectObject( hdc, brush );
    }
    void setPenColor( DWORD c ) {
        clr = c; createPen();
    }
    void setPenWidth( int w ) {
        wid = w; createPen();
    }
    void saveBitmap( std::string path ) {
        BITMAPFILEHEADER fileheader;
        BITMAPINFO       infoheader;
        BITMAP           bitmap;
        DWORD            wb;
        GetObject( bmp, sizeof( bitmap ), &bitmap );
        DWORD* dwpBits = new DWORD[bitmap.bmWidth * bitmap.bmHeight];
        ZeroMemory( dwpBits, bitmap.bmWidth * bitmap.bmHeight * sizeof( DWORD ) );
        ZeroMemory( &infoheader, sizeof( BITMAPINFO ) );
        ZeroMemory( &fileheader, sizeof( BITMAPFILEHEADER ) );
        infoheader.bmiHeader.biBitCount = sizeof( DWORD ) * 8;
        infoheader.bmiHeader.biCompression = BI_RGB;
        infoheader.bmiHeader.biPlanes = 1;
        infoheader.bmiHeader.biSize = sizeof( infoheader.bmiHeader );
        infoheader.bmiHeader.biHeight = bitmap.bmHeight;
        infoheader.bmiHeader.biWidth = bitmap.bmWidth;
        infoheader.bmiHeader.biSizeImage = bitmap.bmWidth * bitmap.bmHeight * sizeof( DWORD );
        fileheader.bfType    = 0x4D42;
        fileheader.bfOffBits = sizeof( infoheader.bmiHeader ) + sizeof( BITMAPFILEHEADER );
        fileheader.bfSize    = fileheader.bfOffBits + infoheader.bmiHeader.biSizeImage;
        GetDIBits( hdc, bmp, 0, height, ( LPVOID )dwpBits, &infoheader, DIB_RGB_COLORS );
        HANDLE file = CreateFile( path.c_str(), GENERIC_WRITE, 0, NULL, CREATE_ALWAYS, 
            FILE_ATTRIBUTE_NORMAL, NULL );
        WriteFile( file, &fileheader, sizeof( BITMAPFILEHEADER ), &wb, NULL );
        WriteFile( file, &infoheader.bmiHeader, sizeof( infoheader.bmiHeader ), &wb, NULL );
        WriteFile( file, dwpBits, bitmap.bmWidth * bitmap.bmHeight * 4, &wb, NULL );
        CloseHandle( file );
        delete [] dwpBits;
    }
    HDC getDC() const     { return hdc; }
    int getWidth() const  { return width; }
    int getHeight() const { return height; }
    DWORD* bits() const { return ( DWORD* )pBits; }
private:
    void createPen() {
        if( pen ) DeleteObject( pen );
        pen = CreatePen( PS_SOLID, wid, clr );
        SelectObject( hdc, pen );
    }
    HBITMAP bmp; HDC    hdc;
    HPEN    pen; HBRUSH brush;
    void    *pBits; int    width, height, wid;
    DWORD    clr;
};
class julia {
public:
    void draw( std::complex<long double> k ) {
        bmp.create( BMP_SIZE, BMP_SIZE );
        DWORD* bits = bmp.bits();
        int res, pos;
        std::complex<long double> c, factor( FCT / BMP_SIZE, FCT / BMP_SIZE ) ;

        for( int y = 0; y < BMP_SIZE; y++ ) {
            pos = y * BMP_SIZE;

            c.imag( ( factor.imag() * y ) + -hFCT );

            for( int x = 0; x < BMP_SIZE; x++ ) {
                c.real( factor.real() * x + -hFCT );
                res = inSet( c, k );
                if( res ) {
                    int n_res = res % 255;
                    if( res < ( ITERATIONS >> 1 ) ) res = RGB( n_res << 2, n_res << 3, n_res << 4 );
                    else res = RGB( n_res << 4, n_res << 2, n_res << 5 );
                }
                bits[pos++] = res;
            }
        }
        bmp.saveBitmap( "./js.bmp" );
    }
private:
    int inSet( std::complex<long double> z, std::complex<long double> c ) {
        long double dist;//, three = 3.0;
        for( int ec = 0; ec < ITERATIONS; ec++ ) {
            z = z * z; z = z + c;
            dist = ( z.imag() * z.imag() ) + ( z.real() * z.real() );
            if( dist > 3 ) return( ec );
        }
        return 0;
    }
    myBitmap bmp;
};
int main( int argc, char* argv[] ) {
    std::complex<long double> c;
    long double factor = FCT / BMP_SIZE;
    c.imag( ( factor * 184 ) + -1.4 );
    c.real( ( factor * 307 ) + -2.0 );
    julia j; j.draw( c ); return 0;    
}

Version 2 (SDL2)

Library: SDL2

Source: https://gist.github.com/KatsumiKougen/74468b3c1c4b9844f6f77a2922f588f9

/************************************************************
 *                     JULIA SET  IN C++                    *
 *                    Library used:  SDL2                   *
 * Written by Katsumi -- https://twitter.com/realKatsumi_vn *
 ************************************************************/

// Standard C++ stuff
#include <iostream>
#include <complex>
#include <vector>
#include <array>

// SDL2 stuff
#include "SDL2/SDL.h"

// Other crazy stuffs
#define ScreenWidth  800
#define ScreenHeight 600

// Compile: g++ -std=c++20 -Wall -Wextra -pedantic julia-set-sdl2.cpp -o julia-set-sdl2 -lSDL2
// Yes, I use the British spelling, it's "colour" not "color". Deal with it.

void DrawJuliaSet(SDL_Renderer *r, int width, int height, double real, double imag, int maxiter) {
    // Generate colours
    std::vector<std::array<int, 3>> colours;
    for (int col = 0; col < 256; col++) {
        std::array<int, 3> CurrentColour = {(col >> 5) * 36, (col >> 3 & 7) * 36, (col & 3) * 85};
        colours.push_back(CurrentColour);
    }
    
    std::complex<double> c = {real, imag}, z;
    
    // Actual calculations
    for (int x = 0; x < width; x++) {
        for (int y = 0; y < height; y++) {
            z.real(1.5 * (x - width / 2) / (0.5 * width));
            z.imag((y - height / 2) / (0.5 * height));
            
            int i = maxiter;
            
            while (std::norm(z) < 4 && i > 0) {
                z = z * z + c;
                i--;
            }
            
            // Draw the set on the window, pixel by pixel
            SDL_SetRenderDrawColor(r, colours[i][0], colours[i][1], colours[i][2], 0xff);
            SDL_RenderDrawPoint(r, x, y);
        }
    }
}

int main(int argc, char *args[]) {
    const int MaximumIterations = 256;    
    
    SDL_Window *window = NULL; // Define window
    SDL_Renderer *renderer = NULL; // Define renderer
    
    // First things first: initialise video
    SDL_Init(SDL_INIT_EVERYTHING);
    
    window = SDL_CreateWindow( // Create window
        "Julia set - Press any key to exit",
        SDL_WINDOWPOS_UNDEFINED,
        SDL_WINDOWPOS_UNDEFINED,
        ScreenWidth, ScreenHeight, // Width and height
        SDL_WINDOW_SHOWN // Always show the window
    );
    
    renderer = SDL_CreateRenderer(window, -1, SDL_RENDERER_ACCELERATED); // Create renderer
    
    SDL_SetRenderDrawColor(renderer, 0xff, 0xff, 0xff, 0xff);
    SDL_RenderClear(renderer); // Clear screen
    
    DrawJuliaSet(renderer, ScreenWidth, ScreenHeight, -0.7, 0.27015, MaximumIterations); // Draw the Julia set
    SDL_RenderPresent(renderer); // Render it!
    
    // Create an event handler and a "quit" flag
    SDL_Event e;
    bool KillWindow = false;
    
    while (!KillWindow) { // The window runs until the "quit" flag is set to true
        while (SDL_PollEvent(&e) != 0) {
            switch (e.type) { // Go through the events in the queue
                case SDL_QUIT: case SDL_KEYDOWN: // Event: user hits a key
                    // Destroy window
                    KillWindow = true;
                    break;
            }
        }
    }
    
    SDL_DestroyRenderer(renderer); // Destroy renderer
    SDL_DestroyWindow(window); // Destroy window
    SDL_Quit();
    
    return 0;
}
Output:

COBOL

Plots—in ASCII or EBCDIC art—a Julia set for the function f(z) = z2 + c, based on a value of c input by the user (real part then imaginary part, pressing the carriage return key after each). The sample output is for the inputs -0.8 and 0.156.

IDENTIFICATION DIVISION.
PROGRAM-ID. JULIA-SET-PROGRAM.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  WS-COMPLEX-CONSTANT.
    05 C-REAL             PIC S9V999.
    05 C-IMAGINARY        PIC S9V999.
01  WS-ARGAND-PLANE.
    05 X                  PIC S9(9)V999.
    05 Y                  PIC S9(9)V999.
01  WS-COMPLEX-VARIABLE.
    05 Z-REAL             PIC S9(9)V999.
    05 Z-IMAGINARY        PIC S9(9)V999.
01  WS-TEMPORARY-RESULTS.
    05 X-SQUARED          PIC S9(9)V999.
    05 Y-SQUARED          PIC S9(9)V999.
    05 X-TIMES-Y          PIC S9(9)V999.
    05 Z-REAL-SQUARED     PIC S9(9)V999.
01  WS-LOOP-COUNTERS.
    05 HORIZONTAL         PIC 999.
    05 VERTICAL           PIC 999.
    05 ITERATIONS         PIC 99.
77  WS-PLOT-CHARACTER     PIC X.
PROCEDURE DIVISION.
INPUT-COMPLEX-CONSTANT-PARAGRAPH.
    ACCEPT C-REAL      FROM CONSOLE.
    ACCEPT C-IMAGINARY FROM CONSOLE.
CONTROL-PARAGRAPH.
    PERFORM OUTER-LOOP-PARAGRAPH  VARYING VERTICAL   FROM 1 BY 10
    UNTIL VERTICAL IS GREATER THAN 320.
    STOP RUN.
OUTER-LOOP-PARAGRAPH.
    PERFORM COMPUTATION-PARAGRAPH VARYING HORIZONTAL FROM 1 BY 10
    UNTIL HORIZONTAL IS GREATER THAN 560.
    DISPLAY '' UPON CONSOLE.
COMPUTATION-PARAGRAPH.
    SUBTRACT 280   FROM HORIZONTAL GIVING X.
    SUBTRACT 160   FROM VERTICAL   GIVING Y.
    DIVIDE   X     BY   200        GIVING X.
    DIVIDE   Y     BY   100        GIVING Y.
    MOVE     '#'   TO   WS-PLOT-CHARACTER.
    PERFORM COMPLEX-MULTIPLICATION-PARAGRAPH
    VARYING ITERATIONS FROM   1  BY      1
    UNTIL   ITERATIONS        IS GREATER THAN 50
    OR      WS-PLOT-CHARACTER IS EQUAL   TO   SPACE.
    DISPLAY WS-PLOT-CHARACTER UPON CONSOLE WITH NO ADVANCING.
COMPLEX-MULTIPLICATION-PARAGRAPH.
    MULTIPLY X         BY   X         GIVING X-SQUARED.
    MULTIPLY Y         BY   Y         GIVING Y-SQUARED.
    SUBTRACT Y-SQUARED FROM X-SQUARED GIVING Z-REAL.
    ADD      C-REAL    TO   Z-REAL.
    MULTIPLY X         BY   Y         GIVING X-TIMES-Y.
    MULTIPLY X-TIMES-Y BY   2         GIVING Z-IMAGINARY.
    ADD C-IMAGINARY    TO   Z-IMAGINARY.
    MULTIPLY Z-REAL    BY   Z-REAL    GIVING Z-REAL-SQUARED.
    IF  Z-REAL-SQUARED IS   GREATER   THAN   10000 THEN
    MOVE SPACE         TO   WS-PLOT-CHARACTER.
    MOVE Z-REAL        TO   X.
    MOVE Z-IMAGINARY   TO   Y.
Output:
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
                            ###                         
                          ## ##                         
                       # ###   #### #                   
                      ################        ###       
         #    #      # ############### #    #######     
       ##   #####      ######## #       #  #####      ##
       ########  ###    ########    # ###   ### # ##  # 
  ## #  ####     # #    # ####      #        ####  ### #
  # #   ###      # #     #########    # ## ######       
  #  #########  #         #########    ######  #        
     ### ###     ## ## ############           #         
       #   #     ######### ## ## #                      
                    #####    ####                       
                           # #                          
                          ###                           
                           #                            
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        

Crystal

Translation of: Ruby
require "complex"

def julia(c_real, c_imag)
  puts Complex.new(c_real, c_imag)
  -1.0.step(to: 1.0, by: 0.04) do |v|
    puts -1.4.step(to: 1.4, by: 0.02).map{|h| judge(c_real, c_imag, h, v)}.join
  end
end
 
def judge(c_real, c_imag, x, y)
  50.times do
    z_real = (x * x - y * y) + c_real
    z_imag = x * y * 2 + c_imag
    return " "  if z_real**2 > 10000
    x, y = z_real, z_imag
  end
  "#"
end
 
julia(-0.8, 0.156)
Output:
-0.8 + 0.156i
                                                                                                                                            
                                                                                                                                            
                                                                                                                                            
                                                                                                                                            
                                                                        #                                                                   
                                                                         #                                                                  
                                                                      ##                                                                    
                                                                     #######                                                                
                                                                      ##  ####                                                              
                                                                            ##                                                              
                                                                # ####  ##  #                                                               
                                                        #      #  ###   ###       # ##     #                                                
                                                         #    ######          ##########  # #                                               
                                                         # #   ######       ########## #                                                    
                                                         #      ###  ### # ############  ######                         #                   
                                                        ################   ###################   #               #   ###  #                 
                                                         ################ #################### ##              #  ###   ##                  
                         ##                            ##############################    ###  #### #          #######     ###               
                       #  ##        ##               #  #####################  # #### ##    #### ###        ########### ######              
                       # #    #####                     #####################     #              # ##       ######################          
                     ###    ####### ####  #            #######################    #                ###      ############  ###   ##      ##  
                  ## ##  ## #################          ########################                     ###      ###########         ##   ### ##
                  #################  ##  ###### #        # ################### #             #####   ##       ######## #      ### #  ###### 
                  ############  ## ##       # ###            ##############   #            ##  ###   ##       #   #### #      # ##     ###  
        ##        ###########  ##             ####          #############    ## #         ##   ### ##         ## #######      ##      ##### 
     #########    #############                 ###           #  # ####### #  #           ###                 #############    #########    
  #####      ##      ####### ##         ## ###   ##         # ##    #############          ####             ##  ###########        ##       
   ###     ## #      # ####   #       ##   ###  ##            #   ##############            ### #       ## ##  ############                 
  ######  # ###      # ########       ##   #####             # ################### #        # ######  ##  #################                 
### ###   ##         ###########      ###                     ########################          ################# ##  ## ##                 
   ##      ##   ###  ############      ###                #    #######################            #  #### #######    ###                    
           ######################       ## #              #     #####################                     #####    # #                      
               ###### ###########        ### ####    ## #### #  #####################  #               ##        ##  #                      
                ###     #######          # ####  ###    ##############################                            ##                        
                   ##   ###  #              ## #################### ################                                                        
                  #  ###   #               #   ###################   ################                                                       
                    #                         ######  ############ # ###  ###      #                                                        
                                                     # ##########       ######   # #                                                        
                                                # #  ##########          ######    #                                                        
                                                 #     ## #       ###   ###  #      #                                                       
                                                                #  ##  #### #                                                               
                                                               ##                                                                           
                                                               ####  ##                                                                     
                                                                 #######                                                                    
                                                                     ##                                                                     
                                                                   #                                                                        
                                                                    #                                                                       
                                                                                                                                            

Delphi

Translation of: C#
program Julia_set;

{$APPTYPE CONSOLE}

uses
  System.SysUtils,
  Winapi.Windows,
  Vcl.Graphics;

var
  Colors: array[0..255] of TColor;
  w, h, zoom, maxiter, moveX, moveY: Integer;
  cX, cY, zx, zy, tmp: Double;
  i: Integer;
  bitmap: TBitmap;
  x, y: Integer;

begin
  w := 800;
  h := 600;
  zoom := 1;
  maxiter := 255;
  moveX := 0;
  moveY := 0;
  cX := -0.7;
  cY := 0.27015;
  bitmap := TBitmap.Create();
  bitmap.SetSize(w, h);
  bitmap.Canvas.Brush.Color := clwhite;
  bitmap.Canvas.FillRect(bitmap.Canvas.ClipRect);

  for i := 0 to 255 do
    Colors[i] := RGB((i shr 5) * 36, ((i shr 3) and 7) * 36, (i and 3) * 85);

  for x := 0 to w - 1 do
  begin
    for y := 0 to h - 1 do
    begin
      zx := 1.5 * (x - w / 2) / (0.5 * zoom * w) + moveX;
      zy := 1.0 * (y - h / 2) / (0.5 * zoom * h) + moveY;
      i := maxiter;
      while (zx * zx + zy * zy < 4) and (i > 1) do
      begin
        tmp := zx * zx - zy * zy + cX;
        zy := 2.0 * zx * zy + cY;
        zx := tmp;
        i := i - 1;
      end;
      bitmap.Canvas.Pixels[x, y] := colors[i];
    end;
  end;

  bitmap.SaveToFile('julia-set.bmp');
  bitmap.Free;
end.

EasyLang

Run it

cx = -0.7
cy = 0.27015
for y = 0 to 299
  for x = 0 to 299
    zx = (x - 150) / 100
    zy = (y - 150) / 150
    color3 0 0 0
    for iter = 0 to 127
      if zx * zx + zy * zy > 4
        color3 iter / 16 0 0
        break 1
      .
      h = zx * zx - zy * zy + cx
      zy = 2 * zx * zy + cy
      zx = h
    .
    move x / 3 y / 3
    rect 0.4 0.4
  .
.

Elixir

Translation of: AWK
defmodule Julia do
  def set(c_real, c_imag) do
    IO.puts "#{c_real}, #{c_imag}"
    vlist = Enum.take_every(-100..100, 4)
    hlist = Enum.take_every(-280..280, 4)
    Enum.each(vlist, fn v ->
      Enum.map(hlist, fn h ->
        loop(c_real, c_imag, h/200, v/100, "#", 0)
      end) |> IO.puts
    end)
  end
  
  defp loop(_, _, _, _, char, i) when i>=50, do: char
  defp loop(_, _, _, _, " ", _), do: " "
  defp loop(c_real, c_imag, x, y, char, i) do
    z_real = (x * x - y * y) + c_real
    z_imag = x * y * 2 + c_imag
    char = if z_real * z_real > 10000, do: " ", else: char
    loop(c_real, c_imag, z_real, z_imag, char, i+1)
  end
end

c_real = if r=Enum.at(System.argv, 0), do: Float.parse(r) |> elem(0), else: -0.8
c_imag = if c=Enum.at(System.argv, 1), do: Float.parse(c) |> elem(0), else: 0.156
Julia.set(c_real, c_imag)
Output:
-0.8, 0.156
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                        #                                                                    
                                                                         #                                                                   
                                                                      ##                                                                     
                                                                     #######                                                                 
                                                                      ##  ####                                                               
                                                                            ##                                                               
                                                                # ####  ##  #                                                                
                                                        #      #  ###   ###       # ##     #                                                 
                                                         #    ######          ##########  # #                                                
                                                         # #   ######       ########## #                                                     
                                                         #      ###  ### # ############  ######                         #                    
                                                        ################   ###################   #               #   ###  #                  
                                                         ################ #################### ##              #  ###   ##                   
                         ##                            ##############################    ###  #### #          #######     ###                
                       #  ##        ##               #  #####################  # #### ##    #### ###        ########### ######               
                       # #    #####                     #####################     #              # ##       ######################           
                     ###    ####### ####  #            #######################    #                ###      ############  ###   ##      ##   
                  ## ##  ## #################          ########################                     ###      ###########         ##   ### ###
                  #################  ##  ###### #        # ################### #             #####   ##       ######## #      ### #  ######  
                  ############  ## ##       # ###            ##############   #            ##  ###   ##       #   #### #      # ##     ###   
        ##        ###########  ##             ####          #############    ## #         ##   ### ##         ## #######      ##      #####  
     #########    #############                 ###           #  # ####### #  #           ###                 #############    #########     
  #####      ##      ####### ##         ## ###   ##         # ##    #############          ####             ##  ###########        ##        
   ###     ## #      # ####   #       ##   ###  ##            #   ##############            ### #       ## ##  ############                  
  ######  # ###      # ########       ##   #####             # ################### #        # ######  ##  #################                  
### ###   ##         ###########      ###                     ########################          ################# ##  ## ##                  
   ##      ##   ###  ############      ###                #    #######################            #  #### #######    ###                     
           ######################       ## #              #     #####################                     #####    # #                       
               ###### ###########        ### ####    ## #### #  #####################  #               ##        ##  #                       
                ###     #######          # ####  ###    ##############################                            ##                         
                   ##   ###  #              ## #################### ################                                                         
                  #  ###   #               #   ###################   ################                                                        
                    #                         ######  ############ # ###  ###      #                                                         
                                                     # ##########       ######   # #                                                         
                                                # #  ##########          ######    #                                                         
                                                 #     ## #       ###   ###  #      #                                                        
                                                                #  ##  #### #                                                                
                                                               ##                                                                            
                                                               ####  ##                                                                      
                                                                 #######                                                                     
                                                                     ##                                                                      
                                                                   #                                                                         
                                                                    #                                                                        
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             


Emacs Lisp

; === Graphical Julia set display in Emacs =====================

(setq julia-size (cons 300 200))
(setq xmin -1.5)
(setq xmax 1.5)
(setq ymin -1)
(setq ymax 1)
(setq julia0 (cons -0.512511498387847167 0.521295573094847167))
(setq max-iter 100)

(defun julia-iter-point (x y)
  "Run the actual iteration for each point."
  (let ((xp x)
        (yp y)
        (it 0)
        (xt 0))
    (while (and (< (+ (* xp xp) (* yp yp)) 4) (< it max-iter))
      (setq xt (+ (* xp xp) (* -1 yp yp) (car julia0)))
      (setq yp (+ (* 2 xp yp) (cdr julia0)))
      (setq xp xt)
      (setq it (1+ it)))
    it))

(defun julia-iter (p)
  "Return string for point based on whether inside/outside the set."
  (let ((it (julia-iter-point (car p) (cdr p))))
    (if (= it max-iter) "*" (if (cl-oddp it) "+" "-"))))

(defun julia-pos (x y)
  "Convert screen coordinates to input coordinates."
  (let ((xp (+ xmin (* (- xmax xmin) (/ (float x) (car julia-size)))))
        (yp (+ ymin (* (- ymax ymin) (/ (float y) (cdr julia-size))))))
       (cons xp yp)))

(defun string-to-image (str)
  "Convert image data string to XPM image with three colors."
  (create-image (concat (format "/* XPM */
static char * julia[] = {
\"%i %i 3 1\",
\"+      c #ff0000\",
\"-      c #0000ff\",
\"*      c #000000\"," (car julia-size) (cdr julia-size))
    str "};") 'xpm t))

(defun julia-pic ()
  "Plot the Julia set in color."
  (setq all "")
  (dotimes (y (cdr julia-size))
    (setq line "")
    (dotimes (x (car julia-size))
      (setq line (concat line (julia-iter (julia-pos x y)))))
    (setq all (concat all "\"" line "\",\n")))
  (insert-image (string-to-image all)))

(julia-pic)

F#

Basic generation code

let getJuliaValues width height centerX centerY zoom maxIter =
  let initzx x = 1.5 * float(x - width/2) / (0.5 * zoom * float(width))
  let initzy y = 1.0 * float(y - height/2) / (0.5 * zoom * float(height))
  let calc y x =
    let rec loop i zx zy =
      if i=maxIter then 0
      elif zx*zx + zy*zy >= 4.0 then i
      else loop (i + 1) (zx*zx - zy*zy + centerX) (2.0*zx*zy + centerY)
    loop 0 (initzx x) (initzy y)
  [0..height-1] |> List.map(fun y->[0..width-1] |> List.map (calc y))

Text display

getJuliaValues 80 25 -0.7 0.27015 1.0 50
|> List.map(fun row-> row |> List.map (function | 0 ->" " |_->".") |> String.concat "")
|> List.iter (printfn "%s")
Output:
................................................................................
.......................................... .....................................
........................................   .....................................
.........................................    ...................................
......................................        ..................................
...................................          .....   ...........................
..................................   .         .     .   ...... .    ...........
................................... .....     ..        ...... .    . ..........
................. ....... .............                  .. ....      . ........
.................    . .  ... ............                      .        .. ....
..............        .   .   ..  .     .                                .     .
.................                         ..                  .  ..       ......
....... .. . ....                                               .... . .. ......
.......       ..  .                  ..                         ................
..     .                                .     .  ..   .   .        .............
..... ..        .                      ............ ...  . .    ................
......... .      .... ..                  ............. ....... ................
........... .    . ......        ..     ..... ..................................
............    . ......   .     .         .   .................................
............................   .....          ..................................
...................................        .....................................
....................................    ........................................
......................................   .......................................
...................................... .........................................
................................................................................

Graphic Display

open System.Drawing 
open System.Windows.Forms

let showGraphic (colorForIter: int -> Color) width height centerX centerY zoom maxIter =
  new Form()
  |> fun frm ->
    frm.Width <- width
    frm.Height <- height
    frm.BackgroundImage <- 
      new Bitmap(width,height)
      |> fun bmp ->
        getJuliaValues width height centerX centerY zoom maxIter
        |> List.mapi (fun y row->row |> List.mapi (fun x v->((x,y),v))) |> List.collect id
        |> List.iter (fun ((x,y),v) -> bmp.SetPixel(x,y,(colorForIter v)))
        bmp
    frm.Show()

let toColor = (function | 0 -> (0,0,0) | n -> ((31 &&& n) |> fun x->(0, 18 + x * 5, 36 + x * 7))) >> Color.FromArgb

showGraphic toColor 640 480 -0.7 0.27015 1.0 5000

Fortran

Fortran 77 version using ASCII art for the display.

Use the PARAMETER statement, on line 4, to modify the display. C is the seed.
The procedure calls, on lines 12 and 13, control the display window on the complex plane.

C     ==================================================================
      PROGRAM JULIA
C     ------------------------------------------------------------------
      INTEGER    NMAP,NROW,NCOL
      COMPLEX*16 C
      PARAMETER(NMAP=11,NROW=40,NCOL=100,C=(-0.798D0,0.1618D0))
      CHARACTER*1 MAP(NMAP)
      DATA MAP /' ','.',':','-','=','+','*','#','%','$','@'/
      REAL*8      X(NCOL), Y(NROW)
      INTEGER     IR, IC, I, J, MX
      CHARACTER*1 CLR, LINE(NCOL)
      COMPLEX*16  Z

      MX = (NMAP-1)*5
      CALL LINSPACE( NCOL, X, -1.5D0,  1.5D0 )
      CALL LINSPACE( NROW, Y,  1.0D0, -1.0D0 )

      WRITE (*,*) C

      DO 110 IR=1,NROW
         DO 100 IC=1,NCOL
            Z = DCMPLX( X(IC), Y(IR) )
            I  = 1
            CLR = ' '
 10         CONTINUE
            Z = Z*Z + C
            IF ( 2.0D0 .LT. CDABS(Z) ) THEN
               CLR = MAP(MOD(I,NMAP-1)+1)
               GOTO 20
            END IF
            I = I + 1
            IF ( MX .GT. I ) GOTO 10
 20         CONTINUE
            LINE(IC) = CLR
 100     CONTINUE
         WRITE(*,*) (LINE(J),J=1,NCOL)
 110  CONTINUE
      
      STOP
      END

C     ==================================================================
      SUBROUTINE LINSPACE( N, A, S, F )
C     ------------------------------------------------------------------
      INTEGER N
      REAL*8  N A(N), S, F
      INTEGER I
      REAL*8  D
      D = (F-S)/DBLE(N-1)
      A(1) = S
      DO 10 I=2,N
         A(I) = A(I-1) + D
 10   CONTINUE
      RETURN
      END
Output:
 .................::::::::::::::::::::::::::::::::::::::::::::::::::::::.............................
 .............::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::.......................
 ..........:::::::::::::::::::::::::::-------------------::::::::::::::::::::::::::..................
 ........::::::::::::::::::::::::------------===+#+===--------::::::::::::::::::::::::...............
 ......::::::::::::::::::::::-------------====+*:.$*+===----------:::::::::::::::::::::::............
 ....:::::::::::::::::::::--------------====+*$=   .$+====-----------:::::::::::::::::::::::.........
 ..::::::::::::::::::::--------------====+++*% . +  %*++====------------::::::::::::::::::::::.......
 .::::::::::::::::::--------------====+++++*#$ %==$-$##*+++===-------------:::::::::::::::::::::.....
 :::::::::::::::----------========++##*##$%%% +.- $#    #***+===-------------::::::::::::::::::::....
 :::::::::::------=============+++*#%. * ==. --* ::-%   -.  $*+====-------------:::::::::::::::::::..
 ::::::::-----==**++++======+++++*#%: := $    -%$$.-#: *$ #=%*+++=========---------:::::::::::::::::.
 :::::------==++ +$%#*#%**++++**#%.     .*    +.:%=$  #% + -.#*++++=============------:::::::::::::::
 :::------===+*# % %.  *%#****##  =*  :%     *  : .#   -  $* +%*+++++++=======++++==-----::::::::::::
 :------===+*# $ * --%%.=$$%%%% $  $  * .  .$*++*#$:         =%#***************$ .%+===-----:::::::::
 -----==+++*%%#   %:     #: $$:  $-#*=++-=*   -=            %+ ####***### $$%%$ =  *+====------::::::
 --==#%####$: -  +#       +:.:   #+=-:....- *+              % $$%%%%$ :*+.#  +-+ % .*+=====------::::
 ==+#:.    :%+-::-        +== $-$#*=-:.  $$ .:%   #        : :  $ .:      $   = .*%  +*+=====------::
 +:$*=+  $* : = $   *#    **#= -=    # $$$$$ :+*$##      $=:=:...$= =       - -+- := *#*++++===------
  % * $ .:.+ - #*%: %=:#.$%%$- %+  %.  %%##%$ $  ++*.   * %+=---  #:$*+==-=# =%.      $##*****$+=----
 =+*#%# %:##  +-=    $%==.   .*   *-* *#**##% :* :-=#   -$#++++   :$#*=-:...-$       % $$:+* $ #++==-
 -==++# $ *+:$$ %       $-...:-=*#$:   ++++#$-   #=-: *: %##**#* *-*   *.   .==%$    =-+  ##:% #%#*+=
 ----=+$*****##$      .%= #=-==+*$:#  ---=+% *   .*++  $ $%##%%  .%  +% -$%%$.#:=% :%*# - +.:. $ * % 
 ------===++++*#* =: -+- -       = =$...:=:=$      ##$*+: $$$$$ #    =- =#**    #*   $ = : *$  +=*$:+
 ::------=====+*+  %*. =   $      :. $  : :        #   %:. $$  .:-=*#$-$ ==+        -::-+%:    .:#+==
 ::::------=====+*. % +-+  #.+*: $%%%%$$ %              +* -....:-=+#   :.:+       #+  - :$####%#==--
 ::::::------====+*  = $%%$$ ###***#### +%            =-   *=-++=*#-$  :$$ :#     :%   #%%*+++==-----
 :::::::::-----===+%. $***************#%=         :$#*++*$.  . *  $  $ %%%%$$=.%%-- * $ #*+===------:
 ::::::::::::-----==++++=======+++++++*%+ *$  -   #. :  *     %:  *=  ##****#%*  .% % #*+===------:::
 :::::::::::::::------=============++++*#.- + %#  $=%:.+    *.     .%#**++++**%#*#%$+ ++==------:::::
 .:::::::::::::::::---------=========+++*%=# $* :#-.$$%-    $ =: :%#*+++++======++++**==-----::::::::
 ..:::::::::::::::::::-------------====+*$  .-   %-:: *-- .== * .%#*+++=============------:::::::::::
 ....::::::::::::::::::::-------------===+***#    #$ -.+ %%%$##*##++========----------:::::::::::::::
 .....:::::::::::::::::::::-------------===+++*##$-$==% $#*+++++====--------------::::::::::::::::::.
 .......::::::::::::::::::::::------------====++*%  + . %*+++====--------------::::::::::::::::::::..
 .........:::::::::::::::::::::::-----------====+$.   =$*+====--------------:::::::::::::::::::::....
 ............:::::::::::::::::::::::----------===+*$.:*+====-------------::::::::::::::::::::::......
 ...............::::::::::::::::::::::::--------===+#+===------------::::::::::::::::::::::::........
 ..................::::::::::::::::::::::::::-------------------:::::::::::::::::::::::::::..........
 .......................::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::.............
 .............................::::::::::::::::::::::::::::::::::::::::::::::::::::::.................

Note that for images the first y value is the top. The call to the linspace procedure inverts the imaginary axis so that the set is displayed with -1*i at the bottom and +1*i at the top.

This next version generates a Portable Gray Map (PGM)

Works with: Fortran version 95 and later
File:Julia-set-gray.png
! ==============================================================================
module julia_mod
  ! ----------------------------------------------------------------------------
  implicit none

  character(*), parameter :: DEF_FSPC = 'julia.pgm'

  complex(8),   parameter :: DEF_SEED = (-0.798d0, 0.1618d0)

  complex(8),   parameter :: DEF_UL   = (-1.5d0,  1.0d0)
  complex(8),   parameter :: DEF_LR   = ( 1.5d0, -1.0d0)

  integer,      parameter :: NUM_COLS = 1024
  integer,      parameter :: NUM_ROWS =  768


contains


  ! ============================================================================
  subroutine juliaPGM( fspc, nr, nc, ul, lr, c )
    ! --------------------------------------------------------------------------
    implicit none
    character(*), intent(in) :: fspc ! path to the PGM file
    integer,      intent(in) :: nr   ! number of rows
    integer,      intent(in) :: nc   ! number of columns
    complex(8),   intent(in) :: ul   ! upper left  point on complex plane
    complex(8),   intent(in) :: lr   ! lower right point on complex plane
    complex(8),   intent(in) :: c    ! seed
    ! --------------------------------------------------------------------------
    real(8), allocatable :: X(:), Y(:)
    integer              :: un, ir, ic, i, clr
    complex(8)           :: z
    integer, parameter   :: max_cycle = 512
    ! --------------------------------------------------------------------------

    allocate( X(nc) )
    allocate( Y(nr) )

    call linSpace( X, ul%RE, lr%RE )
    call linSpace( Y, ul%IM, lr%IM )

    open ( FILE=fspc, NEWUNIT=un, ACTION='WRITE', STATUS='REPLACE' )

    write ( un, 100 )
    write ( un, 110 )
    write ( un, 120 ) nc, nr
    write ( un, 130 )

    do ir=1,nr
       do ic=1,nc
          z   = cmplx( X(ic), Y(ir), kind=8 )
          clr = 0
          i   = 0
          do while ( i .lt. max_cycle )
             z = z*z + c
             if ( 2.0D0 .lt. CDABS(z) ) then
                clr = modulo( i, 256 )
                exit
             end if
             i = i + 1
          end do
          write ( un, 200 ) clr
       end do
    end do

    close( un )

    deallocate( Y )
    deallocate( X )

100 format( 'P2' )
110 format( '# Created for Rosetta Code' )
120 format( I0,1X,I0 )
130 format( '255' )
200 format( I0 )

  end subroutine juliaPGM


  ! ============================================================================
  subroutine linSpace( A, a1, a2 )
    ! --------------------------------------------------------------------------
    implicit none
    real(8), intent(inout) :: A(:) ! array of the elements in this linear space
    real(8), intent(in)    :: a1   ! value of the first element
    real(8), intent(in)    :: a2   ! value of the last  element
    ! --------------------------------------------------------------------------
    integer :: i, n
    real(8) :: delta
    ! --------------------------------------------------------------------------

    n = size(A)

    delta = (a2-a1)/real(n-1,kind=8)
    A(1) = a1
    do i=2,n
       A(i) = A(i-1) + delta
    end do

  end subroutine linSpace


end module julia_mod


! ==============================================================================
program julia
  ! ----------------------------------------------------------------------------
  use julia_mod
  implicit none

  call juliaPGM( DEF_FSPC, NUM_ROWS, NUM_COLS, DEF_UL, DEF_LR, DEF_SEED )

end program julia

Fōrmulæ

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

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

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

Solution

We need first to generate a color palette, this is, a list of colors:

The following function draw the Julia set:

Test Case 1. Grayscale palette

Test case 2. Black & white palette

FutureBasic

#build CheckArrayBounds NO
output file "Julia Fractal Viewer
include "NSLog.incl"

begin record Complex
  float real  // real component of Complex Number
  float imag  // imaginary component of Complex Number
end record

_window = 1
begin enum output 1
  _juliaView
end enum

void local fn BuildWindow
  CGRect r = fn CGRectMake( 0, 0, 520, 600 )
  window _window, @"Rosetta Code Julia Set", r, NSWindowStyleMaskTitled + NSWindowStyleMaskClosable + NSWindowStyleMaskMiniaturizable
  
  r = fn CGRectMake( 10, 10, 500, 580 )
  imageview _juliaView, YES,,r, NSImageScaleAxesIndependently, NSImageAlignCenter, NSImageFramePhoto, _window
end fn

local fn JuliaPoint( c as Complex, w as long, h as long, xl as float, xr as float, yb as float, yt as float, i as long, j as long ) as long
  float   ai, ar, cr, ci, t, x, y
  long    k, value
  
  value = 1
  
  cr = c.real
  ci = c.imag
  
  x = ( ( float ) ( w - i - 1 ) * xl + ( float ) ( i ) * xr ) / ( float ) ( w - 1 )
  y = ( ( float ) ( h - j - 1 ) * yb + ( float ) ( j ) * yt ) / ( float ) ( h - 1 )
  
  ar = x
  ai = y
  for k = 0 to 199
    t  = ar * ar - ai * ai + cr
    ai = ar * ai + ai * ar + ci
    ar = t
    if ( 1000 < ar * ar + ai * ai )
      value = 0
      exit fn
    end if
  next k
end fn = value

void local fn JuliaRGB( c as Complex, w as long, h as long, xl as float, xr as float, yb as float, yt as float, rgb(0) as unsigned char )
  long i, j, juliaValue, k
  
  k = 0
  for j = 0 to h - 1
    for i = 0 to w - 1
      juliaValue = fn JuliaPoint( c, w, h, xl, xr, yb, yt, i, j )
      rgb(k)   = 255 * (1-juliaValue)
      rgb(k+1) = 255 * (1-juliaValue)
      rgb(k+2) = 255
      k += 3
    next i
  next j
end fn

void local fn TGAWrite( w as long, h as long, rgb(0) as ^unsigned char, url as CFURLRef )
  CFMutableDataRef   dta
  unsigned char      header1(11), header2(5)
  
  BlockZero( @header1(0), 12 * sizeof(unsigned char) )
  header1(2) = 2
  
  header2(0) = w mod 256
  header2(1) = w/256
  header2(2) = h mod 256
  header2(3) = h/256
  header2(4) = 24
  header2(5) = 0
  
  dta = fn MutableDataWithCapacity(0)
  MutableDataAppendBytes( dta, @header1(0), 12 * sizeof(unsigned char) )
  MutableDataAppendBytes( dta, @header2(0), 6 * sizeof(unsigned char) )
  MutableDataAppendBytes( dta, @rgb(0), w * h * 3 * sizeof(unsigned char) )
  fn DataWriteToURL( dta, url, NSDataWritingAtomic, NULL )
  
  ImageRef image = fn ImageWithData( dta )
  ImageViewSetImage( _juliaView, image )
end fn

void local fn BuildJuliaSet( c as Complex )
  long     h, w
  float    xl, xr, yb, yt
  ptr      p
  CFURLRef url
  
  // Create 1000x1000-pixel canvas for image
  h = 1000
  w = 1000
  
  // Locate image on canvas
  xl = -1.5
  xr = 1.5
  yb = -1.5
  yt = 1.5
  
  p = fn malloc( w * h * 3 * sizeof(unsigned char) )
  
  xref rgb(1) as unsigned char
  rgb = p
  
  // Create image data
  fn JuliaRGB( c, w, h, xl, xr, yb, yt, @rgb(0) )
  
  // Create path to final image
  url = fn URLFileURLWithPath( fn StringByExpandingTildeInPath( @"~/Desktop/julia_set.png" ) )
  
  // Write image data to file
  fn TGAWrite( w, h, @rgb(0), url )
  
  free(p)
end fn

dim as Complex c

c.real =  0.355534
c.imag = -0.337292

// c.real = -0.8
// c.imag = 0.156

// c.real = 0.26
// c.imag = 0.0016

// c.real = 0.355
// c.imag = 0.355

// c.real = -0.4
// c.imag = -0.59

// c.real = -0.54
// c.imag = 0.54

fn BuildWindow
fn BuildJuliaSet( c )

HandleEvents
Output:

Go

Using the Goroutines results in a performance improvement of about three times on my four-core machine.

package main

import (
	"image"
	"image/color"
	"image/png"
	"log"
	"os"
	"sync"
)

func main() {
	const (
		width, height = 800.0, 600.0
		maxIter       = 255
		cX, cY        = -0.7, 0.27015
		fileName      = "julia.png"
	)
	img := image.NewNRGBA(image.Rect(0, 0, width, height))

	var wg sync.WaitGroup
	wg.Add(width)
	for x := 0; x < width; x++ {
		thisx := float64(x)
		go func() {
			var tmp, zx, zy float64
			var i uint8
			for y := 0.0; y < height; y++ {
				zx = 1.5 * (thisx - width/2) / (0.5 * width)
				zy = (y - height/2) / (0.5 * height)
				i = maxIter
				for zx*zx+zy*zy < 4.0 && i > 0 {
					tmp = zx*zx - zy*zy + cX
					zy = 2.0*zx*zy + cY
					zx = tmp
					i--
				}
				img.Set(int(thisx), int(y), color.RGBA{i, i, i << 3, 255})
			}
			wg.Done()
		}()
	}
	wg.Wait()
	imgFile, err := os.Create(fileName)
	if err != nil {
		log.Fatal(err)
	}
	defer imgFile.Close()
	if err := png.Encode(imgFile, img); err != nil {
		imgFile.Close()
		log.Fatal(err)
	}
}


Haskell

Translation of: AWK
import System.Environment (getArgs)

plotChar :: Int -> Float -> Float -> Float -> Float -> Char
plotChar iter cReal cImag y x
  | zReal^2 > 10000 = ' '
  | iter == 1       = '#'
  | otherwise       = plotChar (pred iter) cReal cImag zImag zReal
 where 
  zReal = x * x - y * y + cReal
  zImag = x * y * 2 + cImag

parseArgs :: [String] -> (Float, Float)
parseArgs []             = (-0.8, 0.156)
parseArgs [cReal, cImag] = (read cReal :: Float, read cImag :: Float)
parseArgs _              = error "Invalid arguments"

main :: IO ()
main = do
  args <- getArgs
  let (cReal, cImag) = parseArgs args
  print (cReal, cImag)
  mapM_ putStrLn $ [-100,-96..100] >>= \y -> 
    [[-280,-276..280] >>= \x -> [plotChar 50 cReal cImag (y/100) (x/200)]]
Output:
(-0.8,0.156)
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                        #                                                                    
                                                                         #                                                                   
                                                                      ##                                                                     
                                                                     #######                                                                 
                                                                      ##  ####                                                               
                                                                            ##                                                               
                                                                # ####  ##  #                                                                
                                                        #      #  ###   ###       # ##     #                                                 
                                                         #    ######          ##########  # #                                                
                                                         # #   ######       ########## #                                                     
                                                         #      ###  ### # ############  ######                         #                    
                                                        ################   ###################   #               #   ###  #                  
                                                         ################ #################### ##              #  ###   ##                   
                         ##                            ##############################    ###  #### #          #######     ###                
                       #  ##        ##               #  #####################  # #### ##    #### ###        ########### ######               
                       # #    #####                     #####################     #              # ##       ######################           
                     ###    ####### ####  #            #######################    #                ###      ############  ###   ##      ##   
                  ## ##  ## #################          ########################                     ###      ###########         ##   ### ###
                  #################  ##  ###### #        # ################### #             #####   ##       ######## #      ### #  ######  
                  ############  ## ##       # ###            ##############   #            ##  ###   ##       #   #### #      # ##     ###   
        ##        ###########  ##             ####          #############    ## #         ##   ### ##         ## #######      ##      #####  
     #########    #############                 ###           #  # ####### #  #           ###                 #############    #########     
  #####      ##      ####### ##         ## ###   ##         # ##    #############          ####             ##  ###########        ##        
   ###     ## #      # ####   #       ##   ###  ##            #   ##############            ### #       ## ##  ############                  
  ######  # ###      # ########       ##   #####             # ################### #        # ######  ##  #################                  
### ###   ##         ###########      ###                     ########################          ################# ##  ## ##                  
   ##      ##   ###  ############      ###                #    #######################            #  #### #######    ###                     
           ######################       ## #              #     #####################                     #####    # #                       
               ###### ###########        ### ####    ## #### #  #####################  #               ##        ##  #                       
                ###     #######          # ####  ###    ##############################                            ##                         
                   ##   ###  #              ## #################### ################                                                         
                  #  ###   #               #   ###################   ################                                                        
                    #                         ######  ############ # ###  ###      #                                                         
                                                     # ##########       ######   # #                                                         
                                                # #  ##########          ######    #                                                         
                                                 #     ## #       ###   ###  #      #                                                        
                                                                #  ##  #### #                                                                
                                                               ##                                                                            
                                                               ####  ##                                                                      
                                                                 #######                                                                     
                                                                     ##                                                                      
                                                                   #                                                                         
                                                                    #                                                                        
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                                                                                                                                                                    
Translation of: F#
{-# LANGUAGE LambdaCase #-}

getJuliaValues :: Float -> Float -> Float -> Float -> Float -> Int -> [[Int]]
getJuliaValues width height centerX centerY zoom maxIter =
  [0..pred height] >>= \h -> [[0..pred width] >>= \w -> [calc h w]]
 where 
  initzx x = 1.5 * (x - width  / 2) / (0.5 * zoom * width)
  initzy y = 1.0 * (y - height / 2) / (0.5 * zoom * height)
  calc y x = loop 0 (initzx x) (initzy y)
   where 
    loop i zx zy
     | zx * zx + zy * zy >= 4.0 = i
     | i == maxIter = 0
     | otherwise = loop (succ i) (zx*zx - zy*zy + centerX) (2.0*zx*zy + centerY)

main :: IO ()
main = mapM_ (putStrLn . fmap (\case 0 -> '#'; _ -> ' ')) (getJuliaValues 140 50 (-0.8) 0.156 1.0 50)
Output:
                                                                                                                                            
                                                                                                                                            
                                                                                                                                            
                                                                                                                                            
                                                                        #                                                                   
                                                                         #                                                                  
                                                                      #                                                                     
                                                                     ####### #                                                              
                                                                      ##   ##                                                               
                                                                           ##                                                               
                                                                # ####  ## #                                                                
                                                         # #   ######   ####      ###    #                                                  
                                                         ##   ######          ######## #  #                                                 
                                                               #####       ########## #                                                     
                                                          #   #  ##   # #  ###########   ####                       ###                     
                                                       # ### ###########   ##################   #            #    ### #                     
                                                          ############### ###########  #######              ## ###  ##                      
                            #                           ############################    ##  #####         ########    ###                   
                          #  ##        #               # ###################    #### ## # #### ###       #################                  
                          # ##    # #                    ####################    #           # # ##      ################### #              
                        ###     ##### ####              #####################  # #               ###     ###########   #  # ##    # # #     
                        ##  ##################          ######################                    ###     ###########        ##  ######     
                      ###############  ##  ######         #####################           ######   ##      ######## #     ### #   ###   #  #
                     ########### # ## #         ###           ############               ###  ###  ##      #   ###        # ##    ###     ##
         # ###        ##########  #             ####         ############    # #         ##   ## ###       ## #######     ##    # ####      
        ##########    ############                ##               #######               ##                ############    ##########       
       #### #    ##     ####### ##       ### ##   ##         # #    ############         ####             #  ##########        ### #        
 ##     ###    ## #        ###   #      ##  ###  ###               ############           ###         # ## # ###########                    
 #  #   ###   # ###     # ########      ##   ######           #####################         ######  ##  ###############                     
      ######  ##        ###########     ###                    ######################          ##################  ##                       
      # # #    ## #  #   ###########     ###               # #  #####################              #### #####     ###                       
               # ###################      ## # #           #    ####################                    # #    ## #                         
                   #################       ### #### # ## ####    ################### #               #        ##  #                         
                    ###    ########         #####  ##    ############################                           #                           
                       ##  ### ##              #######  ########### ###############                                                         
                      # ###    #            #   ##################   ########### ### #                                                      
                      ###                       ####   ###########  # #   ##  #   #                                                         
                                                      # ##########       #####                                                              
                                                  #  # ########          ######   ##                                                        
                                                   #    ###      ####   ######   # #                                                        
                                                                 # ##  #### #                                                               
                                                                ##                                                                          
                                                                ##   ##                                                                     
                                                               # #######                                                                    
                                                                      #                                                                     
                                                                   #                                                                        
                                                                    #                                                                       
                                                                                                                                            
                                                                                                                                            
                                                                                       

J

load '~addons/graphics/fvj4/complex_dynamics.ijs'
pal2=: 255,~0,<.(254$1 0.8 0.6)*Hue 5r6*(i.%<:)254
g=: [: %: 0.3746j0.102863 0.132565j0.389103 _0.373935j_0.353777 1&p.
view_image pal2;b=:g escapetc (10 255) 500 zl_clur _1.5 1.5j1.5

See also: Fractals Visualization and J, 4th edition, Part 1 (by Clifford A. Reiter), Chapter 6

See http://webbox.lafayette.edu/~reiterc/mvp/ec_julia/index.html for some other examples. (That said, note that this is a link into a small college site and it might drift over time. In the past, for example, you would have had to use 'www' where it currently says 'webbox')

Java

Works with: Java version 8
import javax.swing.*;
import java.awt.*;
import java.awt.image.BufferedImage;

public class JuliaSet extends JPanel {
    private static final int MAX_ITERATIONS = 300;
    private static final double ZOOM = 1;
    private static final double CX = -0.7;
    private static final double CY = 0.27015;
    private static final double MOVE_X = 0;
    private static final double MOVE_Y = 0;

    public JuliaSet() {
        setPreferredSize(new Dimension(800, 600));
        setBackground(Color.white);
    }

    void drawJuliaSet(Graphics2D g) {
        int w = getWidth();
        int h = getHeight();
        BufferedImage image = new BufferedImage(w, h, BufferedImage.TYPE_INT_RGB);

        for (int x = 0; x < w; x++) {
            for (int y = 0; y < h; y++) {
                double zx = 1.5 * (x - w / 2) / (0.5 * ZOOM * w) + MOVE_X;
                double zy = (y - h / 2) / (0.5 * ZOOM * h) + MOVE_Y;
                float i = MAX_ITERATIONS;
                while (zx * zx + zy * zy < 4 && i > 0) {
                    double tmp = zx * zx - zy * zy + CX;
                    zy = 2.0 * zx * zy + CY;
                    zx = tmp;
                    i--;
                }
                int c = Color.HSBtoRGB((MAX_ITERATIONS / i) % 1, 1, i > 0 ? 1 : 0);
                image.setRGB(x, y, c);
            }
        }
        g.drawImage(image, 0, 0, null);
    }

    @Override
    public void paintComponent(Graphics gg) {
        super.paintComponent(gg);
        Graphics2D g = (Graphics2D) gg;
        g.setRenderingHint(RenderingHints.KEY_ANTIALIASING,
                RenderingHints.VALUE_ANTIALIAS_ON);
        drawJuliaSet(g);
    }

    public static void main(String[] args) {
        SwingUtilities.invokeLater(() -> {
            JFrame f = new JFrame();
            f.setDefaultCloseOperation(JFrame.EXIT_ON_CLOSE);
            f.setTitle("Julia Set");
            f.setResizable(false);
            f.add(new JuliaSet(), BorderLayout.CENTER);
            f.pack();
            f.setLocationRelativeTo(null);
            f.setVisible(true);
        });
    }
}

To multi-thread, simply swap the for loop for a parallel IntStream.

import javax.swing.*;
import java.awt.*;
import java.awt.image.BufferedImage;
import java.util.stream.IntStream;

public class JuliaSet extends JPanel {
    private static final int MAX_ITERATIONS = 300;
    private static final double ZOOM = 1;
    private static final double CX = -0.7;
    private static final double CY = 0.27015;
    private static final double MOVE_X = 0;
    private static final double MOVE_Y = 0;

    public JuliaSet() {
        setPreferredSize(new Dimension(800, 600));
        setBackground(Color.white);
    }

    void drawJuliaSet(Graphics2D g) {
        int w = getWidth();
        int h = getHeight();
        BufferedImage image = new BufferedImage(w, h, BufferedImage.TYPE_INT_RGB);

        IntStream.range(0, w).parallel().forEach(x -> {
            IntStream.range(0, h).parallel().forEach(y -> {
                double zx = 1.5 * (x - w / 2) / (0.5 * ZOOM * w) + MOVE_X;
                double zy = (y - h / 2) / (0.5 * ZOOM * h) + MOVE_Y;
                float i = MAX_ITERATIONS;
                while (zx * zx + zy * zy < 4 && i > 0) {
                    double tmp = zx * zx - zy * zy + CX;
                    zy = 2.0 * zx * zy + CY;
                    zx = tmp;
                    i--;
                }
                int c = Color.HSBtoRGB((MAX_ITERATIONS / i) % 1, 1, i > 0 ? 1 : 0);
                image.setRGB(x, y, c);
            });
        });
        g.drawImage(image, 0, 0, null);
    }

    @Override
    public void paintComponent(Graphics gg) {
        super.paintComponent(gg);
        Graphics2D g = (Graphics2D) gg;
        g.setRenderingHint(RenderingHints.KEY_ANTIALIASING,
                RenderingHints.VALUE_ANTIALIAS_ON);
        drawJuliaSet(g);
    }

    public static void main(String[] args) {
        SwingUtilities.invokeLater(() -> {
            JFrame f = new JFrame();
            f.setDefaultCloseOperation(JFrame.EXIT_ON_CLOSE);
            f.setTitle("Julia Set");
            f.setResizable(false);
            f.add(new JuliaSet(), BorderLayout.CENTER);
            f.pack();
            f.setLocationRelativeTo(null);
            f.setVisible(true);
        });
    }
}

JavaScript

take a look here.

var maxIterations = 450, minX = -.5, maxX = .5, 
    minY = -.5, maxY = .5, wid, hei, ctx,
    jsX = 0.285, jsY = 0.01;

function remap( x, t1, t2, s1, s2 ) {
    var f = ( x - t1 ) / ( t2 - t1 ),
        g = f * ( s2 - s1 ) + s1;
    return g;
}
function getColor( c ) {
    var r, g, b, p = c / 32,
        l = ~~( p * 6 ), o = p * 6 - l, 
        q = 1 - o;

    switch( l % 6 ) {
        case 0: r = 1; g = o; b = 0; break;
        case 1: r = q; g = 1; b = 0; break;
        case 2: r = 0; g = 1; b = o; break;
        case 3: r = 0; g = q; b = 1; break;
        case 4: r = o; g = 0; b = 1; break;
        case 5: r = 1; g = 0; b = q; break;
    }
    var c = "#" + ( "00" + ( ~~( r * 255 ) ).toString( 16 ) ).slice( -2 ) + 
                  ( "00" + ( ~~( g * 255 ) ).toString( 16 ) ).slice( -2 ) + 
                  ( "00" + ( ~~( b * 255 ) ).toString( 16 ) ).slice( -2 );
    return (c);
}
function drawFractal() {
    var a, as, za, b, bs, zb, cnt, clr
    for( var j = 0; j < hei; j++ ) {
        for( var i = 0; i < wid; i++ ) {
            a = remap( i, 0, wid, minX, maxX )
            b = remap( j, 0, hei, minY, maxY )
            cnt = 0;
            while( ++cnt < maxIterations ) {
                za = a * a; zb = b * b;
                if( za + zb > 4 ) break;
                as = za - zb; bs = 2 * a * b;
                a = as + jsX; b = bs + jsY;
            }
            if( cnt < maxIterations ) {
                ctx.fillStyle = getColor( cnt );
            }
            ctx.fillRect( i, j, 1, 1 );
        }
    }
}
function init() {
    var canvas = document.createElement( "canvas" );
    wid = hei = 800;
    canvas.width = wid; canvas.height = hei;
    ctx = canvas.getContext( "2d" );
    ctx.fillStyle = "black"; ctx.fillRect( 0, 0, wid, hei );
    document.body.appendChild( canvas );
    drawFractal();
}

jq

Translation of: awk
# Example values:
# $re : -0.8
# $im : 0.156
{}
| range(-100; 101; 10) as $v
| (( range (-280; 281; 10) as $h
  | .x = $h / 200
  | .y = $v / 100
  | .plot = "#"
  | .i = 0
  | until (.i == 50 or .plot == ".";
           .i += 1
           | .z_real = ((.x * .x) - (.y * .y) + $re)
           | .z_imag = ((.x * .y * 2) + $im)
 	   | if pow(.z_real; 2) > 10000 then .plot = " " 
             else .x = .z_real | .y = .z_imag
   	     end )
  | .plot ), "\n")

With the above program in a file called julia.jq, the following invocation of jq 1.5 produces the same output as shown in the awk entry on this page:

jq -nrj -f julia.jq --argjson re -0.8 --argjson im 0.156 

(If your jq does not support the --argjson options, then use --arg instead, and add the `tonumber` conversions at the beginning of the program.)

Julia

The following code creates the fractal as a ppm file named julia.ppm. There is no need of an external library to create this image since the ppm format is straightforward to generate.

function iter(z,c)
  n = 0
  while (abs2(z)<4)  z = z^2+c ; n+=1 end
  return n
end

coord(i,j,w,h,a,b) = 2*a*(i-1)/(w-1) - a + im * (2*b*(j-1)/(h-1) - b)

palette(n) = string(min(3n,255)," ", min(n,255)," ", 0);

julia(c) = (w,h,a,b,i,j) -> palette(iter(coord(i,j,w,h,a,b), c))

writeppm(f; width=600,height=300,a=2,b=1,file="julia.ppm") =
  open(file, "w") do out
    write(out, string("P3\n", width, " ", height, "\n255\n"))
    writedlm(out, [f(width,height,a,b,i,j) for j = 1:height, i = 1:width], '\n')
  end

We can then produce a 600x300 ppm image of the Julia set associated to the parameter -0.786+0.147i as follows.

writeppm(julia(-0.786+0.147im))

The following code makes use of the library Images to build a png image.

using Images

@inline function hsv2rgb(h, s, v)
    c = v * s
    x = c * (1 - abs(((h/60) % 2) - 1))
    m = v - c

    if h < 60
        r,g,b = (c, x, 0)
    elseif h < 120
        r,g,b = (x, c, 0)
    elseif h < 180
        r,g,b = (0, c, x)
    elseif h < 240
        r,g,b = (0, x, c)
    elseif h < 300
        r,g,b = (x, 0, c)
    else
        r,g,b = (c, 0, x)
    end

    (r + m), (b + m), (g + m)
end

function julia_set(c = -0.7+0.27015im)

    w, h = 800, 800

    zoom  = 0.7       # the zoom factor
    moveX = 0         # the amount of shift on the x axis
    moveY = 0         # the amount of shift on the y axis

    L = 2             # the maximum value of |z|
    I = 255           # the maximum number of iterations

    img = zeros(RGB{Float64}, h, w)

    for x in 1:w, y in 1:h
        n = 0
        z = Complex(
            (2*x - w) / (w * zoom) + moveX,
            (2*y - h) / (h * zoom) + moveY
        )
        while abs(z) < L && (n += 1) < I
            z = z^2 + c
        end
        v = (I - n) / I
        r,g,b = hsv2rgb(v*360, 1, v)
        img[y,x] = RGB{Float64}(r, g, b)
    end

    save("julia_set.png", img)
end

julia_set()

Kotlin

import java.awt.*
import java.awt.image.BufferedImage
import javax.swing.JFrame
import javax.swing.JPanel

class JuliaPanel : JPanel() {
    init {
        preferredSize = Dimension(800, 600)
        background = Color.white
    }

    private val maxIterations = 300
    private val zoom = 1
    private val moveX = 0.0
    private val moveY = 0.0
    private val cX = -0.7
    private val cY = 0.27015

    public override fun paintComponent(graphics: Graphics) {
        super.paintComponent(graphics)
        with(graphics as Graphics2D) {
            setRenderingHint(RenderingHints.KEY_ANTIALIASING, RenderingHints.VALUE_ANTIALIAS_ON)
            val image = BufferedImage(width, height, BufferedImage.TYPE_INT_RGB)
            (0 until width).forEach { x ->
                (0 until height).forEach { y ->
                    var zx = 1.5 * (x - width / 2) / (0.5 * zoom * width) + moveX
                    var zy = (y - height / 2) / (0.5 * zoom * height) + moveY
                    var i = maxIterations.toFloat()
                    while (zx * zx + zy * zy < 4 && i > 0) {
                        val tmp = zx * zx - zy * zy + cX
                        zy = 2.0 * zx * zy + cY
                        zx = tmp
                        i--
                    }
                    image.setRGB(x, y, Color.HSBtoRGB(maxIterations / i % 1, 1f, (if (i > 0) 1 else 0).toFloat()))
                }
            }
            drawImage(image, 0, 0, null)
        }
    }
}

fun main() {
    with(JFrame()) {
        defaultCloseOperation = JFrame.EXIT_ON_CLOSE
        title = "Julia Set"
        isResizable = false
        add(JuliaPanel(), BorderLayout.CENTER)
        pack()
        setLocationRelativeTo(null)
        isVisible = true
    }
}

Lua

local cmap = { [0]=" ", ".", ":", "-", "=", "+", "*", "#", "%", "$", "@" }
for y = -1.0, 1.0, 0.05 do
  for x = -1.5, 1.5, 0.025 do
    local zr, zi, i = x, y, 0
    while i < 100 do
      zr, zi = zr*zr - zi*zi - 0.79, zr * zi * 2 + 0.15
      if (zr*zr + zi*zi > 4) then break else i = i + 1 end
    end
    io.write(cmap[math.floor(i/10)])
  end
  print()
end
Output:




                                                             .:
                                                          =@=:.#:
                                                           %@=:@%@
                                                           ..::::#.
                                                       :.+=-:+@--%
                                                 =+- .#+@@::::@-....--@:.@..$@
                                                 .@*:.**=@=::::...=@@@*@@::@-#
                                                 :-:::*@@@-:::::--@@%@*+=+::%+:.                   -@+
                                              %@-=@@@==*@**=*@:%#*@@%@@@@@@@*@@#:-.          @:.@@@+:-
                       -                       .$-==@%**@@==--*@@@@====@@@-#=@@@%@:        -@+:%@@:::.
                      @@:@.     .@            @*:=*@%@@@@*++@%@@@@#-#*-::::=:::*@@#+.    .+%@%*@$=+:%%@@=--
                      $-$-..@@#*:@... +        .:=#@@@@@%@@@@@*$#@=:::@::::::::::-+%@.....%@@@@*+##@@=*@@@#
                  ..:@=:::.*@%@=@#%*+:.@.     ..:@@$@@@@%**%==+=*$:::::::::::::::::-+@....@@$@#*@+@@:=::::=-   +:@=
                  .::@@#-:%*@=*@@-=@@=*@@@.......@-@+@*@@*+@=--==:::::::::::::@$=*---@=....=@=@@=-*=:::::::-@.-@@*#@.
                  -+@*@@=+@@@*%::::::::@+*$@......@=+@+@@@@@@--@=@::......:-@@===+*--#@....::@@@@@::...:@=@=+.:@@:::-.%@
        : .+.     =#@@@@@+#@:::::::::::::-=@-.......:*==*#@@@#@@:::.......:-+=-=+%===@::...:::-#%#@+:...@-:::::##@$.@$-
      @@-$=@==@+...-+@@+@==@::::::::-#@@----@=.......::=%@@@@@@@%=::.......=@----@@#-::::::::@==@+@@+-...+@==@=$-@@
  -$@.$@##:::::-@...:+@#%#-:::...::@===%+=-=+-:.......:::@@#@@@#*==*:.......-@=-:::::::::::::@#+@@@@@#=     .+. :
 @%.-:::@@:.+=@=@:...::@@@@@::....@#--*+===@@-:......::@=@--@@@@@@+@+=@......@$*+@::::::::%*@@@+=@@*@+-
    .@#*@@-.@-:::::::=*-=@@=@=....=@---*=$@:::::::::::::==--=@+*@@*@+@-@.......@@@*=@@=-@@*=@*%:-#@@::.
      =@:+   -=::::=:@@+@*#@$@@....@+-:::::::::::::::::$*=+==%**%@@@@$@@:..     .@.:+*%#@=@%@*.:::=@:..
              #@@@*=@@##+*@@@@%.....@%+-::::::::::@:::=@#$*@@@@@%@@@@@#=:.        + ...@:*#@@..-$-$
              --=@@%%:+=$@*%@%+.    .+#@@*:::=::::-*#-#@@@@%@++*@@@@%@*=:*@            @.     .@:@@
                   .:::@@%:+@-        :@%@@@=#-@@@====@@@@*--==@@**%@==-$.                       -
                   -:+@@@.:@          .-:#@@*@@@@@@@%@@*#%:@*=**@*==@@@=-@%
                   +@-                   .:+%::+=+*@%@@--:::::-@@@*:::-:
                                           #-@::@@*@@@=...::::=@=**.:*@.
                                           @$..@.:@--....-@::::@@+#. -+=
                                                       %--@+:-=+.:
                                                      .#::::..
                                                       @%@:=@%
                                                        :#.:=@=
                                                          :.




Mathematica/Wolfram Language

Mathematica provides built-in functions for Julia sets. Generate the set of points for the -0.77 +0.22 I Julia set with step sizes of 0.01

JuliaSetPoints[-0.77 + 0.22 I, "ClosenessTolerance" -> 0.01]

Visualize the same Julia set

JuliaSetPlot[-0.77 + 0.22 I]

Maxima

Using autoloaded package plotdf

julia (-0.786, 0.147, [iterations, 255], [x, -1.5, 1.5],
      [y, -1, 1], [grid, 320, 320])$
File:JuliaMaxima.png

Nim

Translation of: C#
Library: imageman
import lenientops
import imageman

const
  W = 800
  H = 600
  Zoom = 1
  MaxIter = 255
  MoveX = 0
  MoveY = 0
  Cx = -0.7
  Cy = 0.27015

var colors: array[256, ColorRGBU]
for n in byte.low..byte.high:
  colors[n] = ColorRGBU [n shr 5 * 36, (n shr 3 and 7) * 36, (n and 3) * 85]

var image = initImage[ColorRGBU](W, H)

for x in 0..<W:
  for y in 0..<H:
    var zx = 1.5 * (x - W / 2) / (0.5 * Zoom * W) + MoveX
    var zy = 1.0 * (y - H / 2) / (0.5 * Zoom * H) + MoveY
    var i = MaxIter
    while zx * zx + zy * zy < 4 and i > 1:
      (zy, zx) = (2.0 * zx * zy + Cy, zx * zx - zy * zy + Cx)
      dec i
    image[x, y] = colors[i]

# Save into a PNG file.
image.savePNG("julia.png", compression = 9)

Perl

use Imager;

my($w, $h, $zoom) = (800, 600, 1);
my $img = Imager->new(xsize => $w, ysize => $h, channels => 3);

my $maxIter = 255;
my ($cX, $cY) = (-0.7, 0.27015);
my ($moveX, $moveY) = (0, 0);

my $color = Imager::Color->new('#000000');

foreach my $x (0 .. $w - 1) {
    foreach my $y (0 .. $h - 1) {
        my $zx = (1.5 * ($x - $w / 2) / (0.5 * $zoom * $w) + $moveX);
        my $zy = (($y - $h / 2) / (0.5 * $zoom * $h) + $moveY);
        my $i = $maxIter;
        while ($zx**2 + $zy**2 < 4 and --$i >= 0) {
            ($zy, $zx) = (2 * $zx * $zy + $cY, $zx**2 - $zy**2 + $cX);
        }
        $color->set(hsv => [$i / $maxIter * 360, 1, $i > 0 ? 1 : 0]);
        $img->setpixel(x => $x, y => $y, color => $color);
    }
}

$img->write(file => 'julia_set.png');

Phix

Library: Phix/pGUI

Interactive gui (zoom/pan incomplete).

--
-- demo\rosetta\Julia_set.exw
-- ==========================
--
-- Interactive gui (zoom/pan incomplete).
--
--with javascript_semantics -- not quite yet:
without js    -- [DEV] IupValuator, IupImageRGB
include pGUI.e

constant title = "Julia set"
Ihandle dlg, cxv, cxl, cyv, cyl, ispin, pspin, clrzn, label, bb, redraw

atom cX = -0.7,
     cY = -0.353777
integer iter = 255,
        pwr = 2,
        zoom = 1,       -- (not yet used/to do)
        moveX = 0,      -- drag?? (to do)
        moveY = 0

constant clrzns = {{8,32,16},
                   {2,4,8},
                   {1,1,8}}

sequence colourisation = clrzns[1]

function julia(integer width, integer height)
    atom tpt25 = time()+0.25
    sequence img = repeat(repeat(0,width),height)
    for x=1 to width do
        for y=1 to height do
            atom zx := 1.5*((x-1)-width/2)/(0.5*zoom*width)+moveX,
                 zy := 1.0*((y-1)-height/2)/(0.5*zoom*height)+moveY;
            integer i := iter;
            while ((zx*zx+zy*zy)<4) and (i>1) do
                atom pn = power(zx*zx+zy*zy,pwr/2),
                     pa = pwr*atan2(zy, zx)
                zx = pn*cos(pa)+cX
                zy = pn*sin(pa)+cY
                i -= 1;
            end while
--          img[y,x] = {i*2,i*4,i*8}        -- (experiment thusly)
            img[y,x] = sq_mul(i,colourisation)
        end for
        if time()>tpt25 then
            IupSetStrAttribute(dlg, "TITLE", "%s (generating - %3.2f%%)",{title,x/width*100})
            IupFlush()
            tpt25 = time()+0.25
        end if
    end for
    img = flatten(img)
    Ihandle new_img = IupImageRGB(width, height, img)
    return new_img
end function

function redraw_cb(Ihandln /*redraw*/)
    Ihandln image = IupGetAttributeHandle(label, "IMAGE")
    IupSetAttributeHandle(label, "IMAGE", NULL)
    image = IupDestroy(image)
    IupSetAttribute(redraw,"ACTIVE","NO")
    IupRefreshChildren(bb)
    integer {w,h} = IupGetIntInt(bb, "RASTERSIZE")
    image = julia(w,h)
    IupSetAttribute(redraw,"ACTIVE","YES")
    IupUnmap(label)
    IupSetAttribute(label,"RASTERSIZE",NULL)
    IupSetAttributeHandle(label, "IMAGE", image)
    IupMap(label)
    IupRefresh(label)
    IupSetStrAttribute(dlg, "TITLE", title)
    return IUP_DEFAULT
end function
constant cb_redraw = Icallback("redraw_cb")

function valuechanged_cb(Ihandle ih)
    atom a = IupGetFloat(ih, "VALUE")
    switch ih do
        case cxv:   cX = a  IupSetStrAttribute(cxl,"TITLE","cY: %f",{cX})
        case cyv:   cY = a  IupSetStrAttribute(cyl,"TITLE","cY: %f",{cY})
        case ispin: iter = a
        case pspin: pwr = a
        case clrzn: colourisation = clrzns[a]
    end switch
    return IUP_DEFAULT
end function
constant cb_valuechanged = Icallback("valuechanged_cb")

procedure create_dlg()

    Ihandle lx1 = IupLabel("+")
            cxl = IupLabel(sprintf("cX: %f",cX))
    Ihandle lx2 = IupLabel("-"),
            hx1 = IupHbox({lx1, IupFill(), cxl, IupFill(), lx2})
            cxv = IupValuator(NULL,"MIN=-2.5, MAX=+1")
    Ihandle bxv = IupVbox({hx1, cxv})

    Ihandle ly1 = IupLabel("+")
            cyl = IupLabel(sprintf("cY: %f",cY))
    Ihandle ly2 = IupLabel("-"),
            hx2 = IupHbox({ly1, IupFill(), cyl, IupFill(), ly2})
            cyv = IupValuator(NULL,"MIN=-1, MAX=+1")
    Ihandle byv = IupVbox({hx2, cyv})

    IupSetCallback(cxv, "VALUECHANGED_CB", cb_valuechanged)
    IupSetCallback(cyv, "VALUECHANGED_CB", cb_valuechanged)
    IupSetFloat(cxv, "VALUE", cX)
    IupSetFloat(cyv, "VALUE", cY)

    Ihandle ilbl = IupLabel("iter'ns:","PADDING=0x3")
            ispin = IupText("VALUECHANGED_CB", cb_valuechanged,
                            "SPIN=Yes, SPINMIN=1, SPINMAX=500, RASTERSIZE=48x")
    IupSetInt(ispin,"VALUE",iter)
    Ihandle ibox = IupHbox({IupFill(),ilbl,ispin,IupFill()})

    Ihandle plbl = IupLabel("power:","PADDING=0x3")
            pspin = IupText("VALUECHANGED_CB", cb_valuechanged,
                            "SPIN=Yes, SPINMIN=2, SPINMAX=6, RASTERSIZE=48x")
    IupSetInt(pspin,"VALUE",pwr)
    Ihandle pbox = IupHbox({IupFill(),plbl,pspin,IupFill()})

    Ihandle clbl = IupLabel("colourization:","PADDING=0x3")
    clrzn = IupList("DROPDOWN=YES")
    for i=1 to length(clrzns) do
        IupSetStrAttributeId(clrzn,"",i,sprint(clrzns[i]))
    end for
    IupSetInt(clrzn,"VISIBLEITEMS",length(clrzns)+1)
    IupSetInt(clrzn,"VALUE",1)
    IupSetCallback(clrzn, "VALUECHANGED_CB", cb_valuechanged)
    Ihandle cbox = IupHbox({IupFill(),IupVbox({clbl,clrzn}),IupFill()})

    redraw = IupButton("redraw",cb_redraw)
    Ihandle rbox = IupHbox({IupFill(),redraw,IupFill()},"EXPAND=YES, MARGIN=10x20")

    Ihandle params = IupVbox({bxv,byv,ibox,pbox,cbox,rbox},
                              "GAP=5, EXPAND=NO, EXPANDCHILDREN=YES, MARGIN=3x3")

    label = IupLabel("please wait...","ALIGNMENT=ACENTER:ACENTER, RASTERSIZE=800x600")
    bb = IupBackgroundBox(IupHbox({IupVbox({label,IupFill()}),IupFill()}),"EXPAND=YES, SHRINK=YES")

    dlg = IupDialog(IupHbox({params,bb}))
    IupSetAttribute(dlg, "TITLE", title)
end procedure

procedure main()
    IupOpen()
    create_dlg()
    IupShow(dlg)
    {} = redraw_cb(NULL)
    if platform()!=JS then
        IupMainLoop()
        IupClose()
    end if
end procedure

main()

PHP

Click here to see a sample image created using this script.

set_time_limit(300);
header("Content-Type: image/png");

class Julia {
	
	static private $started = false;
	
	public static function start() {
		if (!self::$started) {
			self::$started = true;
			new self;
		}
	}
	
	const AXIS_REAL 	= 0;
	const AXIS_IMAGINARY 	= 1;
	const C 		= [-0.75, 0.1];
	const RADII 		= [1, 0.5];
	const CENTER 		= [0, 0];
	const MAX_ITERATIONS 	= 100;
	const TICK_SPACING 	= 0.001;
	
	private $maxDistance;
	private $imageResource;
	private $whiteColorResource;
	private $z0 = [];
	
	private function __construct() {
		$this->maxDistance = max($this->distance(self::C), 2);
		$this->imageResource = imagecreate(
			$this->coordinateToPixel(self::RADII[self::AXIS_REAL], self::AXIS_REAL),
			$this->coordinateToPixel(self::RADII[self::AXIS_IMAGINARY], self::AXIS_IMAGINARY)
		);
		imagecolorallocate($this->imageResource, 0, 0, 0);
		$this->whiteColorResource = imagecolorallocate($this->imageResource, 255, 255, 255);
		
		for ($x = self::CENTER[self::AXIS_REAL] - self::RADII[self::AXIS_REAL];
		$x <= self::CENTER[self::AXIS_REAL] + self::RADII[self::AXIS_REAL]; $x += self::TICK_SPACING) {
			$z0[self::AXIS_REAL] = $x;
			
			for ($y = self::CENTER[self::AXIS_IMAGINARY] - self::RADII[self::AXIS_IMAGINARY];
			$y <= self::CENTER[self::AXIS_IMAGINARY] + self::RADII[self::AXIS_IMAGINARY]; $y += self::TICK_SPACING) {
				$z0[self::AXIS_IMAGINARY] = $y;
				$iterations = 1;
				do {
					$z0 = $this->q($z0);
					$iterations++;
				} while($iterations < self::MAX_ITERATIONS && $this->distance($z0) <= $this->maxDistance);
				
				if ($iterations !== self::MAX_ITERATIONS) {
					imagesetpixel(
						$this->imageResource,
						$this->coordinateToPixel($x, self::AXIS_REAL),
						$this->coordinateToPixel($y, self::AXIS_IMAGINARY),
						$this->whiteColorResource
					);
				}
				$z0[self::AXIS_REAL] = $x;
			}
		}
	}
	
	public function __destruct() {
		imagepng($this->imageResource);
		imagedestroy($this->imageResource);
	}
	
	private function q($z) {
		return [ ($z[self::AXIS_REAL] ** 2) - ($z[self::AXIS_IMAGINARY] ** 2) + self::C[self::AXIS_REAL],
                       (2 * $z[self::AXIS_REAL] * $z[self::AXIS_IMAGINARY]) + self::C[self::AXIS_IMAGINARY] ];
	}
	
	private function distance($z) {
		return sqrt( ($z[self::AXIS_REAL] ** 2) + ($z[self::AXIS_IMAGINARY] ** 2) );
	}
	
	private function coordinateToPixel($coordinate, $axis) {
		return ($coordinate + self::RADII[$axis]) * (self::TICK_SPACING ** -1);
	}
}

Julia::start();

Processing

float cX = -0.7;
float cY = 0.27015;
float zx, zy;
float maxIter = 300;

void setup() {
  size(640, 480);
}

void draw() {
  for (int x = 0; x < width; x++) {
    for (int y = 0; y < height; y++) {
      zx = 1.5 * (x - width / 2) / (0.5 * width);
      zy = (y - height / 2) / (0.5 * height);
      float i = maxIter;
      while (zx * zx + zy * zy < 4 && i > 0) {
        float tmp = zx * zx - zy * zy + cX;
        zy = 2.0 * zx * zy + cY;
        zx = tmp;
        i -= 1;
      }
     colorMode(HSB); 
     color c = color(i / maxIter * 255, 255,  i > 1 ? 255 : 0);
     set(x, y, c);
    }
  }
  noLoop();
}

Processing Python mode

Translation of: Processing
from __future__ import division

cX = -0.7
cY = 0.27015
maxIter = 300

def setup():
    size(640, 480)

def draw():
    for x in range(width):
        for y in range(height):
            zx = 1.5 * (x - width / 2) / (0.5 * width)
            zy = (y - height / 2) / (0.5 * height)
            i = maxIter
            while zx * zx + zy * zy < 4 and i > 0:
                tmp = zx * zx - zy * zy + cX
                zy = 2.0 * zx * zy + cY
                zx = tmp
                i -= 1
            colorMode(HSB)
            c = color(i / maxIter * 255, 255, 255 if i > 1 else 0)
            set(x, y, c)
   noLoop()

Python

Naive approach

Translation of: zkl
from PIL import Image

if __name__ == "__main__":
	w, h, zoom = 800,600,1
	bitmap = Image.new("RGB", (w, h), "white")
	pix = bitmap.load()
 
	cX, cY = -0.7, 0.27015
	moveX, moveY = 0.0, 0.0
	maxIter = 255
 
	for x in range(w):
		for y in range(h):
			zx = 1.5*(x - w/2)/(0.5*zoom*w) + moveX
			zy = 1.0*(y - h/2)/(0.5*zoom*h) + moveY
			i = maxIter
			while zx*zx + zy*zy < 4 and i > 1:
				tmp = zx*zx - zy*zy + cX
				zy,zx = 2.0*zx*zy + cY, tmp
				i -= 1
			# convert byte to RGB (3 bytes), kinda magic to get nice colors
			pix[x][y] = (i << 21) + (i << 10) + i*8
 
	bitmap.show()

Vectorized

Efficient version using vectorized operations in NumPy.

Example output.

"""
Solution from:
https://codereview.stackexchange.com/questions/210271/generating-julia-set
"""
from functools import partial
from numbers import Complex
from typing import Callable

import matplotlib.pyplot as plt
import numpy as np


def douady_hubbard_polynomial(z: Complex,
                              c: Complex) -> Complex:
    """
    Monic and centered quadratic complex polynomial
    https://en.wikipedia.org/wiki/Complex_quadratic_polynomial#Map
    """
    return z ** 2 + c


def julia_set(mapping: Callable[[Complex], Complex],
              *,
              min_coordinate: Complex,
              max_coordinate: Complex,
              width: int,
              height: int,
              iterations_count: int = 256,
              threshold: float = 2.) -> np.ndarray:
    """
    As described in https://en.wikipedia.org/wiki/Julia_set
    :param mapping: function defining Julia set
    :param min_coordinate: bottom-left complex plane coordinate
    :param max_coordinate: upper-right complex plane coordinate
    :param height: pixels in vertical axis
    :param width: pixels in horizontal axis
    :param iterations_count: number of iterations
    :param threshold: if the magnitude of z becomes greater
    than the threshold we assume that it will diverge to infinity
    :return: 2D pixels array of intensities
    """
    im, re = np.ogrid[min_coordinate.imag: max_coordinate.imag: height * 1j,
                      min_coordinate.real: max_coordinate.real: width * 1j]
    z = (re + 1j * im).flatten()

    live, = np.indices(z.shape)  # indexes of pixels that have not escaped
    iterations = np.empty_like(z, dtype=int)

    for i in range(iterations_count):
        z_live = z[live] = mapping(z[live])
        escaped = abs(z_live) > threshold
        iterations[live[escaped]] = i
        live = live[~escaped]
        if live.size == 0:
            break
    else:
        iterations[live] = iterations_count

    return iterations.reshape((height, width))


if __name__ == '__main__':
    mapping = partial(douady_hubbard_polynomial,
                      c=-0.7 + 0.27015j)  # type: Callable[[Complex], Complex]

    image = julia_set(mapping,
                      min_coordinate=-1.5 - 1j,
                      max_coordinate=1.5 + 1j,
                      width=800,
                      height=600)
    plt.axis('off')
    plt.imshow(image,
               cmap='nipy_spectral_r',
               origin='lower')
    plt.show()

Racket

File:JuliaSet racket.png
;; Based on Mandelbrot code (GPL) from:
;;  https://github.com/hebr3/Mandelbrot-Set-Racket/blob/master/Mandelbrot.v6.rkt 
;; Julia set algoithm (and coloring) from:
;;  http://lodev.org/cgtutor/juliamandelbrot.html
;; HSV code (GPL) based on:
;;  https://github.com/takikawa/pict-utils/blob/master/pict-utils/hsv.rkt 

#lang racket

;; Required to generate image
(require picturing-programs)

;; CONSTANTS - NUMBERS
(define DEPTH  300)
(define WIDTH  800)
(define HEIGHT 600)

;; Structures
(struct posn [x y] #:transparent)

;; CONSTANTS - GRAPHIC
(define BACKGROUND (rectangle WIDTH HEIGHT 'solid 'grey))
(define jcnst (posn -0.7 0.27015))

;; PROCEDURES
;; make an RGB color from HSV values
(define (make-color/hsv hue saturation value)
  (define chroma (* saturation value))
  (define hue* (/ (remainder* hue (* 2 pi)) (/ pi 3)))
  (define X (* chroma (- 1 (abs (- (remainder* hue* 2) 1)))))
  (define-values (r1 g1 b1)
    (cond [(and (<= 0 hue*) (< hue* 1)) (values chroma X 0)]
          [(and (<= 1 hue*) (< hue* 2)) (values X chroma 0)]
          [(and (<= 2 hue*) (< hue* 3)) (values 0 chroma X)]
          [(and (<= 3 hue*) (< hue* 4)) (values 0 X chroma)]
          [(and (<= 4 hue*) (< hue* 5)) (values X 0 chroma)]
          [(and (<= 5 hue*) (< hue* 6)) (values chroma 0 X)]))
  (define m (- value chroma))
  (apply make-color (map (λ (x) (exact-round (* 255 (+ x m))))
                         (list r1 g1 b1))))

;; general remainder
(define (remainder* n1 n2)
  (define num-divides (/ n1 n2))
  (- n1 (* (floor num-divides) n2)))

;; Posn -> Number
;; Returns the magnitude of the posn
(define (posn-mag pt)
  (let ([pt-x (posn-x pt)]
        [pt-y (posn-y pt)])
    (sqrt (+ (* pt-x pt-x)
                 (* pt-y pt-y)))))

;; Posn Posn -> Posn
;; Posn addition
(define (posn+ pt1 pt2)
  (let ([pt1-x (posn-x pt1)]
        [pt1-y (posn-y pt1)]
        [pt2-x (posn-x pt2)]
        [pt2-y (posn-y pt2)])
    (posn (+ pt1-x pt2-x)
          (+ pt1-y pt2-y))))

;; Posn Posn -> Posn
;; Posn multiplication
(define (posn* pt1 pt2)
  (let ([x1 (posn-x pt1)]
        [y1 (posn-y pt1)]
        [x2 (posn-x pt2)]
        [y2 (posn-y pt2)])
    (posn (- (* x1 x2) (* y1 y2))
          (+ (* x1 y2) (* x2 y1)))))

;; Posn -> Posn
;; Posn square
(define (posn-sqr pt)
  (posn* pt pt))

;; Posn -> Number
;; Returns the julia set  escape number for a given complex number
;; given in rectangular coordinates.
(define (julia-set-number  start)
  (define (iter result count)
    (cond [(> (posn-mag result) 2) (sub1 count)]
          [(> count DEPTH) DEPTH]
          [else (iter (posn+ jcnst (posn-sqr result))
                      (add1 count))]))
  (iter start 1))

;; Number -> Number
;; Returns the scaled location of a point
(define (scaled-x x)
  (/ (* 1.5 (- x (/ WIDTH 2))) (* 0.5 WIDTH)))
(define (scaled-y y)
  (/ (- y (/ HEIGHT 2)) (* 0.5 HEIGHT)))

;; Generates image
(define M-Image
  (map-image
   (λ (x y c)
     (let* ([ref (julia-set-number  (posn (scaled-x x) (scaled-y y)))])
       (cond [(= ref DEPTH) (name->color 'black)]
             [else (make-color/hsv (* 2 (* pi (/ ref DEPTH))) 1 1)]) ))
 BACKGROUND))

M-Image ;show image if using drracket

(save-image M-Image "julias.png")

Raku

(formerly Perl 6)

Translation of: Perl
with the pallette swapped, just because.
Works with: Rakudo version 2016.03
use Image::PNG::Portable;

my ($w, $h) = 800, 600;
my $out = Image::PNG::Portable.new: :width($w), :height($h);

my $maxIter = 255;
my $c = -0.7 + 0.27015i;

julia($out);

$out.write: 'Julia-set-perl6.png';

sub julia ( $png ) {
    ^$w .race.map: -> $x {
        for ^$h -> $y {
            my $z = Complex.new(($x - $w / 2) / $w * 3, ($y - $h / 2) / $h * 2);
            my $i = $maxIter;
            while (abs($z) < 2 and --$i) {
                $z = $z*$z + $c;
            }
            $png.set: $x, $y, |hsv2rgb($i / $maxIter, 1, ?$i).reverse;
        }
    }
}

sub hsv2rgb ( $h, $s, $v ){
    my $c = $v * $s;
    my $x = $c * (1 - abs( (($h*6) % 2) - 1 ) );
    my $m = $v - $c;
    [(do given $h {
        when   0..^1/6 { $c, $x, 0 }
        when 1/6..^1/3 { $x, $c, 0 }
        when 1/3..^1/2 { 0, $c, $x }
        when 1/2..^2/3 { 0, $x, $c }
        when 2/3..^5/6 { $x, 0, $c }
        when 5/6..1    { $c, 0, $x }
    } ).map: ((*+$m) * 255).Int]
}

REXX

Translation of: AWK
which is a
Translation of: COBOL
/*REXX program  displays  an  ASCII plot   (character plot)   of a  Julia set.          */
parse arg real imag fine .                       /*obtain optional arguments from the CL*/
if real=='' | real==","  then real= -0.8         /*Not specified?  Then use the default.*/
if imag=='' | imag==","  then imag=  0.156       /* "      "         "   "   "     "    */
if fine=='' | fine==","  then fine= 50           /* "      "         "   "   "     "    */
_=scrsize(); parse var _ sd sw; sd=sd-4; sw=sw-1 /*obtain useable area for the terminal.*/
                                                 /*$:  the plot line that is constructed*/
         do   v= -sd%2  to sd%2;     $=          /*step through  vertical   axis values.*/
           do h= -sw%2  to sw%2                  /*  "     "    horizontal    "     "   */
           x=h/sw*2                              /*calculate the initial   X   value.   */
           y=v/sd*2                              /*    "      "     "      Y     "      */
           @='■';    do fine                     /*FINE: is the "fineness" for the plot.*/
                     zr=x*x - y*y + real         /*calculate a new   real   Julia point.*/
                     zi=x*y*2     + imag         /*    "     "  "  imaginal   "     "   */
                     if zr**2>10000  then do; @=' '; leave; end    /*is  ZR  too large? */
                     x=zr;    y=zi                                 /*use this new point.*/
                     end   /*50*/
           $=$ || @                              /*append the plot char to the plot line*/
           end            /*h*/
         if $\=''  then say strip($, 'T')        /*only display a plot line if non-blank*/
         end   /*v*/                             /*stick a fork in it,  we're all done. */

This REXX program makes use of   scrsize   REXX program (or BIF) which is used to determine the screen size of the terminal (console),
and the plot size is adjusted according.


The   SCRSIZE.REX   REXX program is included here   ──►   SCRSIZE.REX.

(final)  output   when using the default input   (screen size was 200x420):

(Shown at   1/6   size.)

output   when using the input of:     -0.8   0.156   50
 
                                                                                                                                                                                                                          ■■
                                                                                                                                                                                                                          ■ ■
                                                                                                                                                                                                                       ■■ ■■
                                                                                                                                                                                                                       ■■■■■■■ ■
                                                                                                                                                                                                                      ■■■■ ■■■
                                                                                                                                                                                                                             ■■■■
                                                                                                                                                                                                                      ■■■■■   ■■
                                                                                                                                                                                                                  ■■■■   ■■  ■■■
                                                                                                                                                                                                                ■■■■■     ■■■
                                                                                                                                                                                                        ■■■■   ■■■■■■              ■■   ■
                                                                                                                                                                                                         ■■■    ■■■■ ■■        ■■■■■■■   ■
                                                                                                                                                                                                          ■      ■■■■■■■■ ■■■■■■■■■■■■■■■■■■■ ■■
                                                                                                                                                                                                          ■■■ ■■■■■■■■■■■  ■■■■■■■■■■■■■■   ■  ■■■
                                                                                                                                                                                                             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■
                                                                                                                                                                                                        ■  ■ ■■■■■■■■■■■■■■  ■■■■■■■■■■■■■ ■
                                                                                                                                                                                                           ■■■■■■■■■■■■■■■    ■■■■■ ■■■■■■■■■■
                                                                                                                                                                                                            ■■■■■■■■■■■ ■    ■■■     ■■■■■■■■■■
                                                                                                                                                                                                                 ■■■■            ■ ■■■■■■■■■■■■ ■
                                                                                                                                                                                                                                         ■■■■   ■ ■
                                                                                                                                                                                                                                     ■■■■■■■■■■
                                                                                                                                                                                                                      ■  ■             ■■■■■■■■■
                                                                                                                                                                                                         ■    ■ ■ ■■■■■■■■■■■■         ■■ ■■■■■■
                                                                                                                                                                                                  ■■■   ■■  ■■■■■■■■        ■■■        ■■■■■■■  ■■
                                                                                                                                                                                      ■  ■       ■■ ■ ■■■■■■■■■ ■            ■■■      ■■ ■■■■■
                                                                                                                                                                                      ■■■■       ■■  ■■■■■■■ ■■        ■■■■■■■■■       ■■■■■
                                                                                                                                                                                        ■     ■■■■■■■■■■■■■■          ■■■ ■■■■■       ■■■■■■ ■
                                                                                                                                                                                     ■■  ■■  ■■■■■■■■■■   ■           ■■■           ■■■■■                                   ■■ ■                            ■■
                                                                                                                                                                                    ■■■      ■■■■■■■■■■■ ■■■           ■■■■■     ■■■■■■■■                         ■         ■■■■                      ■ ■ ■  ■■
                                                                                                                                                       ■        ■                 ■ ■■■  ■■■  ■■■■■■■■■■■■              ■■■■■■■■■■■■■■  ■                          ■   ■■■ ■■■■ ■■                  ■■■■■■ ■ ■
                                                                                                                                                     ■■  ■  ■■■                 ■■■■■■■■■■■■■■■■■■■■■■■■■               ■  ■ ■■■ ■■■                      ■  ■■■■    ■■■■■■  ■ ■     ■    ■         ■■■■■■  ■■
                                                                                                                                                      ■   ■■■■■■■■■■             ■■■■■■■■■■■■■■■■■     ■■ ■                     ■                    ■■  ■   ■■■■■   ■■■■■       ■■■■■■    ■■         ■■■ ■■■■■■
                                                                                                                                                     ■■■ ■■■■■■■■■ ■■■■       ■ ■■■■■■■■■■■■■■■■■■■    ■■■■                                          ■  ■■■■■■■■■■■■■■■■         ■■■■■■■■■■■■■■■■■■        ■■  ■
                                                                                                                                                   ■■  ■■■■■■■      ■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■                                          ■  ■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■■■■■ ■■■■       ■■    ■■■■
                                                                                                                                                       ■■■■■         ■■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■                                        ■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■      ■■■ ■   ■■■
                                                                                                                                                              ■■  ■■  ■■      ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■                                    ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■      ■■■■
                                                                                                                                                             ■■  ■   ■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■                             ■■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■ ■       ■■■■■■■■■ ■
                                                                                                                                                            ■■     ■          ■■ ■■■■■■■■■■■■■■■■■■■■ ■  ■■■  ■■                        ■■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■           ■ ■
                                                                                                                                                         ■ ■■■                  ■■■■■■■■■■■■■■■■■■■■      ■■■ ■■                        ■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
                                                                                                                                                         ■■■■■                ■   ■■■■■■■■■■■■■■■         ■■■■              ■        ■ ■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                                                                                      ■ ■
                                                                                                                                                     ■ ■ ■■■■■■■■             ■■■     ■■■■■■■■■■■                 ■  ■     ■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■    ■ ■ ■■ ■■ ■     ■
                                                                                                                                                      ■  ■ ■■■   ■           ■■        ■■■■■■■■■■■          ■■■■■■■■   ■ ■■■■■■ ■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■  ■■■   ■■■■■■■■■■■■■■■■■  ■                                                                                                      ■ ■■■
                                                                                                                                                      ■■■■■■■■■■■■■■■■■■  ■■■■■■  ■■■ ■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■   ■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■■■■■■■■■■■■■■■■■■■■■                                                                                                            ■■■■
                                                                                                                                                     ■■■■■■■■■■■■■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■ ■■■■■■■    ■■■                                                              ■                               ■■
                                                                                                                                                     ■■■■■■■■■■■■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■               ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■ ■■■   ■■■                                                          ■■■■■■■             ■
                                                                                                                                            ■■ ■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■           ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■     ■■■  ■■ ■                                                         ■■    ■■■       ■■   ■■■■■■■■■■■■■■
                                                                                                                                            ■■■    ■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■  ■■                                                              ■    ■    ■■■■■■■ ■■■■■■■■
                                                                                                                                           ■■■  ■ ■ ■          ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                     ■■■■  ■■■    ■■■■■■■■■■■■■■■      ■■■■
                                                                                                                                           ■   ■           ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■                                                                 ■■■          ■■■■■■■■■■  ■■■      ■■
                                                                                                                                               ■■         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                             ■        ■■■■■          ■■■■■■■■■■■■■           ■■
          ■■■  ■■                                                                                                                              ■■■■■   ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                             ■■  ■  ■■■■■■■■■■■   ■■ ■■■■■■■■■■■■■
            ■■■ ■                                                                                                                             ■  ■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                            ■■  ■■■■■■■   ■■■■■   ■■■■■■ ■   ■ ■■
         ■■■       ■■■■■■ ■                                                                                                                    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■             ■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■ ■  ■■                                    ■■     ■■ ■■■■■■■■■■■■■■■■■■■■■     ■
         ■■■■■  ■■■■■■■                                                                                                                         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■             ■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■    ■■ ■■                                   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■■■■
      ■ ■ ■■■■■■■■■■■■■■■■■■                                        ■                                                                             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■      ■■■■■■■■■■■■          ■■■■■■■■■■■■■■■■■ ■                                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■ ■■
        ■■■■■■■■■  ■■  ■■■■■ ■■                                ■ ■■                                                                      ■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■  ■■■■■■■■■■■■   ■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■                                   ■ ■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■
       ■ ■■■■■■■■         ■■■■                                 ■■■■■■■■                                                                   ■■   ■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■   ■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■ ■■  ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                               ■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■
                          ■■■ ■                   ■                 ■■■■                                                                      ■■ ■  ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                    ■■■■■■■■■■■■■■■     ■■■                    ■■    ■ ■■ ■■■■■      ■■■■■■■■■■■■■■■                               ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■
                   ■      ■■■■                  ■■ ■  ■■  ■■■■■■■■■   ■■                                                                      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                    ■■■■■■■■■■■■■■■       ■■■■■■■■               ■■■■           ■■■  ■■■■■■■■■■■■■■■    ■■                           ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
              ■■■    ■■    ■■                ■■■     ■■■■■■■    ■■■  ■■                                                                       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                     ■■■■■■■  ■■            ■  ■■               ■             ■■■■■■■■■■■■■■■■■■■ ■  ■■■                        ■ ■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
          ■ ■■■   ■■■■■   ■■■          ■ ■■ ■■■■■  ■■■■■■■■     ■■■■■                        ■                                                 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                  ■■■■■■■  ■              ■                                ■■■    ■■■■■■■■■■■■■■■■■                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
       ■ ■■■■■    ■■    ■■■ ■         ■■■■■■■■■■■■■■■■■■■ ■                  ■    ■       ■■                                                    ■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                   ■■■■                                                                   ■■■■■■■■■■■ ■                          ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■■ ■ ■■■■■ ■      ■■■■■ ■■         ■■■■■■■■■■■■■■■■■■■■               ■■■■■■■■■   ■■      ■■■ ■                                             ■■ ■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■              ■■■■■■■■■■■                                                                ■■■■■■■■■■■■■■■■■■ ■■                     ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
  ■   ■■■■■■                       ■ ■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■■■■■■■■■■■■■■      ■                                               ■  ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■           ■■■■■■■■■                                                                  ■   ■■■■■■■■■■■  ■ ■                     ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
  ■■■■■■■   ■■                   ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■ ■■■■■■■■■■■■■■■■■■ ■    ■  ■■                                                   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■    ■■■■■                                                                     ■■■■■■■■                           ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■■■■■■■■■■                      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■                                                              ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■    ■■■■ ■                                                                 ■■■■■■■■■■■■■■                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■                  ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■  ■   ■■■ ■■                                                      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■■■  ■                                                                      ■■■■■■■■■■ ■■■                    ■ ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■ ■■ ■       ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■  ■■■                                     ■■ ■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■  ■■   ■■                                                                         ■■■■■■   ■                       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
  ■■■■■■■■■■   ■■    ■     ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■ ■                                      ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                                      ■■■■■■■■■■■■                         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
    ■■■■■■■     ■■■■■■■■  ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                                         ■■■■■■■■■■                                ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■   ■■■■■■■■■■■■■■■■■■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■ ■ ■                                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■                                                           ■■ ■■■  ■■■■■                 ■■■■■■■  ■■                       ■ ■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■
■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■■■■■■■■■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■                                                   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                      ■■  ■■■■■■■■■■■■■■■■■■              ■■■■■■■■                         ■■ ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■          ■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■                                   ■ ■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■ ■                                                   ■■  ■■■■■■■■■■■■■■■■■■■■■■            ■■■■■■■■                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■■■■   ■■■■■■■■■■■■■    ■■■■■■■■■■■■■■    ■                                  ■ ■■ ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                  ■   ■■■■■■■■■■■■■  ■  ■■■■■■■■■■■        ■■■■■■■■■ ■                           ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■             ■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■■■■■■■■■ ■■■   ■■■■■■■■ ■■■   ■ ■■■■■■■■■■■■■■ ■■                                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                ■■■■ ■■■■■■■■■■         ■■■■■■■■■■          ■■■■■■■ ■■                            ■■■■■■■■■ ■■■■■■■■■■■■■■■■■■■          ■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■■■■■■■■■■■■■■  ■■■■■■            ■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■                                         ■■■■■■■ ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■■■■■■                                                  ■■ ■■■■■■■■ ■         ■■■■■■■■■■■         ■■■■■■■■                                          ■  ■■■■■■■■■■■■■■■■          ■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■  ■■■■■■■■■■■     ■■■■■■                       ■■■   ■■■■   ■■■■■■■■■■■■■■■■ ■■                                                ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■             ■■■■■                                                 ■■■■■■■■■■          ■■■■■■■■■■■■■         ■■■■■■■■                              ■■■■■           ■■■■■■■■■■■■■■■■  ■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■            ■■■■■■■ ■        ■■■                                  ■■■■■■■■■■■■■■■■  ■ ■■                                      ■■■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■               ■■    ■■                                           ■■■■■■■■ ■         ■■■■■■■■■■■■■         ■■■■■■■ ■                           ■■■   ■■■■           ■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■              ■■■■ ■■                                             ■■ ■■■■■■■■■■■■■■                                         ■  ■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■ ■               ■■■  ■■■■■                                     ■■■  ■■■■■■■■          ■■■■■■■■■■■          ■■■■■■■■■                            ■■■■ ■■■             ■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■            ■■■■                                                         ■■■■■■■■■■■                                      ■■  ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                    ■■■■■■■   ■■   ■                                     ■■■■■■■■■■■■         ■■■■■■■■■         ■■■■■■■■ ■■                                  ■■        ■■■■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■■                                                         ■■■■■■■■■■■■■■■■■                                         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                   ■■■■■■    ■■■■                                        ■■■■■■■■■             ■■■■■■■■■■    ■■■■■■■■■■■  ■                                 ■ ■■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■■  ■■■                                                          ■■■■■■■■■■■    ■                                          ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                    ■■■■■■■■■■■                                           ■■■■■■■■■            ■■■■■■■■■■■■■■■■■■■■■ ■                                       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■ ■                                                             ■■■■■■■■                                            ■■■■■■■■■■■■■■■■■■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                          ■                                          ■    ■■■■■■■■■■■            ■■■■■■■■■■■■■■■■■ ■■                                     ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■         ■                                                           ■■■■■■■■■■■■■                                            ■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                    ■ ■■■■■■■■■                  ■    ■■■  ■                                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                       ■■■■■■■■■■■                                                ■■ ■■         ■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■         ■■ ■■                                                ■■■■■■■■■■■                                                                       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                            ■  ■■■    ■                  ■■■■■■■■■ ■                                                                    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■                                            ■■■■■■■■■■■■■                                                           ■         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■                                     ■■ ■■■■■■■■■■■■■■■■■            ■■■■■■■■■■■    ■                                          ■                          ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■■■■■■■■■■■■■■■■■■                                            ■■■■■■■■                                                             ■ ■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                       ■ ■■■■■■■■■■■■■■■■■■■■■            ■■■■■■■■■                                           ■■■■■■■■■■■                    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                          ■    ■■■■■■■■■■■                                                          ■■■  ■■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■■ ■                                 ■  ■■■■■■■■■■■    ■■■■■■■■■■             ■■■■■■■■■                                        ■■■■    ■■■■■■                   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                         ■■■■■■■■■■■■■■■■■                                                         ■■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■■■■        ■■                                  ■■ ■■■■■■■■         ■■■■■■■■■         ■■■■■■■■■■■■                                     ■   ■■   ■■■■■■■                    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■  ■■                                      ■■■■■■■■■■■                                                         ■■■■            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■             ■■■ ■■■■                            ■■■■■■■■■          ■■■■■■■■■■■          ■■■■■■■■  ■■■                                     ■■■■■  ■■■               ■ ■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■  ■                                         ■■■■■■■■■■■■■■ ■■                                             ■■ ■■■■              ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■           ■■■■   ■■■                           ■ ■■■■■■■         ■■■■■■■■■■■■■         ■ ■■■■■■■■                                           ■■    ■■               ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■■■                                      ■■ ■  ■■■■■■■■■■■■■■■■                                  ■■■        ■ ■■■■■■■            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
          ■  ■■■■■■■■■■■■■■■■           ■■■■■                              ■■■■■■■■         ■■■■■■■■■■■■■          ■■■■■■■■■■                                                 ■■■■■             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                ■■ ■■■■■■■■■■■■■■■■   ■■■■   ■■■                       ■■■■■■     ■■■■■■■■■■■  ■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
■■■■          ■■■■■■■■■■■■■■■■  ■                                          ■■■■■■■■         ■■■■■■■■■■■         ■ ■■■■■■■■ ■■                                                  ■■■■■■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■ ■■■■■■■                                         ■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■            ■■■■■■  ■■■■■■■■■■■■■■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
  ■■■          ■■■■■■■■■■■■■■■■■■■ ■■■■■■■■■                            ■■ ■■■■■■■          ■■■■■■■■■■         ■■■■■■■■■■ ■■■■                                                ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                            ■■ ■■■■■■■■■■■■■■ ■   ■■■ ■■■■■■■■   ■■■ ■■■■■■■■■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
  ■             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■                           ■ ■■■■■■■■■        ■■■■■■■■■■■  ■  ■■■■■■■■■■■■■   ■                                                  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■ ■■ ■                                  ■    ■■■■■■■■■■■■■■    ■■■■■■■■■■■■■   ■■■■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■
  ■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                            ■■■■■■■■            ■■■■■■■■■■■■■■■■■■■■■■  ■■                                                   ■ ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■ ■                                   ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■          ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■ ■■                         ■■■■■■■■              ■■■■■■■■■■■■■■■■■■  ■■                                                      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                   ■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■■■■■■■■■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■
■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■ ■                       ■■  ■■■■■■■                 ■■■■■  ■■■ ■■                                                           ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                            ■ ■ ■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■■■■■■■■■■■■■■■■■■   ■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                ■■■■■■■■■■                                                                                         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■  ■■■■■■■■     ■■■■■■■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                         ■■■■■■■■■■■■                                                                                      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■                                      ■ ■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■     ■    ■■   ■■■■■■■■■■
 ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                       ■   ■■■■■■                                                                         ■■   ■■  ■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■ ■■                                     ■■■  ■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■       ■ ■■ ■■■■■■■■■■■■■
  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■ ■                    ■■■ ■■■■■■■■■■                                                                      ■  ■■■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                      ■■ ■■■   ■  ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■                  ■■■■■■■■■■■■■
     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                            ■■■■■■■■■■■■■■                                                                 ■ ■■■■    ■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                              ■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■                      ■■■■■■■■■■
  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                           ■■■■■■■■                                                                     ■■■■■    ■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                   ■■  ■    ■ ■■■■■■■■■■■■■■■■■■ ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■ ■                   ■■   ■■■■■■■
    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■                     ■ ■  ■■■■■■■■■■■   ■                                                                  ■■■■■■■■■           ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■  ■                                               ■      ■■■■■■■■■■■■■■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■ ■                       ■■■■■■   ■
  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■                     ■■ ■■■■■■■■■■■■■■■■■■                                                                ■■■■■■■■■■■              ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■ ■■                                             ■ ■■■      ■■   ■■■■■■■■■               ■■■■■■■■■■■■■■■■■■■■         ■■ ■■■■■      ■ ■■■■■ ■ ■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                          ■ ■■■■■■■■■■■                                                                   ■■■■                   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■                                                    ■■       ■    ■                  ■ ■■■■■■■■■■■■■■■■■■■         ■ ■■■    ■■    ■■■■■ ■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                            ■■■■■■■■■■■■■■■■■    ■■■                                ■              ■  ■■■■■■■                  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                 ■                        ■■■■■     ■■■■■■■■  ■■■■■ ■■ ■          ■■■   ■■■■■   ■■■ ■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■ ■                        ■■■  ■ ■■■■■■■■■■■■■■■■■■■             ■               ■■  ■            ■■  ■■■■■■■                     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                       ■■  ■■■    ■■■■■■■     ■■■                ■■    ■■    ■■■
■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                           ■■    ■■■■■■■■■■■■■■■  ■■■           ■■■■               ■■■■■■■■       ■■■■■■■■■■■■■■■                    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                      ■■   ■■■■■■■■■  ■■  ■ ■■                  ■■■■      ■
■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                               ■■■■■■■■■■■■■■■      ■■■■■ ■■ ■    ■■                    ■■■     ■■■■■■■■■■■■■■■                    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■  ■ ■■                                                                      ■■■■                 ■                   ■ ■■■
■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■                               ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■  ■■ ■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■   ■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■   ■■                                                                   ■■■■■■■■                                 ■■■■         ■■■■■■■■ ■
■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■ ■                                   ■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■   ■■■■■■■■■■■■  ■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■                                                                      ■■ ■                                ■■ ■■■■■  ■■  ■■■■■■■■■
■■ ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                            ■ ■■■■■■■■■■■■■■■■■          ■■■■■■■■■■■■      ■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                             ■                                        ■■■■■■■■■■■■■■■■■■ ■ ■
          ■■■■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                   ■■ ■■    ■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                                                                         ■■■■■■■  ■■■■■
            ■     ■■■■■■■■■■■■■■■■■■■■■ ■■     ■■                                    ■■  ■ ■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■■■■■■■■■■■■             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■                                                                                                                    ■ ■■■■■■       ■■■
         ■■ ■   ■ ■■■■■■   ■■■■■   ■■■■■■■  ■■                                            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■■  ■                                                                                                                             ■ ■■■
            ■■■■■■■■■■■■■ ■■   ■■■■■■■■■■■  ■  ■■                                             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■   ■■■■■                                                                                                                              ■■  ■■■
■■           ■■■■■■■■■■■■■          ■■■■■        ■                                             ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■         ■■
  ■■      ■■■  ■■■■■■■■■■          ■■■                                                                 ■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■           ■   ■
■■■■      ■■■■■■■■■■■■■■■    ■■■  ■■■■                                                                     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■          ■ ■ ■  ■■■
        ■■■■■■■■ ■■■■■■■    ■    ■                                                              ■■  ■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■         ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■    ■■■
 ■■■■■■■■■■■■■■   ■■       ■■■    ■■                                                         ■ ■■  ■■■     ■  ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■           ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■ ■■
               ■             ■■■■■■■                                                          ■■■   ■■■ ■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■               ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■■■■■■■■■■■■
■■                               ■                                                              ■■■    ■■■■■■■ ■■■■■■■■■■■■■■■■■■■■■■■■■     ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■            ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■■■■■■■■■■■■■
■■■■                                                                                                            ■■■■■■■■■■■■■■■■■■■■■■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■■   ■■■■■■■■■■■■■■■■■  ■■■■■■■■■■■■■■■■■ ■■■  ■■■■■■  ■■■■■■■■■■■■■■■■■■
■■■ ■                                                                                                      ■  ■■■■■■■■■■■■■■■■■   ■■■  ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■ ■■■■■■ ■   ■■■■■■■■          ■■■■■■■■■■■        ■■           ■   ■■■ ■  ■
                                                                                                           ■     ■ ■■ ■■ ■ ■    ■      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■■■■     ■  ■                 ■■■■■■■■■■■     ■■■             ■■■■■■■■ ■ ■
 ■ ■                                                                                                                                      ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■    ■■ ■        ■              ■■■■         ■■■■■■■■■■■■■■■   ■                ■■■■■
                                                                                                                                          ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■   ■■■                        ■■ ■■■      ■■■■■■■■■■■■■■■■■■■■                  ■■■ ■
                                                                                                                            ■ ■           ■■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■■                        ■■  ■■■  ■ ■■■■■■■■■■■■■■■■■■■■ ■■          ■     ■■
                                                                                                                       ■ ■■■■■■■■■       ■ ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■■                             ■    ■■■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■   ■  ■■
                                                                                                                      ■■■■      ■■        ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■ ■■                                    ■■■■■■■■■■■■■■■■■■■■■■■■■■ ■      ■■  ■■  ■■
                                                                                                                      ■■■   ■ ■■■      ■■ ■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■■  ■■                                        ■■■■■■■■■■■■■■■■■■■■■■■■■■      ■■■         ■■■■■
                                                                                                                    ■■■■    ■■       ■■■■ ■■■■■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■  ■                                          ■■■■■■■■■■■■■■■■■■■■■■■■■       ■■■      ■■■■■■■  ■■
                                                                                                                   ■  ■■        ■■■■■■■■■■■■■■■■■■         ■■■■■■■■■■■■■■■■  ■                                          ■■■■    ■■■■■■■■■■■■■■■■■■■ ■       ■■■■ ■■■■■■■■■ ■■■
                                                                                                                   ■■■■■■ ■■■         ■■    ■■■■■■       ■■■■■   ■■■■■   ■  ■■                    ■                     ■ ■■     ■■■■■■■■■■■■■■■■■             ■■■■■■■■■■   ■
                                                                                                                     ■■  ■■■■■■         ■    ■     ■ ■  ■■■■■■    ■■■■  ■                      ■■■ ■■■ ■  ■               ■■■■■■■■■■■■■■■■■■■■■■■■■                 ■■■  ■  ■■
                                                                                                                     ■ ■ ■■■■■■                  ■■ ■■■■ ■■■   ■                          ■  ■■■■■■■■■■■■■■              ■■■■■■■■■■■■  ■■■  ■■■ ■                 ■        ■
                                                                                                                    ■■  ■ ■ ■                      ■■■■         ■                         ■■■■■■■■     ■■■■■           ■■■ ■■■■■■■■■■■      ■■■
                                                                                                                     ■■                            ■ ■■                                   ■■■■■           ■■■           ■   ■■■■■■■■■■  ■■  ■■
                                                                                                                                                                                     ■ ■■■■■■       ■■■■■ ■■■          ■■■■■■■■■■■■■■     ■
                                                                                                                                                                                       ■■■■■       ■■■■■■■■■        ■■ ■■■■■■■  ■■       ■■■■
                                                                                                                                                                                     ■■■■■ ■■      ■■■            ■ ■■■■■■■■■ ■ ■■       ■  ■
                                                                                                                                                                                 ■■  ■■■■■■■        ■■■        ■■■■■■■■  ■■   ■■■
                                                                                                                                                                                   ■■■■■■ ■■         ■■■■■■■■■■■■ ■ ■    ■
                                                                                                                                                                                   ■■■■■■■■■             ■  ■
                                                                                                                                                                                    ■■■■■■■■■■
                                                                                                                                                                                ■ ■   ■■■■
                                                                                                                                                                                  ■ ■■■■■■■■■■■■ ■            ■■■■
                                                                                                                                                                                    ■■■■■■■■■■     ■■■    ■ ■■■■■■■■■■■
                                                                                                                                                                                     ■■■■■■■■■■ ■■■■■    ■■■■■■■■■■■■■■■
                                                                                                                                                                                       ■ ■■■■■■■■■■■■■  ■■■■■■■■■■■■■■ ■  ■
                                                                                                                                                                                  ■■■■■   ■■■■■■■■■■■■■■■■■■■■■■■■■■■■
                                                                                                                                                                                 ■■■  ■   ■■■■■■■■■■■■■■  ■■■■■■■■■■■ ■■■
                                                                                                                                                                                   ■■ ■■■■■■■■■■■■■■■■■■■ ■■■■■■■■      ■
                                                                                                                                                                                         ■   ■■■■■■■        ■■ ■■■■    ■■■
                                                                                                                                                                                          ■   ■■              ■■■■■■   ■■■■
                                                                                                                                                                                                      ■■■     ■■■■■
                                                                                                                                                                                                   ■■■  ■■   ■■■■
                                                                                                                                                                                                   ■■   ■■■■■
                                                                                                                                                                                                  ■■■■
                                                                                                                                                                                                     ■■■ ■■■■
                                                                                                                                                                                                   ■ ■■■■■■■
                                                                                                                                                                                                       ■■ ■■
                                                                                                                                                                                                      ■ ■
                                                                                                                                                                                                       ■■    

Other outputs are shown in this Rosetta Code task's   discussion   page.

Ring

# Project : Julia Set

load "guilib.ring"

new qapp 
        {
        win1 = new qwidget() {
                  setwindowtitle("Julia set")
                  setgeometry(100,100,500,400)
                  label1 = new qlabel(win1) {
                              setgeometry(10,10,400,400)
                              settext("")
                  }
                  new qpushbutton(win1) {
                          setgeometry(150,300,100,30)
                          settext("draw")
                          setclickevent("draw()")
                  }
                  show()
        }
        exec()
        }

func draw
        p1 = new qpicture()
               color = new qcolor() {
               setrgb(0,0,255,255)
        }
        pen = new qpen() {
                 setcolor(color)
                 setwidth(1)
        }
        paint = new qpainter() {
                  begin(p1)
                  setpen(pen)

        creal=-0.8
        cimag=0.156
        for v=-16 to 16
             for h=-64 to 64
                   x=h/40
                   y=v/20
                   for i=1 to 50
                         flag = 1
                         zreal=x*x-y*y+creal
                         zimag=x*y*2+cimag
                         if zreal*zreal>1000 flag = 0 loop ok
                         x=zreal
                         y=zimag
                  next 
                  if flag = 1
                     drawpoint(h+100,150-v)
                  ok
             next
        next
        endpaint()
        }
        label1 { setpicture(p1) show() }

Ruby

Translation of: AWK
def julia(c_real, c_imag)
  puts Complex(c_real, c_imag)
  -1.0.step(1.0, 0.04) do |v|
    puts -1.4.step(1.4, 0.02).map{|h| judge(c_real, c_imag, h, v)}.join
  end
end

def judge(c_real, c_imag, x, y)
  50.times do
    z_real = (x * x - y * y) + c_real
    z_imag = x * y * 2 + c_imag
    return " "  if z_real**2 > 10000
    x, y = z_real, z_imag
  end
  "#"
end

julia(-0.8, 0.156)
Output:
-0.8+0.156i
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                                                                                             
                                                                        #                                                                    
                                                                         #                                                                   
                                                                      ##                                                                     
                                                                     #######                                                                 
                                                                      ##  ####                                                               
                                                                            ##                                                               
                                                                # ####  ##  #                                                                
                                                        #      #  ###   ###       # ##     #                                                 
                                                         #    ######          ##########  # #                                                
                                                         # #   ######       ########## #                                                     
                                                         #      ###  ### # ############  ######                         #                    
                                                        ################   ###################   #               #   ###  #                  
                                                         ################ #################### ##              #  ###   ##                   
                         ##                            ##############################    ###  #### #          #######     ###                
                       #  ##        ##               #  #####################  # #### ##    #### ###        ########### ######               
                       # #    #####                     #####################     #              # ##       ######################           
                     ###    ####### ####  #            #######################    #                ###      ############  ###   ##      ##   
                  ## ##  ## #################          ########################                     ###      ###########         ##   ### ###
                  #################  ##  ###### #        # ################### #             #####   ##       ######## #      ### #  ######  
                  ############  ## ##       # ###            ##############   #            ##  ###   ##       #   #### #      # ##     ###   
        ##        ###########  ##             ####          #############    ## #         ##   ### ##         ## #######      ##      #####  
     #########    #############                 ###           #  # ####### #  #           ###                 #############    #########     
  #####      ##      ####### ##         ## ###   ##         # ##    #############          ####             ##  ###########        ##        
   ###     ## #      # ####   #       ##   ###  ##            #   ##############            ### #       ## ##  ############                  
  ######  # ###      # ########       ##   #####             # ################### #        # ######  ##  #################                  
### ###   ##         ###########      ###                     ########################          ################# ##  ## ##                  
   ##      ##   ###  ############      ###                #    #######################            #  #### #######    ###                     
           ######################       ## #              #     #####################                     #####    # #                       
               ###### ###########        ### ####    ## #### #  #####################  #               ##        ##  #                       
                ###     #######          # ####  ###    ##############################                            ##                         
                   ##   ###  #              ## #################### ################                                                         
                  #  ###   #               #   ###################   ################                                                        
                    #                         ######  ############ # ###  ###      #                                                         
                                                     # ##########       ######   # #                                                         
                                                # #  ##########          ######    #                                                         
                                                 #     ## #       ###   ###  #      #                                                        
                                                                #  ##  #### #                                                                
                                                               ##                                                                            
                                                               ####  ##                                                                      
                                                                 #######                                                                     
                                                                     ##                                                                      
                                                                   #                                                                         
                                                                    #                                                                        
Library: RubyGems
Library: JRubyArt

JRubyArt is a port of Processing to the ruby language, here we target same Julia Set as Processing for comparison, produces a colored output

# frozen_string_literal: true

attr_reader :max_iter
CONST = Complex(-0.7, 0.27015)

def setup
  sketch_title 'Julia Set'
  @max_iter = 360
  color_mode HSB, 360, 100, 100
  load_pixels
end

def draw
  grid(width, height) do |x, y|
    i = max_iter
    z = Complex(map1d(x, 0..width, -1.4..1.4), map1d(y, 0..height, -1.0..1.0))
    while z.abs < 2 && i -= 1
      z *= z
      z += CONST
    end 
    pixels[x + width * y] = color((360 * i) / max_iter, 100, i) 
  end 
  update_pixels 
  fill 0 
  text CONST.to_s, 530, 400 
  no_loop 
end

Rust

extern crate image;

use image::{ImageBuffer, Pixel, Rgb};

fn main() {
    // 4 : 3 ratio is nice
    let width = 8000;
    let height = 6000;

    let mut img = ImageBuffer::new(width as u32, height as u32);

    // constants to tweak for appearance
    let cx = -0.9;
    let cy = 0.27015;
    let iterations = 110;

    for x in 0..width {
        for y in 0..height {
            let inner_height = height as f32;
            let inner_width = width as f32;
            let inner_y = y as f32;
            let inner_x = x as f32;

            let mut zx = 3.0 * (inner_x - 0.5 * inner_width) / (inner_width);
            let mut zy = 2.0 * (inner_y - 0.5 * inner_height) / (inner_height);

            let mut i = iterations;

            while zx * zx + zy * zy < 4.0 && i > 1 {
                let tmp = zx * zx - zy * zy + cx;
                zy = 2.0 * zx * zy + cy;
                zx = tmp;
                i -= 1;
            }

            // guesswork to make the rgb color values look okay
            let r = (i << 3) as u8;
            let g = (i << 5) as u8;
            let b = (i << 4) as u8;
            let pixel = Rgb::from_channels(r, g, b, 0);
            img.put_pixel(x as u32, y as u32, pixel);
        }
    }

    let _ = img.save("output.png");

}

Scala

Java Swing Interoperability

import java.awt._
import java.awt.image.BufferedImage

import javax.swing._

object JuliaSet extends App {
  SwingUtilities.invokeLater(() =>
    new JFrame("Julia Set") {

      class JuliaSet() extends JPanel {
        private val (maxIter, zoom) = (300, 1)

        override def paintComponent(gg: Graphics): Unit = {
          val g = gg.asInstanceOf[Graphics2D]

          def drawJuliaSet(g: Graphics2D): Unit = {
            val (w, h) = (getWidth, getHeight)
            val image = new BufferedImage(w, h, BufferedImage.TYPE_INT_RGB)
            val (cX, cY) = (-0.7, 0.27015)
            val moveX, moveY = 0
            var zx, zy = 0.0

            for (x <- 0 until w;
                 y <- 0 until h) {
              zx = 1.5 * (x - w / 2) / (0.5 * zoom * w) + moveX
              zy = (y - h / 2) / (0.5 * zoom * h) + moveY
              var i: Float = maxIter
              while (zx * zx + zy * zy < 4 && i > 0) {
                val tmp = zx * zx - zy * zy + cX
                zy = 2.0 * zx * zy + cY
                zx = tmp
                i -= 1
              }
              val c = Color.HSBtoRGB((maxIter / i) % 1, 1, if (i > 0) 1 else 0)
              image.setRGB(x, y, c)
            }
            g.drawImage(image, 0, 0, null)
          }

          super.paintComponent(gg)
          g.setRenderingHint(RenderingHints.KEY_ANTIALIASING, RenderingHints.VALUE_ANTIALIAS_ON)
          drawJuliaSet(g)
        }

        setBackground(Color.white)
        setPreferredSize(new Dimension(800, 600))
      }

      add(new JuliaSet, BorderLayout.CENTER)
      pack()
      setDefaultCloseOperation(WindowConstants.EXIT_ON_CLOSE)
      setLocationRelativeTo(null)
      setResizable(false)
      setVisible(true)
    }
  )

}

Sidef

require('Imager')

var (w, h) = (640, 480)
var img = %s'Imager'.new(xsize => w, ysize => h, channels => 3)

var maxIter = 50
var c = Complex(-0.388, 0.613)

var color = %s'Imager::Color'.new('#000000')

for x,y in (^w ~X ^h) {
    var i = maxIter
    var z = Complex((x - w/2) / w * 3, (y - h/2) / h * 2)
    while (z.abs < 2 && --i) {
        z = (z*z + c)
    }
    color.set(hsv => [i / maxIter * 360, 1, i])
    img.setpixel(x => x, y => y, color => color)
}

img.write(file => "JuliaSet_sidef.png")

This version generates an ASCII representation:

var (w, h) = (141, 50)

var maxIter = 40
var c = Complex(-0.8, 0.156)

for y in ^h {
    for x in ^w {
        var i = maxIter
        var z = Complex(3 * (x - w/2) / w, 2 * (y - h/2) / h)
        while (z.abs < 2 && --i) {
            z = (z*z + c)
        }
        print (i > 0 ? ' ' : '#')
    }
    print "\n"
}
Output:
                                                                        ##                                                                   
                                                                      ##                                                                     
                                                                     #######                                                                 
                                                                      ########                                                               
                                                                        #   ##                                                               
                                                                 # ###  ##  #                                                                
                                                         #      #####   ####       ##     ##                                                 
                                                          #    ######         ##########   #                                                 
                                                               ########     ##########    #                                                  
                                                          ##   ###### ########################                       ###                     
                                                          ################ ################### ##             ## # ### #                     
                                                        #  #####################################             #  ###  ##                      
                          # #                           ############################# ###########          # ######    ###                   
                          #   #       ##                  ########################### #    ########       ################# #                
                          # #    ####                    #####################  ###             ####      #####################              
                        ###    ############             ######################  # #               ###     ################ ###     # # #     
                        ###  # #################         ######################                    ##      ########### #      ##  ######     
                      ###########################           ####################           ######  ##       ##########     ### #   ###   # ##
                     ################ ##      ######          #################           ######## ##       #  ######     ## ##   ####     ##
         #  #         ########### #             ####         #############   ####        ###  #######       ###########    ##    ######      
        ##########    ############                ##           #  ##########  #           ##                ############    ##########       
       ######    ##    ###########       #######  ###        ####   #############         ####             # ###########         #  #        
###     ####   ## ##     ######  #       ## ########           #################          ######      ## ################                    
 ## #   ###   # ###     ##########       ##  ######           ####################           ###########################                     
      ######  ##      # ###########      ##                    ######################         ################# #  ###                       
      # # #     ### ################     ###               # #  ######################             ############    ###                       
               #####################      ####             ###  #####################                    ####    # #                         
                 # #################       ########    # ###########################                  ##       #   #                         
                    ###    ###### #          ########### #############################                           # #                         
                       ##  ###  #             #####################################  #                                                       
                      # ### # ##             ## ################### ################                                                         
                      ###                       ######################## ######   ##                                                         
                                                   #    ##########     ########                                                              
                                                  #   ##########         ######    #                                                         
                                                  ##     ##       ####   #####      #                                                        
                                                                 #  ##  ### #                                                                
                                                                ##   #                                                                       
                                                                ########                                                                     
                                                                  #######                                                                    
                                                                      ##                                                                     
                                                                    ##

Transact-SQL

This is a Transact-SQL version of SQL Server to generate Julia set. Export the final result to a .ppm file to view the image.

-- Juila Set
-- SQL Server 2017 and above
SET NOCOUNT ON
GO

-- Plot area 800 X 600
DECLARE @width INT = 800
DECLARE @height INT = 600

DECLARE @r_min DECIMAL (10, 8) = -1.5;
DECLARE @r_max DECIMAL (10, 8) = 1.5;
DECLARE @i_min DECIMAL (10, 8) = -1;
DECLARE @i_max DECIMAL (10, 8) = 1;

DECLARE @zoom INT = 1,
		@moveX INT = 0, 
		@moveY INT = 0;

DECLARE @iter INT = 255; -- Iteration

DROP TABLE IF EXISTS dbo.Numbers
DROP TABLE IF EXISTS dbo.julia_set;

CREATE TABLE dbo.Numbers (n INT);

-- Generate a number table of 1000 rows
;WITH N1(n) AS
(
    SELECT 1 UNION ALL SELECT 1 UNION ALL SELECT 1 UNION ALL 
    SELECT 1 UNION ALL SELECT 1 UNION ALL SELECT 1 UNION ALL 
    SELECT 1 UNION ALL SELECT 1 UNION ALL SELECT 1 UNION ALL SELECT 1
), -- 10
N2(n) AS (SELECT 1 FROM N1 CROSS JOIN N1 AS b), -- 10*10
N3(n) AS (SELECT 1 FROM N1 CROSS JOIN N2) -- 10*100
INSERT INTO dbo.Numbers (n)
SELECT n = ROW_NUMBER() OVER (ORDER BY n) 
FROM N3 ORDER BY n;
/*
-- If the version is SQL Server 2022 and above
INSERT INTO dbo.Numbers (n)
SELECT value FROM GENERATE_SERIES(0, 1000);
*/

CREATE TABLE dbo.julia_set
(
	a INT,
	b INT,
	c_re DECIMAL (10, 8),
	c_im DECIMAL (10, 8),
	z_re DECIMAL (10, 8) DEFAULT 0,
	z_im DECIMAL (10, 8) DEFAULT 0,
	znew_re DECIMAL (10, 8) DEFAULT 0,
	znew_im DECIMAL (10, 8) DEFAULT 0,
	steps INT DEFAULT 0,
	active BIT DEFAULT 1,
)

-- Store all the z_re, z_im with constant c_re, c_im corresponding to each point in the plot area
-- Generate 480,000 rows (800 X 600)
INSERT INTO dbo.julia_set (a, b, c_re, c_im, z_re, z_im, steps)
SELECT   a.n as a, b.n as b
		,-0.7 AS c_re
		,0.27015 AS c_im
		,@r_max * (a.n - @width / 2) / (0.5 * @zoom * @width) + @moveX AS z_re
		,@i_max * (b.n - @height / 2) / (0.5 * @zoom * @height) + @moveY AS z_im
		,@iter as steps
FROM
		(
		SELECT n - 1 as n FROM dbo.Numbers WHERE n <= @width
		) as a
CROSS JOIN
		(
		SELECT n - 1 as n FROM dbo.Numbers WHERE n <= @height
		) as b;

-- Iteration
WHILE (@iter > 1)
	BEGIN

		UPDATE dbo.julia_set
		SET
			znew_re = POWER(z_re,2)-POWER(z_im,2)+c_re,
			znew_im = 2*z_re*z_im+c_im,
			steps = steps-1
		WHERE active=1;

		UPDATE dbo.julia_set 
		SET
			z_re=znew_re,
			z_im=znew_im,
			active= CASE
						WHEN POWER(znew_re,2)+POWER(znew_im,2)>4 THEN 0
						ELSE 1
					END
		WHERE active=1;

		SET @iter = @iter - 1;
	END

-- Generating PPM File
-- Save the below query results to a file with extension .ppm
-- NOTE : All the unwanted info like 'rows affected', 'completed time' etc. needs to be 
-- removed from the file. Most of the image editing softwares and online viewers can display the .ppm file
SELECT 'P3' UNION ALL
SELECT CAST(@width AS VARCHAR(5)) + ' ' + CAST(@height AS VARCHAR(5)) UNION ALL
SELECT '255' UNION ALL
SELECT 
	STRING_AGG(CAST(CASE WHEN active = 1 THEN 0 ELSE 55 + steps % 200 END AS VARCHAR(MAX)) + ' ' -- R
	+ CAST(CASE WHEN active = 1 THEN 0 ELSE 55+POWER(steps,3) %  200 END AS VARCHAR(MAX)) + ' '  -- G
	+ CAST(CASE WHEN active = 1 THEN 0 ELSE 55+ POWER(steps,2) % 200 END AS VARCHAR(MAX))		-- B
	, ' ') WITHIN GROUP (ORDER BY a, b)
FROM dbo.julia_set 
GROUP BY a, b

OUTPUT

Julia set in Transact-SQL

VBScript

'ASCII Julia set. Translated from lua. Run with CScript
'Console should be 135x50 to avoid wrapping and scroll
sub pause() wscript.stdout.write  "Press Enter to Continue":wscript.stdin.readline: end sub
cmap=array(" ", ".", ":", "-", "=", "+", "*", "#", "%", "$", "@" )
for y = -1.0 to 1.0 step 0.05
  for x = -1.5 to 1.5 step 0.025
    zr=x
		zi=y
		i=0
    do while i < 100
       zr1 = zr*zr - zi*zi - 0.79 
			 zi=zr * zi * 2 + 0.15
			 zr=zr1
      if (zr*zr + zi*zi) > 4. then exit do
			i = i + 1 
    loop 
    wscript.stdout.write cmap(i\10)
  next
	wscript.stdout.write vbcrlf
Next
pause
Output:

                                                             .:                                                          
                                                          =@=:.#:                                                        
                                                           %@=:@%@                                                       
                                                           ..::::#.                                                      
                                                       :.+=-:+@--%                                                       
                                                 =+- .#+@@::::@-....--@:.@..$@                                           
                                                 .@*:.**=@=::::...=@@@*@@::@-#                                           
                                                 :-:::*@@@-:::::--@@%@*+=+::%+:.                   -@+                   
                                              %@-=@@@==*@**=*@:%#*@@%@@@@@@@*@@#:-.          @:.@@@+:-                   
                       -                       .$-==@%**@@==--*@@@@====@@@-#=@@@%@:        -@+:%@@:::.                   
                      @@:@.     .@            @*:=*@%@@@@*++@%@@@@#-#*-::::=:::*@@#+.    .+%@%*@$=+:%%@@=--              
                      $-$-..@@#*:@... +        .:=#@@@@@%@@@@@*$#@=:::@::::::::::-+%@.....%@@@@*+##@@=*@@@#              
                  ..:@=:::.*@%@=@#%*+:.@.     ..:@@$@@@@%**%==+=*$:::::::::::::::::-+@....@@$@#*@+@@:=::::=-   +:@=      
                  .::@@#-:%*@=*@@-=@@=*@@@.......@-@+@*@@*+@=--==:::::::::::::@$=*---@=....=@=@@=-*=:::::::-@.-@@*#@.    
                  -+@*@@=+@@@*%::::::::@+*$@......@=+@+@@@@@@--@=@::......:-@@===+*--#@....::@@@@@::...:@=@=+.:@@:::-.%@ 
        : .+.     =#@@@@@+#@:::::::::::::-=@-.......:*==*#@@@#@@:::.......:-+=-=+%===@::...:::-#%#@+:...@-:::::##@$.@$-  
      @@-$=@==@+...-+@@+@==@::::::::-#@@----@=.......::=%@@@@@@@%=::.......=@----@@#-::::::::@==@+@@+-...+@==@=$-@@      
  -$@.$@##:::::-@...:+@#%#-:::...::@===%+=-=+-:.......:::@@#@@@#*==*:.......-@=-:::::::::::::@#+@@@@@#=     .+. :        
 @%.-:::@@:.+=@=@:...::@@@@@::....@#--*+===@@-:......::@=@--@@@@@@+@+=@......@$*+@::::::::%*@@@+=@@*@+-                  
    .@#*@@-.@-:::::::=*-=@@=@=....=@---*=$@:::::::::::::==--=@+*@@*@+@-@.......@@@*=@@=-@@*=@*%:-#@@::.                  
      =@:+   -=::::=:@@+@*#@$@@....@+-:::::::::::::::::$*=+==%**%@@@@$@@:..     .@.:+*%#@=@%@*.:::=@:..                  
              #@@@*=@@##+*@@@@%.....@%+-::::::::::@:::=@#$*@@@@@%@@@@@#=:.        + ...@:*#@@..-$-$                      
              --=@@%%:+=$@*%@%+.    .+#@@*:::=::::-*#-#@@@@%@++*@@@@%@*=:*@            @.     .@:@@                      
                   .:::@@%:+@-        :@%@@@=#-@@@====@@@@*--==@@**%@==-$.                       -                       
                   -:+@@@.:@          .-:#@@*@@@@@@@%@@*#%:@*=**@*==@@@=-@%                                              
                   +@-                   .:+%::+=+*@%@@--:::::-@@@*:::-:                                                 
                                           #-@::@@*@@@=...::::=@=**.:*@.                                                 
                                           @$..@.:@--....-@::::@@+#. -+=                                                 
                                                       %--@+:-=+.:                                                       
                                                      .#::::..                                                           
                                                       @%@:=@%                                                           
                                                        :#.:=@=                                                          
                                                          :.    

Wren

Library: DOME
import "graphics" for Canvas, Color
import "dome" for Window

var MaxIters = 300
var Zoom = 1
var MoveX = 0
var MoveY = 0
var CX = -0.7
var CY = 0.27015

class JuliaSet {
    construct new(width, height) {
        Window.title = "Julia Set"
        Window.resize(width, height)
        Canvas.resize(width, height)
        _w = width
        _h = height
    }

    init() {
        Canvas.cls(Color.white)
        createJulia()
    }

    createJulia() {
        for (x in 0..._w) {
            for (y in 0..._h) {
                var zx = 1.5 * (x - _w / 2) / (0.5 * Zoom * _w) + MoveX
                var zy = (y - _h / 2) / (0.5 * Zoom * _h) + MoveY
                var i = MaxIters
                while (zx * zx + zy * zy < 4 && i > 0) {
                    var tmp = zx * zx - zy * zy + CX
                    zy = 2 * zx * zy + CY
                    zx = tmp
                    i = i - 1
                }
                var c = Color.rgb(i % 256, i % 256, (i*8) % 256)
                Canvas.pset(x, y, c)
            }
        }
    }

    update() {}

    draw(alpha) {}
}

var Game = JuliaSet.new(800, 600)
Output:

File:Wren-Julia set.png

XPL0

def  Cx = -0.72, Cy = 0.27;
def  ScrW=800, ScrH=600;
int  X, Y, Iter;
real Zx, Zy, T;
[SetVid($115);
for Y:= 0 to ScrH-1 do
    for X:= 0 to ScrW-1 do
        [Iter:= 0;
        Zx:= 3.2 * float(X-ScrW/2) / float(ScrW);
        Zy:= 2.4 * float(ScrH/2-Y) / float(ScrH);
        while Zx*Zx + Zy*Zy < 4.0 and Iter < 300 do
            [T:= Zx*Zx - Zy*Zy + Cx;
            Zy:= 2.0*Zx*Zy + Cy;
            Zx:= T;
            Iter:= Iter+1;
            ];
        Point(X, Y, Iter<<21+Iter<<8+Iter<<3);
        ];
]


zkl

Uses the PPM class from http://rosettacode.org/wiki/Bitmap/Bresenham%27s_line_algorithm#zkl

Translation of: Java
fcn juliaSet{
   w,h,zoom:=800,600, 1;
   bitmap:=PPM(w,h,0xFF|FF|FF);  // White background

   cX,cY:=-0.7, 0.27015;
   moveX,moveY:=0.0, 0.0;
   maxIter:=255;

   foreach x,y in (w,h){
      zx:=1.5*(x - w/2)/(0.5*zoom*w) + moveX;
      zy:=1.0*(y - h/2)/(0.5*zoom*h) + moveY;
      i:=maxIter;
      while(zx*zx + zy*zy < 4 and i > 1){
	 tmp:=zx*zx - zy*zy + cX;
	 zy,zx=2.0*zx*zy + cY, tmp;
	 i-=1;
      }
      // convert byte to RGB (3 bytes), kinda magic to get nice colors
      bitmap[x,y]=i.shiftLeft(21) + i.shiftLeft(10) + i*8;
   }

   bitmap.writeJPGFile("juliaSet.jpg",True);
}();