15 puzzle game

From Rosetta Code
(Redirected from 15 Puzzle Game)
Task
15 puzzle game
You are encouraged to solve this task according to the task description, using any language you may know.


Task

Implement the Fifteen Puzzle Game.


The   15-puzzle   is also known as:

  •   Fifteen Puzzle
  •   Gem Puzzle
  •   Boss Puzzle
  •   Game of Fifteen
  •   Mystic Square
  •   14-15 Puzzle
  •   and some others.


Related Tasks



11l

T Puzzle
   position = 0
   [Int = String] items

   F main_frame()
      V& d = .items
      print(‘+-----+-----+-----+-----+’)
      print(‘|#.|#.|#.|#.|’.format(d[1], d[2], d[3], d[4]))
      print(‘+-----+-----+-----+-----+’)
      print(‘|#.|#.|#.|#.|’.format(d[5], d[6], d[7], d[8]))
      print(‘+-----+-----+-----+-----+’)
      print(‘|#.|#.|#.|#.|’.format(d[9], d[10], d[11], d[12]))
      print(‘+-----+-----+-----+-----+’)
      print(‘|#.|#.|#.|#.|’.format(d[13], d[14], d[15], d[16]))
      print(‘+-----+-----+-----+-----+’)

   F format(=ch)
      ch = ch.trim(‘ ’)
      I ch.len == 1
         R ‘  ’ch‘  ’
      E I ch.len == 2
         R ‘  ’ch‘ ’
      E
         assert(ch.empty)
         R ‘     ’

   F change(=to)
      V fro = .position
      L(a, b) .items
         I b == .format(String(to))
            to = a
            L.break
      swap(&.items[fro], &.items[to])
      .position = to

   F build_board(difficulty)
      L(i) 1..16
         .items[i] = .format(String(i))
      V tmp = 0
      L(a, b) .items
         I b == ‘  16 ’
            .items[a] = ‘     ’
            tmp = a
            L.break
      .position = tmp
      Int diff
      I difficulty == 0
         diff = 10
      E I difficulty == 1
         diff = 50
      E
         diff = 100
      L 0 .< diff
         V lst = .valid_moves()
         [Int] lst1
         L(j) lst
            lst1.append(Int(j.trim(‘ ’)))
         .change(lst1[random:(lst1.len)])

   F valid_moves()
      V pos = .position
      I pos C [6, 7, 10, 11]
         R [.items[pos - 4], .items[pos - 1], .items[pos + 1], .items[pos + 4]]
      E I pos C [5, 9]
         R [.items[pos - 4], .items[pos + 4], .items[pos + 1]]
      E I pos C [8, 12]
         R [.items[pos - 4], .items[pos + 4], .items[pos - 1]]
      E I pos C [2, 3]
         R [.items[pos - 1], .items[pos + 1], .items[pos + 4]]
      E I pos C [14, 15]
         R [.items[pos - 1], .items[pos + 1], .items[pos - 4]]
      E I pos == 1
         R [.items[pos + 1], .items[pos + 4]]
      E I pos == 4
         R [.items[pos - 1], .items[pos + 4]]
      E I pos == 13
         R [.items[pos + 1], .items[pos - 4]]
      E
         assert(pos == 16)
         R [.items[pos - 1], .items[pos - 4]]

   F game_over()
      V flag = 0B
      L(a, b) .items
         I b != ‘     ’
            I a == Int(b.trim(‘ ’))
               flag = 1B
            E
               flag = 0B
      R flag

V g = Puzzle()
g.build_board(Int(input("Enter the difficulty : 0 1 2\n2 => highest 0 => lowest\n")))
g.main_frame()
print(‘Enter 0 to exit’)
L
   print("Hello user:\nTo change the position just enter the no. near it")
   V lst = g.valid_moves()
   [Int] lst1
   L(i) lst
      lst1.append(Int(i.trim(‘ ’)))
      print(i.trim(‘ ’)" \t", end' ‘’)
   print()
   V x = Int(input())
   I x == 0
      L.break
   E I x !C lst1
      print(‘Wrong move’)
   E
      g.change(x)
   g.main_frame()
   I g.game_over()
      print(‘You WON’)
      L.break
Output:

The same as in Python.

68000 Assembly

This is an entire Sega Genesis game, tested in the Fusion emulator. Thanks to Keith S. of Chibiakumas for the cartridge header, font routines, and printing logic. I programmed the actual game logic. This code can be copied and pasted into a text file and assembled as-is using vasmm68k_mot_win32.exe, no includes or incbins necessary (even the bitmap font is here too.)

;15 PUZZLE GAME
;Ram Variables
Cursor_X equ $00FF0000		;Ram for Cursor Xpos
Cursor_Y equ $00FF0000+1	;Ram for Cursor Ypos
joypad1 equ $00FF0002

GameRam equ $00FF1000		;Ram for where the pieces are
GameRam_End equ $00FF100F	;the last valid slot in the array
;Video Ports
VDP_data	EQU	$C00000	; VDP data, R/W word or longword access only
VDP_ctrl	EQU	$C00004	; VDP control, word or longword writes only

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; 					VECTOR TABLE
;org $00000000
	DC.L	$00FFFFFE		;SP register value
	DC.L	ProgramStart	;Start of Program Code
	DC.L	IntReturn		; bus err
	DC.L	IntReturn		; addr err
	DC.L	IntReturn		; illegal inst
	DC.L	IntReturn		; divzero
	DC.L	IntReturn		; CHK
	DC.L	IntReturn		; TRAPV
	DC.L	IntReturn		; privilege viol
	DC.L	IntReturn		; TRACE
	DC.L	IntReturn		; Line A (1010) emulator
	DC.L	IntReturn		; Line F (1111) emulator
	DC.L	IntReturn,IntReturn,IntReturn,IntReturn		; Reserved /Coprocessor/Format err/ Uninit Interrupt
	DC.L	IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn
	DC.L	IntReturn		; spurious interrupt
	DC.L	IntReturn		; IRQ level 1
	DC.L	IntReturn		; IRQ level 2 EXT
	DC.L	IntReturn		; IRQ level 3
	DC.L	IntReturn		; IRQ level 4 Hsync
	DC.L	IntReturn		; IRQ level 5
	DC.L	IntReturn		; IRQ level 6 Vsync
	DC.L	IntReturn		; IRQ level 7 (NMI)
;org $00000080
;TRAPS
	DC.L	IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn
	DC.L	IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn
;org $000000C0
;FP/MMU
	DC.L	IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn
	DC.L	IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn,IntReturn

	

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;					Header
HEADER:
	DC.B	"SEGA GENESIS    "	        ;System Name	MUST TAKE UP 16 BYTES, USE PADDING IF NECESSARY
	DC.B	"(C)PDS  "			;Copyright	MUST TAKE UP 8 BYTES, USE PADDING IF NECESSARY
 	DC.B	"2022.JUN"			;Date		MUST TAKE UP 8 BYTES, USE PADDING IF NECESSARY
CARTNAME:
	DC.B 	"15 PUZZLE"
CARTNAME_END:
	DS.B 48-(CARTNAME_END-CARTNAME)	;ENSURES PROPER SPACING
CARTNAMEALT:
	DC.B	"15 PUZZLE"
CARTNAMEALT_END:
	DS.B 48-(CARTNAMEALT_END-CARTNAMEALT)	;ENSURES PROPER SPACING
gameID:
	DC.B	"GM PUPPY001-00"	        ;TT NNNNNNNN-RR T=Type (GM=Game) N=game Num  R=Revision
	DC.W	$0000				;16-bit Checksum (Address $000200+)
CTRLDATA:
	DC.B	"J               "	        ;Control Data (J=3button K=Keyboard 6=6button C=cdrom) 
                                                ;(MUST TAKE UP 16 BYTES, USE PADDING IF NECESSARY)
ROMSTART:
	DC.L	$00000000			;ROM Start
ROMLEN:
	DC.L	$003FFFFF			;ROM Length
RAMSTART:
	DC.L	$00FF0000
RAMEND:
	DC.L	$00FFFFFF	;RAM start/end (fixed)

	DC.B	"            "		;External RAM Data	(MUST TAKE UP 12 BYTES, USE PADDING IF NECESSARY)
	DC.B	"            "		;Modem Data		(MUST TAKE UP 12 BYTES, USE PADDING IF NECESSARY)
MEMO:
	DC.B	"                                        "      ;(MUST TAKE UP 40 BYTES, USE PADDING IF NECESSARY)
REGION:
	DC.B	"JUE             "	;Regions Allowed        (MUST TAKE UP 16 BYTES, USE PADDING IF NECESSARY)
	even
HEADER_END:

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;					Generic Interrupt Handler
IntReturn:
	rte                            ;immediately return to game
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;					Program Start
ProgramStart:
	;initialize TMSS (TradeMark Security System)
	move.b ($A10001),D0		;A10001 test the hardware version
	and.b #$0F,D0
	beq	NoTmss				;branch if no TMSS chip
	move.l #'SEGA',($A14000);A14000 disable TMSS 
NoTmss:
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;					Set Up Graphics

	lea VDPSettings,A5		      ;Initialize Screen Registers
	move.l #VDPSettingsEnd-VDPSettings,D1 ;length of Settings
	
	move.w (VDP_ctrl),D0	              ;C00004 read VDP status (interrupt acknowledge?)
	move.l #$00008000,d5	              ;VDP Reg command (%8rvv)
	
NextInitByte:
	move.b (A5)+,D5			      ;get next video control byte
	move.w D5,(VDP_ctrl)	              ;C00004 send write register command to VDP
		;   8RVV - R=Reg V=Value
	add.w #$0100,D5			      ;point to next VDP register
	dbra D1,NextInitByte	              ;loop for rest of block

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;       Set up palette
	
	;Define palette
	move.l #$C0000000,d0	;Color 0 (background)
	move.l d0,VDP_Ctrl
	;        ----BBB-GGG-RRR-
	move.w #%0000011000000000,VDP_data
	
	move.l #$C01E0000,d0	;Color 15 (Font)
	move.l d0,VDP_Ctrl
	move.w #%0000000011101110,VDP_data
	
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;					Set up Font
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

; FONT IS 1BPP, THIS ROUTINE CONVERTS IT TO A 4BPP FORMAT.
	lea Font,A1					 ;Font Address in ROM
	move.l #Font_End-Font,d6	                 ;Our font contains 96 letters 8 lines each
	
	move.l #$40000000,(VDP_Ctrl);Start writes to VRAM address $0000
NextFont:
	move.b (A1)+,d0		;Get byte from font
	moveq.l #7,d5		;Bit Count (8 bits)
	clr.l d1		;Reset BuildUp Byte
	
Font_NextBit:			;1 color per nibble = 4 bytes

	rol.l #3,d1		;Shift BuildUp 3 bits left
	roxl.b #1,d0		;Shift a Bit from the 1bpp font into the Pattern
	roxl.l #1,d1		;Shift bit into BuildUp
	dbra D5,Font_NextBit    ;Next Bit from Font
	
	move.l d1,d0		; Make fontfrom Color 1 to color 15
	rol.l #1,d1		;Bit 1
	or.l d0,d1
	rol.l #1,d1		;Bit 2
	or.l d0,d1
	rol.l #1,d1		;Bit 3
	or.l d0,d1
	
	move.l d1,(VDP_Data);Write next Long of char (one line) to VDP
	dbra d6,NextFont	;Loop until done

	

	clr.b Cursor_X		;Clear Cursor XY
	clr.b Cursor_Y
	
	;Turn on screen
	move.w	#$8144,(VDP_Ctrl);C00004 reg 1 = 0x44 unblank display
	
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; all of the above was just the prep work to boot the Sega Genesis, and had nothing to do with a 15 Puzzle.
; That's hardware for you!

	LEA GameRam,A0        
        ;load the initial state of the puzzle. There is no randomization here unfortunately, as creating a sufficient pseudo-RNG
        ;to make the game "believable" is more difficult than programming the game itself!
        ;so instead we'll start in such a manner that the player has to do quite a bit of work to win.
	MOVE.B #'F',(A0)+
	MOVE.B #'E',(A0)+
	MOVE.B #'D',(A0)+
	MOVE.B #'C',(A0)+
	MOVE.B #'B',(A0)+
	MOVE.B #'A',(A0)+
	MOVE.B #'9',(A0)+
	MOVE.B #'8',(A0)+
	MOVE.B #'7',(A0)+
	MOVE.B #'6',(A0)+
	MOVE.B #'5',(A0)+
	MOVE.B #'4',(A0)+
	MOVE.B #'3',(A0)+
	MOVE.B #'2',(A0)+
	MOVE.B #'1',(A0)+
	MOVE.B #' ',(A0)+

       ;puzzle will look like:
       ;FEDC
       ;BA98
       ;7654
       ;321 

main:
	JSR Player_ReadControlsDual     ;get controller input
	move.w d0,(joypad1)


	;adjust the number of these as you see fit.
	;this affects the game's overall speed.
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank
	JSR waitVBlank

        ;find where the blank space is among GameRAM
	LEA GameRAM,a0
	MOVE.B #' ',D0
	JSR REPNE_SCASB
	MOVE.L A0,A1	
	
;;;;;;;;;;;;;;;;;;; check controller presses
JOYPAD_BITFLAG_M equ 2048
JOYPAD_BITFLAG_Z equ 1024
JOYPAD_BITFLAG_Y equ 512
JOYPAD_BITFLAG_X equ 256
JOYPAD_BITFLAG_S equ 128
JOYPAD_BITFLAG_C equ 64
JOYPAD_BITFLAG_B equ 32
JOYPAD_BITFLAG_A equ 16
JOYPAD_BITFLAG_R equ 8
JOYPAD_BITFLAG_L equ 4
JOYPAD_BITFLAG_D equ 2
JOYPAD_BITFLAG_U equ 1

JOYPAD_BITNUM_M equ 11
JOYPAD_BITNUM_Z equ 10
JOYPAD_BITNUM_Y equ 9
JOYPAD_BITNUM_X equ 8
JOYPAD_BITNUM_S equ 7
JOYPAD_BITNUM_C equ 6
JOYPAD_BITNUM_B equ 5
JOYPAD_BITNUM_A equ 4
JOYPAD_BITNUM_R equ 3
JOYPAD_BITNUM_L equ 2
JOYPAD_BITNUM_D equ 1
JOYPAD_BITNUM_U equ 0




	move.w (joypad1),D0

	BTST #JOYPAD_BITNUM_U,D0
	BNE JoyNotUp
		MOVEM.L D0/A1,-(SP)
			ADDA.L #4,A1
			CMPA.L #GameRam_End,A1
			BHI .doNothing
			;OTHERWISE SWAP THE EMPTY SPACE WITH THE BYTE BELOW IT.
				MOVE.B (A1),D7
				MOVE.B (A0),(A1)
				MOVE.B D7,(A0)	
.doNothing
		MOVEM.L (SP)+,D0/A1
		bra vdraw	
JoyNotUp:
	BTST #JOYPAD_BITNUM_D,D0
	BNE JoyNotDown
		MOVEM.L D0/A1,-(SP)

			SUBA.L #4,A1		;CHECK ONE ROW ABOVE WHERE WE ARE
			CMPA.L #GameRam,A1
			BCS .doNothing		;if A1-4 IS BELOW THE START OF GAME RAM, DON'T MOVE
			;OTHERWISE SWAP THE EMPTY SPACE WITH THE BYTE ABOVE IT.
				MOVE.B (A1),D7
				MOVE.B (A0),(A1)
				MOVE.B D7,(A0)				
.doNothing:
		MOVEM.L (SP)+,D0/A1
		bra vdraw
JoyNotDown:
	BTST #JOYPAD_BITNUM_L,D0
	BNE JoyNotLeft
		MOVEM.L D0/A1,-(SP)
			ADDA.L #1,A1
			MOVE.L A1,D4
			MOVE.L A0,D3
			AND.L #3,D4
			AND.L #3,D3
			CMP.L D3,D4	
			BCS .doNothing
			;OTHERWISE SWAP THE EMPTY SPACE WITH THE BYTE TO THE LEFT
				MOVE.B (A1),D7
				MOVE.B (A0),(A1)
				MOVE.B D7,(A0)				
.doNothing:
		MOVEM.L (SP)+,D0/A1
		bra vdraw
JoyNotLeft:
	BTST #JOYPAD_BITNUM_R,D0
	BNE JoyNotRight
		MOVEM.L D0/A1,-(SP)
			SUBA.L #1,A1
			MOVE.L A1,D4
			MOVE.L A0,D3
			AND.L #3,D4
			AND.L #3,D3
			CMP.L D3,D4	
			BHI .doNothing
			;OTHERWISE SWAP THE EMPTY SPACE WITH THE BYTE TO THE RIGHT
				MOVE.B (A1),D7
				MOVE.B (A0),(A1)
				MOVE.B D7,(A0)				
.doNothing:
		MOVEM.L (SP)+,D0/A1
		bra vdraw
JoyNotRight:

vdraw:
	;this actually draws the current state of the puzzle to the screen.
	LEA GameRam,A0
	CLR.B (Cursor_X)   ;reset text cursors to top left of screen
	CLR.B (Cursor_Y)
	
;draw the puzzle

;anything insize a REPT N...ENDR block is in-lined N times, back to back.
       rept 4

	      MOVE.B (A0)+,D0      
	      JSR PrintChar

	      MOVE.B (A0)+,D0
	      JSR PrintChar

	      MOVE.B (A0)+,D0
	      JSR PrintChar

	      MOVE.B (A0)+,D0
	      JSR PrintChar         ;we just finished drawing one row of the puzzle. Now, begin a new line and continue drawing.

              jsr newline
       endr
	
	
checkIfWin:
	;YES THIS IS MESSY, I TRIED IT WITH A LOOP BUT IT WOULDN'T WORK SO I JUST UNROLLED THE LOOP.
	LEA GameRam,a4
	MOVE.B (A4)+,D5
	CMP.B #'1',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'2',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'3',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'4',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'5',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'6',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'7',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'8',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'9',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'A',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'B',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'C',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'D',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'E',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #'F',D5
	BNE .keepGoing

	MOVE.B (A4)+,D5
	CMP.B #' ',D5
	BNE .keepGoing
	
	clr.b (Cursor_X)
	move.b #7,(Cursor_Y)
	LEA victoryMessage,a3
	jsr PrintString
	jmp *  ;game freezes after you win.

.keepGoing:
;it's unlikely that the label "main" is in range of here so I didn't bother checking and just assumed it was out of range.
;Otherwise I would have said "BEQ main" instead of BNE .keepGoing
	jmp main
		

VictoryMessage:
	DC.B "A WINNER IS YOU",255
	EVEN

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
REPNE_SCASB:
	;INPUT: 
	;A0 = POINTER TO START OF MEMORY
	;D0 = THE BYTE TO SEARCH FOR
	;OUTPUT = A0 POINTS TO THE BYTE THAT CONTAINED D0
	MOVE.B (A0),D1
	CMP.B D0,D1
	BEQ .done
	ADDA.L #1,A0
	BRA REPNE_SCASB
.done:
	RTS
	

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;



Player_ReadControlsDual:
	
	move.b #%01000000,($A1000B)	; Set direction IOIIIIII (I=In O=Out)
	move.l #$A10003,a0		;RW port for player 1

	move.b  #$40,(a0)	; TH = 1
	nop		;Delay
	nop
	move.b  (a0),d2		; d0.b = --CBRLDU	Store in D2
	
	move.b	#$0,(a0)	; TH = 0
	nop		;Delay
	nop
	move.b	(a0),d1		; d1.b = --SA--DU	Store in D1
	
	move.b  #$40,(a0)	; TH = 1
	nop		;Delay
	nop
	move.b	#$0,(a0)	; TH = 0
	nop		;Delay
	nop
	move.b  #$40,(a0)	; TH = 1
	nop		;Delay
	nop
	move.b	(a0),d3		; d1.b = --CBXYZM	Store in D3
	move.b	#$0,(a0)	; TH = 0
	
	clr.l d0			;Clear buildup byte
	roxr.b d2
	roxr.b d0			;U
	roxr.b d2
	roxr.b d0			;D
	roxr.b d2
	roxr.b d0			;L
	roxr.b d2
	roxr.b d0			;R
	roxr.b #5,d1
	roxr.b d0			;A
	roxr.b d2
	roxr.b d0			;B
	roxr.b d2
	roxr.b d0			;C
	roxr.b d1
	roxr.b d0			;S
	
	move.l d3,d1
	roxl.l #7,d1		;XYZ
	and.l #%0000011100000000,d1
	or.l d1,d0			
	
	move.l d3,d1
	roxl.l #8,d1		;M
	roxl.l #3,d1		
	and.l #%0000100000000000,d1
	or.l d1,d0
	
	or.l #$FFFFF000,d0	;Set unused bits to 1

	
	
	;this returns player 1's buttons into D0 as the following:
	;----MZYXSCBARLDU
	rts
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
waitVBlank:							;Bit 3 defines if we're in Vblank
	MOVE.L d0,-(sp)
.wait:
		move.w VDP_ctrl,d0
		and.w #%0000000000001000,d0		;See if vblank is running
		bne .wait					;wait until it is
		
waitVBlank2:
		move.w VDP_ctrl,d0
		and.w #%0000000000001000,d0		;See if vblank is running
		beq waitVBlank2					;wait until it isnt
	MOVE.L (SP)+,d0
	rts		
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
	
PrintChar:				;Show D0 to screen
	moveM.l d0-d7/a0-a7,-(sp)
		and.l #$FF,d0			;Keep only 1 byte
		sub #32,d0				;No Characters in our font below 32
PrintCharAlt:		
		Move.L  #$40000003,d5	;top 4=write, bottom $3=Cxxx range
		clr.l d4					;Tilemap at $C000+

		Move.B (Cursor_Y),D4	
		rol.L #8,D4				;move $-FFF to $-FFF----
		rol.L #8,D4
		rol.L #7,D4				;2 bytes per tile * 64 tiles per line
		add.L D4,D5				;add $4------3
		
		Move.B (Cursor_X),D4
		rol.L #8,D4				;move $-FFF to $-FFF----
		rol.L #8,D4
		rol.L #1,D4				;2 bytes per tile
		add.L D4,D5				;add $4------3
		
		MOVE.L	D5,(VDP_ctrl)	; C00004 write next character to VDP
		MOVE.W	D0,(VDP_data)	; C00000 store next word of name data

		addq.b #1,(Cursor_X)	;INC Xpos
		move.b (Cursor_X),d0
		cmp.b #39,d0
		bls nextpixel_Xok
		jsr NewLine			;If we're at end of line, start newline
nextpixel_Xok:
	moveM.l (sp)+,d0-d7/a0-a7
	rts
	
PrintString:
		move.b (a3)+,d0			;Read a character in from A3
		cmp.b #255,d0
		beq PrintString_Done	;return on 255
		jsr PrintChar			;Print the Character
		bra PrintString
PrintString_Done:		
	rts
	
NewLine:
	addq.b #1,(Cursor_Y)		;INC Y
	clr.b (Cursor_X)			;Zero X
	rts	
	
Font:							
;1bpp font - 8x8 96 characters
;looks just like your typical "8-bit" font. You'll just have to take my word for it.
     DC.B $00,$00,$00,$00,$00,$00,$00,$00,$18,$3c,$3c,$18,$18,$00,$18,$18
     DC.B $36,$36,$12,$24,$00,$00,$00,$00,$00,$12,$7f,$24,$24,$fe,$48,$00
     DC.B $00,$04,$1e,$28,$1c,$0a,$3c,$10,$00,$62,$64,$08,$10,$26,$46,$00
     DC.B $00,$18,$24,$20,$12,$2c,$44,$3a,$18,$18,$08,$10,$00,$00,$00,$00
     DC.B $08,$10,$20,$20,$20,$20,$10,$08,$10,$08,$04,$04,$04,$04,$08,$10
     DC.B $00,$10,$38,$10,$28,$00,$00,$00,$00,$00,$10,$10,$7c,$10,$10,$00
     DC.B $00,$00,$00,$00,$0c,$0c,$04,$08,$00,$00,$00,$00,$7e,$00,$00,$00
     DC.B $00,$00,$00,$00,$00,$18,$18,$00,$01,$02,$04,$08,$10,$20,$40,$00
     DC.B $1c,$26,$63,$63,$63,$32,$1c,$00,$0c,$1c,$0c,$0c,$0c,$0c,$3f,$00
     DC.B $3e,$63,$07,$1e,$3c,$70,$7f,$00,$3f,$06,$0c,$1e,$03,$63,$3e,$00
     DC.B $0e,$1e,$36,$66,$7f,$06,$06,$00,$7e,$60,$7e,$03,$03,$63,$3e,$00
     DC.B $1e,$30,$60,$7e,$63,$63,$3e,$00,$7f,$63,$06,$0c,$18,$18,$18,$00
     DC.B $3c,$62,$72,$3c,$4f,$43,$3e,$00,$3e,$63,$63,$3f,$03,$06,$3c,$00
     DC.B $00,$18,$18,$00,$18,$18,$00,$00,$00,$0c,$0c,$00,$0c,$0c,$04,$08
     DC.B $00,$00,$06,$18,$60,$18,$06,$00,$00,$00,$00,$7e,$00,$7e,$00,$00
     DC.B $00,$00,$60,$18,$06,$18,$60,$00,$1c,$36,$36,$06,$0c,$00,$0c,$0c
     DC.B $3c,$42,$99,$a1,$a1,$99,$42,$3c,$1c,$36,$63,$63,$7f,$63,$63,$00
     DC.B $7e,$63,$63,$7e,$63,$63,$7e,$00,$1e,$33,$60,$60,$60,$33,$1e,$00
     DC.B $7c,$66,$63,$63,$63,$66,$7c,$00,$3f,$30,$30,$3e,$30,$30,$3f,$00
     DC.B $7f,$60,$60,$7e,$60,$60,$60,$00,$1f,$30,$60,$67,$63,$33,$1f,$00
     DC.B $63,$63,$63,$7f,$63,$63,$63,$00,$3f,$0c,$0c,$0c,$0c,$0c,$3f,$00
     DC.B $03,$03,$03,$03,$03,$63,$3e,$00,$63,$66,$6c,$78,$7c,$6e,$67,$00
     DC.B $30,$30,$30,$30,$30,$30,$3f,$00,$63,$77,$7f,$7f,$6b,$63,$63,$00
     DC.B $63,$73,$7b,$7f,$6f,$67,$63,$00,$3e,$63,$63,$63,$63,$63,$3e,$00
     DC.B $7e,$63,$63,$63,$7e,$60,$60,$00,$3e,$63,$63,$63,$6f,$66,$3d,$00
     DC.B $7e,$63,$63,$67,$7c,$6e,$67,$00,$3c,$66,$60,$3e,$03,$63,$3e,$00
     DC.B $3f,$0c,$0c,$0c,$0c,$0c,$0c,$00,$63,$63,$63,$63,$63,$63,$3e,$00
     DC.B $63,$63,$63,$77,$3e,$1c,$08,$00,$63,$63,$6b,$7f,$7f,$77,$63,$00
     DC.B $63,$77,$3e,$1c,$3e,$77,$63,$00,$33,$33,$33,$1e,$0c,$0c,$0c,$00
     DC.B $7f,$07,$0e,$1c,$38,$70,$7f,$00,$00,$38,$20,$20,$20,$20,$38,$00
     DC.B $80,$40,$20,$10,$08,$04,$02,$00,$00,$1c,$04,$04,$04,$04,$1c,$00
     DC.B $10,$28,$44,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$7e,$00
     DC.B $00,$20,$10,$00,$00,$00,$00,$00,$00,$18,$04,$1c,$24,$2c,$1c,$00
     DC.B $00,$20,$20,$38,$24,$24,$38,$00,$00,$00,$1c,$20,$20,$20,$1c,$00
     DC.B $00,$04,$04,$1c,$24,$24,$1c,$00,$00,$00,$1c,$24,$3c,$20,$1c,$00
     DC.B $00,$18,$24,$20,$30,$20,$20,$00,$00,$1c,$24,$24,$1c,$04,$3c,$00
     DC.B $00,$20,$20,$38,$24,$24,$24,$00,$00,$10,$00,$10,$10,$10,$10,$00
     DC.B $08,$00,$08,$08,$08,$08,$28,$10,$20,$20,$24,$28,$30,$28,$24,$00
     DC.B $10,$10,$10,$10,$10,$10,$18,$00,$00,$00,$40,$68,$54,$54,$54,$00
     DC.B $00,$00,$28,$34,$24,$24,$24,$00,$00,$00,$1c,$22,$22,$22,$1c,$00
     DC.B $00,$00,$38,$24,$24,$38,$20,$20,$00,$00,$1c,$24,$24,$1c,$04,$04
     DC.B $00,$00,$2c,$30,$20,$20,$20,$00,$00,$00,$1c,$20,$1c,$02,$3c,$00
     DC.B $00,$10,$3c,$10,$10,$14,$08,$00,$00,$00,$24,$24,$24,$24,$1a,$00
     DC.B $00,$00,$24,$24,$24,$14,$18,$00,$00,$00,$92,$92,$92,$5a,$6c,$00
     DC.B $00,$00,$22,$14,$08,$14,$22,$00,$00,$00,$24,$24,$1c,$04,$18,$00
     DC.B $00,$00,$3c,$04,$18,$20,$3c,$00,$00,$08,$10,$10,$20,$10,$10,$08
     DC.B $18,$18,$18,$18,$18,$18,$18,$18,$00,$10,$08,$08,$04,$08,$08,$10
     DC.B $00,$00,$00,$30,$4a,$04,$00,$00,$1c,$7f,$00,$7f,$55,$55,$55,$00
Font_End:

VDPSettings:
	DC.B $04 ; 0 mode register 1											---H-1M-
	DC.B $04 ; 1 mode register 2											-DVdP---
	DC.B $30 ; 2 name table base for scroll A (A=top 3 bits)				--AAA--- = $C000
	DC.B $3C ; 3 name table base for window (A=top 4 bits / 5 in H40 Mode)	--AAAAA- = $F000
	DC.B $07 ; 4 name table base for scroll B (A=top 3 bits)				-----AAA = $E000
	DC.B $6C ; 5 sprite attribute table base (A=top 7 bits / 6 in H40)		-AAAAAAA = $D800
	DC.B $00 ; 6 unused register											--------
	DC.B $00 ; 7 background color (P=Palette C=Color)						--PPCCCC
	DC.B $00 ; 8 unused register											--------
	DC.B $00 ; 9 unused register											--------
	DC.B $FF ;10 H interrupt register (L=Number of lines)					LLLLLLLL
	DC.B $00 ;11 mode register 3											----IVHL
	DC.B $81 ;12 mode register 4 (C bits both1 = H40 Cell)					C---SIIC
	DC.B $37 ;13 H scroll table base (A=Top 6 bits)							--AAAAAA = $FC00
	DC.B $00 ;14 unused register											--------
	DC.B $02 ;15 auto increment (After each Read/Write)						NNNNNNNN
	DC.B $01 ;16 scroll size (Horiz & Vert size of ScrollA & B)				--VV--HH = 64x32 tiles
	DC.B $00 ;17 window H position (D=Direction C=Cells)					D--CCCCC
	DC.B $00 ;18 window V position (D=Direction C=Cells)					D--CCCCC
	DC.B $FF ;19 DMA length count low										LLLLLLLL
	DC.B $FF ;20 DMA length count high										HHHHHHHH
	DC.B $00 ;21 DMA source address low										LLLLLLLL
	DC.B $00 ;22 DMA source address mid										MMMMMMMM
	DC.B $80 ;23 DMA source address high (C=CMD)							CCHHHHHH
VDPSettingsEnd:
	even
Output:

Screenshot of emulator

AArch64 Assembly

Works with: as version Raspberry Pi 3B version Buster 64 bits
/* ARM assembly AARCH64 Raspberry PI 3B */
/*  program puzzle15_64.s   */

/*******************************************/
/* Constantes file                         */
/*******************************************/
/* for this file see task include a file in language AArch64 assembly*/
.include "../includeConstantesARM64.inc"

.equ NBBOX,  16
.equ GRAINE,  123456      // change for other game
.equ NBSHUFFLE, 4         
.equ KEYSIZE,  8
 
.equ IOCTL,     0x1D  // Linux syscall
.equ SIGACTION, 0x86   // Linux syscall
.equ SYSPOLL,   0x16  // Linux syscall
.equ CREATPOLL, 0x14  // Linux syscall
.equ CTLPOLL,   0x15  // Linux syscall
 
.equ TCGETS,    0x5401
.equ TCSETS,    0x5402
.equ ICANON,    2
.equ ECHO,     10
.equ POLLIN,    1
.equ EPOLL_CTL_ADD,    1

.equ SIGINT,   2    // Issued if the user sends an interrupt signal (Ctrl + C)
.equ SIGQUIT,  3    // Issued if the user sends a quit signal (Ctrl + D)
.equ SIGTERM, 15    // Software termination signal (sent by kill by default)
.equ SIGTTOU, 22    // 

/*******************************************/
/* Structures                               */
/********************************************/
/* structure termios see doc linux*/
    .struct  0
term_c_iflag:                    // input modes
    .struct  term_c_iflag + 4 
term_c_oflag:                    // output modes
    .struct  term_c_oflag + 4 
term_c_cflag:                    // control modes
    .struct  term_c_cflag + 4 
term_c_lflag:                    // local modes
    .struct  term_c_lflag + 4 
term_c_cc:                       // special characters
    .struct  term_c_cc + 20      // see length if necessary 
term_fin:
 
/* structure sigaction see doc linux */
    .struct  0
sa_handler:
    .struct  sa_handler + 8
sa_mask:
    .struct  sa_mask + 8
sa_flags:
    .struct  sa_flags + 8
sa_sigaction:
    .struct  sa_sigaction + 8
sa_fin:

/* structure poll see doc linux */
    .struct  0
poll_event:
    .struct  poll_event + 8
poll_fd:                            //   File Descriptor
    .struct  poll_fd + 8 
poll_fin:
/*********************************/
/* Initialized data              */
/*********************************/
.data
sMessResult:           .ascii " "
sMessValeur:           .fill 11, 1, ' '             // size => 11
szCarriageReturn:      .asciz "\n"
szMessGameWin:         .asciz "You win in @ move number !!!!\n"
szMessMoveError:       .asciz "Huh... Impossible move !!!!\n"
szMessErreur:          .asciz "Error detected.\n"
szMessErrInitTerm:     .asciz "Error terminal init.\n"
szMessErrInitPoll:     .asciz "Error poll init.\n"
szMessErreurKey:       .asciz "Error read key.\n"
szMessSpaces:          .asciz "    "
qGraine:               .quad GRAINE
szMessErr:             .asciz    "Error code hexa : @ décimal : @ \n"

szClear:     .byte 0x1B 
             .byte 'c'                         // console clear
             .byte 0
/*********************************/
/* UnInitialized data            */
/*********************************/
.bss
.align 4
sZoneConv:      .skip 24
qCodeError:     .skip 8
ibox:           .skip 4 * NBBOX                // game boxes
qEnd:           .skip 8                        // 0 loop  1 = end loop
qTouche:        .skip KEYSIZE                  // value key pressed
stOldtio:       .skip term_fin                 // old terminal state
stCurtio:       .skip term_fin                 // current terminal state
stSigAction:    .skip sa_fin                   // area signal structure
stSigAction1:   .skip sa_fin
stSigAction2:   .skip sa_fin
stSigAction3:   .skip sa_fin
stPoll1:        .skip poll_fin                 // area poll structure
stPoll2:        .skip poll_fin
stevents:       .skip 16
/*********************************/
/*  code section                 */
/*********************************/
.text
.global main 
main:                                // entry of program 
    mov x0,#0
    bl initTerm                      // terminal init
    cmp x0,0                         // error ?
    blt 100f
    bl initPoll                      // epoll instance init
    cmp x0,0
    blt 99f
    mov x22,x0                       // save epfd
    ldr x2,qAdribox
    mov x9,#0                        // init counter 
    mov x0,0
1:                                   // loop init boxs
    add x1,x0,#1                     // box value
    str w1,[x2,x0, lsl #2]           // store value
    add x0,x0,#1                     // increment counter
    cmp x0,#NBBOX - 2                // end ?
    ble 1b
    mov x10,#15                      // empty box location 
    ldr x0,qAdribox
    bl shuffleGame
2:                                   // loop moves
    ldr x0,qAdribox
    bl displayGame
3:
    mov x0,x22                       // epfd
    bl waitKey
    cmp x0,0
    beq 3b                           // no ket pressed -> loop
    blt 99f                          // error ?
    bl readKey                       // read key 
    cmp x0,#-1
    beq 99f                          // error  
    cmp x0,3                         // <ctrl_C>
    beq 5f
    cmp x0,113                       // saisie q (quit) ?
    beq 5f
    cmp x0,81                        // saisie Q  (Quit)?
    beq 5f
    mov x1,x0                        // key
    ldr x0,qAdribox
    bl keyMove                       // analyze key move 
    ldr x0,qAdribox
    bl gameOK                        // end game ?
    cmp x0,#1
    bne 2b                           // no -> loop
                                     // win
    mov x0,x9                        // move counter
    ldr x1,qAdrsZoneConv
    bl conversion10
    ldr x0,qAdrszMessGameWin
    ldr x1,qAdrsZoneConv
    bl strInsertAtCharInc            // insert result at @ character
    bl affichageMess
5:
    bl restauTerm                    // terminal restaur
    mov x0, #0                       // return code
    b 100f
99:
    bl restauTerm                    // terminal restaur
    mov x0,1                         // return code error
    b 100f
100:                                 // standard end of the program 
    mov x8, #EXIT                    // request to exit program
    svc #0                           // perform the system call
 
qAdrsMessValeur:          .quad sMessValeur
qAdrszCarriageReturn:     .quad szCarriageReturn
qAdrsMessResult:          .quad sMessResult
qAdribox:                 .quad ibox
qAdrszMessGameWin:        .quad szMessGameWin
qAdrstevents:             .quad stevents
qAdrszMessErreur:         .quad szMessErreur
qAdrstOldtio:             .quad stOldtio
qAdrstCurtio:             .quad stCurtio
qAdrstSigAction:          .quad stSigAction
qAdrstSigAction1:         .quad stSigAction1
qAdrSIG_IGN:              .quad 1
qAdrqEnd:                 .quad qEnd
qAdrqTouche:              .quad qTouche
qAdrszMessErrInitTerm:    .quad szMessErrInitTerm
qAdrszMessErrInitPoll:    .quad szMessErrInitPoll
qAdrszMessErreurKey:      .quad szMessErreurKey
/******************************************************************/
/*     key move                                                   */ 
/******************************************************************/
/* x0 contains boxs address           */
/* x1 contains key value               */
/* x9 move counter                     */
/* x10 contains location empty box    */
keyMove:
    stp x1,lr,[sp,-16]!              // save  registers
    mov x7,x0
    lsr x1,x1,16           
    cmp x1,#0x42                     // down arrow 
    bne 1f
    cmp x10,#4                       // if x10 < 4   error
    blt 80f
    sub x2,x10,#4                    // compute location
    b 90f
1:
    cmp x1,#0x41                     // high arrow
    bne 2f
    cmp x10,#11                      // if x10 > 11   error
    bgt 80f
    add x2,x10,#4                    // compute location
    b 90f
2:
    cmp x1,#0x43                     // right arrow
    bne 3f
    tst x10,#0b11                    // if x10 = 0,4,8,12   error
    beq 80f
    sub x2,x10,#1                    // compute location
    b 90f
3:
    cmp x1,#0x44                     // left arrow
    bne 100f
    and x3,x10,#0b11                 // error if x10 = 3 7 11 and 15
    cmp x3,#3
    beq 80f
    add x2,x10,#1                    // compute location
    b 90f
 
80:                                  // move error
    ldr x0,qAdrqCodeError
    mov x1,#1
    str x1,[x0]
    b 100f
90:                                  // white box and move box inversion
    ldr w3,[x7,x2,lsl #2]
    str w3,[x7,x10,lsl #2]
    mov x10,x2
    mov x3,#0
    str w3,[x7,x10,lsl #2]
    add x9,x9,#1                        // increment move counter
100:
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
qAdrqCodeError:             .quad qCodeError
/******************************************************************/
/*     shuffle game                                       */ 
/******************************************************************/
/* x0 contains boxs address           */
shuffleGame:
    stp x1,lr,[sp,-16]!            // save  registers
    stp x2,x3,[sp,-16]!            // save  registers
    stp x4,x5,[sp,-16]!            // save  registers
    mov x1,x0
    mov x0,NBSHUFFLE
    bl genereraleas
    lsl x4,x0,#1
1:
    mov x0,#14
    bl genereraleas
    add x3,x0,#1
    mov x0,#14
    bl genereraleas
    add x5,x0,#1
    ldr w2,[x1,x3,lsl #2]
    ldr w0,[x1,x5,lsl #2]
    str w2,[x1,x5,lsl #2]
    str w0,[x1,x3,lsl #2]
    subs x4,x4,#1
    bgt 1b
 
100:
    ldp x4,x5,[sp],16              // restaur  2 registers
    ldp x2,x3,[sp],16              // restaur  2 registers
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/******************************************************************/
/*     game Ok ?                                      */ 
/******************************************************************/
/* x0 contains boxs address           */
gameOK:
    stp x1,lr,[sp,-16]!            // save  registers
    stp x2,x3,[sp,-16]!            // save  registers
    mov x2,#0
    ldr w3,[x0,x2,lsl #2]
    add x2,x2,#1
1:
    ldr w1,[x0,x2,lsl #2]
    cmp w1,w3
    bge 2f
    mov x0,#0                      // game not Ok
    b 100f
2:
    mov x3,x1
    add x2,x2,#1
    cmp x2,#NBBOX -2
    ble 1b
    mov x0,#1                      // game Ok
 
100:
    ldp x2,x3,[sp],16              // restaur  2 registers
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/******************************************************************/
/*     display game                                       */ 
/******************************************************************/
/* x0 contains boxs address           */
displayGame:
    stp x1,lr,[sp,-16]!            // save  registers
                                   // clear screen !
    mov x4,x0
    ldr x0,qAdrszClear
    bl affichageMess 
    mov x2,#0
    ldr x1,qAdrsMessValeur
1:
    ldr w0,[x4,x2,lsl #2]
    cmp w0,#0
    bne 2f
    ldr w0,iSpaces                    // store spaces
    str w0,[x1]
    b 3f
2:
    bl conversion10                     // call conversion decimal
    cmp x0,1
    beq 21f
    mov x0,0x20
    strh w0,[x1,#2]
    b 3f
21:
    mov w0,0x2020
    str w0,[x1,#1]
3:
    ldr x0,qAdrsMessResult
    bl affichageMess                    // display message
    add x0,x2,#1
    tst x0,#0b11
    bne 4f
    ldr x0,qAdrszCarriageReturn
    bl affichageMess                    // display message
4:
    add x2,x2,#1
    cmp x2,#NBBOX - 1
    ble 1b
    ldr x0,qAdrszCarriageReturn
    bl affichageMess                    // display line return
    ldr x0,qAdrqCodeError               // error detected ?
    ldr x1,[x0]
    cmp x1,#0
    beq 100f
    mov x1,#0                           // raz error code
    str x1,[x0]
    ldr x0,qAdrszMessMoveError          // display error message
    bl affichageMess
100:
    ldp x1,lr,[sp],16                   // restaur  2 registers
    ret                                 // return to address lr x30
iSpaces:              .int 0x00202020   // spaces
qAdrszClear:          .quad szClear          
qAdrszMessMoveError:  .quad szMessMoveError

/***************************************************/
/*   Generation random number                  */
/***************************************************/
/* x0 contains limit  */
genereraleas:
    stp x1,lr,[sp,-16]!            // save  registers
    stp x2,x3,[sp,-16]!            // save  registers
    ldr x1,qAdrqGraine
    ldr x2,[x1]
    ldr x3,qNbDep1
    mul x2,x3,x2
    ldr x3,qNbDep2
    add x2,x2,x3
    str x2,[x1]                    // maj de la graine pour l appel suivant 
    cmp x0,#0
    beq 100f
    udiv x3,x2,x0
    msub x0,x3,x0,x2               // résult = remainder
 
100:                               // end function
    ldp x2,x3,[sp],16              // restaur  2 registers
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/*****************************************************/
qAdrqGraine: .quad qGraine
qNbDep1:     .quad 0x0019660d
qNbDep2:     .quad 0x3c6ef35f

/******************************************************************/
/*     traitement du signal                                       */ 
/******************************************************************/
sighandler:
    stp x0,lr,[sp,-16]!            // save  registers
    str x1,[sp,-16]! 
    ldr x0,qAdrqEnd
    mov x1,#1                      // maj zone end
    str x1,[x0]
    ldr x1,[sp],16
    ldp x0,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/***************************************************/
/*   display error message                         */
/***************************************************/
/* x0 contains error code  x1 : message address */
displayError:
    stp x2,lr,[sp,-16]!            // save  registers
    mov x2,x0                      // save error code
    mov x0,x1
    bl affichageMess
    mov x0,x2                      // error code
    ldr x1,qAdrsZoneConv
    bl conversion16                // conversion hexa
    ldr x0,qAdrszMessErr           // display error message
    ldr x1,qAdrsZoneConv
    bl strInsertAtCharInc               // insert result at @ character
    mov x3,x0
    mov x0,x2                      // error code
    ldr x1,qAdrsZoneConv               // result address
    bl conversion10S                // conversion decimale
    mov x0,x3
    ldr x1,qAdrsZoneConv
    bl strInsertAtCharInc               // insert result at @ character
    bl affichageMess
100:
    ldp x2,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
qAdrszMessErr:                 .quad szMessErr
qAdrsZoneConv:                 .quad sZoneConv
/*********************************/
/* init terminal state            */
/*********************************/
initTerm:
    stp x1,lr,[sp,-16]!            // save  registers
    /* read terminal state */
    mov x0,STDIN                   // input console
    mov x1,TCGETS
    ldr x2,qAdrstOldtio
    mov x8,IOCTL                   // call system Linux
    svc 0 
    cbnz x0,98f                    // error ?

    adr x0,sighandler              // adresse routine traitement signal
    ldr x1,qAdrstSigAction         // adresse structure sigaction
    str x0,[x1,sa_handler]         // maj handler
    mov x0,SIGINT                  // signal type
    ldr x1,qAdrstSigAction
    mov x2,0
    mov x3,8
    mov x8,SIGACTION               // call system
    svc 0 

    cmp x0,0                       // error ?
    bne 98f
    mov x0,SIGQUIT
    ldr x1,qAdrstSigAction
    mov x2,0                       // NULL
    mov x8,SIGACTION               // call system 
    svc 0 
    cmp x0,0                       // error ?
    bne 98f
    mov x0,SIGTERM
    ldr x1,qAdrstSigAction
    mov x2,0                       // NULL
    mov x8,SIGACTION               // appel systeme 
    svc 0 
    cmp x0,0
    bne 98f
    //
    adr x0,qAdrSIG_IGN             // address signal igonre function
    ldr x1,qAdrstSigAction1
    str x0,[x1,sa_handler]
    mov x0,SIGTTOU                 //invalidate other process signal
    ldr x1,qAdrstSigAction1
    mov x2,0                       // NULL
    mov x8,SIGACTION               // call system 
    svc 0 
    cmp x0,0
    bne 98f
    //
    /* read terminal current state  */
    mov x0,STDIN
    mov x1,TCGETS
    ldr x2,qAdrstCurtio            // address current termio
    mov x8,IOCTL                   // call systeme 
    svc 0 
    cmp x0,0                       // error ?
    bne 98f
    mov x2,ICANON | ECHO           // no key pressed echo on display
    mvn x2,x2                      // and one key 
    ldr x1,qAdrstCurtio
    ldr x3,[x1,#term_c_lflag]
    and x3,x2,x2                   // add flags 
    str x3,[x1,#term_c_lflag]      // and store
    mov x0,STDIN                   // maj terminal current state 
    mov x1,TCSETS
    ldr x2,qAdrstCurtio
    mov x8,IOCTL                   // call system
    svc 0 
    cbz x0,100f
98:                                // error display
    ldr x1,qAdrszMessErrInitTerm
    bl   displayError
    mov x0,-1
100:
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
qAdrstSigAction2:    .quad stSigAction2
qAdrstSigAction3:    .quad stSigAction3
/*********************************/
/* init instance epool            */
/*********************************/
initPoll:
    stp x1,lr,[sp,-16]!            // save  registers
    ldr x0,qAdrstevents
    mov x1,STDIN                   // maj structure events
    str x1,[x0,#poll_fd]           // maj FD
    mov x1,POLLIN                  // action code
    str x1,[x0,#poll_event]
    mov x0,0
    mov x8,CREATPOLL               // create epoll instance
    svc 0
    cmp x0,0                       // error ?
    ble 98f
    mov x10,x0                     // return FD epoll instance
    mov x1,EPOLL_CTL_ADD
    mov x2,STDIN                   // Fd to we want add
    ldr x3,qAdrstevents            // structure events address
    mov x8,CTLPOLL                 // call system control epoll
    svc 0
    cmp x0,0                       // error ?
    blt 98f                       // no
    mov x0,x10                     // return FD epoll instance
    b 100f
98:                                // error display
    ldr x1,qAdrszMessErrInitPoll   // error message
    bl   displayError
    mov x0,-1
100:
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/*********************************/
/* wait key                      */
/*********************************/
/* x0 contains FD poll    */
waitKey:
    stp x1,lr,[sp,-16]!            // save  registers
    ldr x11,qAdrqTouche            // key address
    str xzr,[x11]                  // raz key
1:
    ldr x1,qAdrqEnd                // if signal ctrl-c  -> end
    ldr x1,[x1]
    cbnz x1,100f

    ldr x1,qAdrstevents
    mov x2,12                      // size events
    mov x3,1                       // timeout = 1  TODO: ??
    mov x4,0
    mov x8,SYSPOLL                 // call system wait POLL
    svc 0 
    cmp x0,0                       // key pressed ?
    bge 100f
98:                                // error display
    ldr x1,qAdrszMessErreurKey        // error message
    bl   displayError
    mov x0,-1
100:
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/*********************************/
/* read key                      */
/*********************************/
/* x0 returns key value */
readKey:
    stp x1,lr,[sp,-16]!            // save  registers
    mov x0,STDIN                   // File Descriptor
    ldr x1,qAdrqTouche             // buffer address
    mov x2,KEYSIZE                 // key size
    mov x8,READ                    // read key
    svc #0
    cmp x0,0                       // error ?
    ble 98f
    ldr x2,qAdrqTouche             // key address
    ldr x0,[x2]
    b 100f
98:                                // error display
    ldr x1,qAdrszMessErreur        // error message
    bl   displayError
    mov x0,-1
100:
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30
/*********************************/
/* restaur terminal state        */
/*********************************/
restauTerm:
    stp x1,lr,[sp,-16]!            // save  registers
    mov x0,STDIN                   // end then restaur begin state terminal
    mov x1,TCSETS
    ldr x2,qAdrstOldtio
    mov x8,IOCTL                   // call system  
    svc 0
    cbz x0,100f
    ldr x1,qAdrszMessErreur        // error message
    bl   displayError
100:
    ldp x1,lr,[sp],16              // restaur  2 registers
    ret                            // return to address lr x30

/********************************************************/
/*        File Include fonctions                        */
/********************************************************/
/* for this file see task include a file in language AArch64 assembly */
.include "../includeARM64.inc"

Action!

DEFINE BOARDSIZE="16"
DEFINE X0="13"
DEFINE Y0="6"
DEFINE ITEMW="3"
DEFINE ITEMH="2"

BYTE ARRAY board(BOARDSIZE)
BYTE emptyX,emptyY,solved,first=[1]

BYTE FUNC Index(BYTE x,y)
RETURN (x+y*4)

PROC UpdateItem(BYTE x,y)
  BYTE item

  Position(X0+x*ITEMW+1,Y0+y*ITEMH+1)
  item=board(Index(x,y))
  IF item=0 THEN
    Print("  ")
  ELSEIF item<10 THEN
    Put(160) Put(item+176)
  ELSE
    Put(item/10+176)
    Put(item MOD 10+176)
  FI
RETURN

PROC UpdateBoard()
  BYTE x,y

  FOR y=0 TO 3
  DO
    FOR x=0 TO 3
    DO
      UpdateItem(x,y)     
    OD
  OD
RETURN

PROC DrawGrid()
  CHAR ARRAY
    top=[13 17 18 18 23 18 18 23 18 18 23 18 18 5],
    row=[13 124 32 32 124 32 32 124 32 32 124 32 32 124],
    mid=[13 1 18 18 19 18 18 19 18 18 19 18 18 4],
    bot=[13 26 18 18 24 18 18 24 18 18 24 18 18 3]
  BYTE y,i

  y=Y0
  Position(X0,y) Print(top) y==+1
  Position(X0,y) Print(row) y==+1
  FOR i=0 TO 2
  DO
    Position(X0,y) Print(mid) y==+1
    Position(X0,y) Print(row) y==+1
  OD
  Position(X0,y) Print(bot)
RETURN

PROC DrawBoard()
  DrawGrid()
  UpdateBoard()
RETURN

PROC FindEmpty()
  BYTE i

  FOR i=0 TO BOARDSIZE-1
  DO
    IF board(i)=0 THEN
      emptyX=i MOD 4
      emptyY=i/4
    FI
  OD
RETURN

PROC Wait(BYTE frames)
  BYTE RTCLOK=$14
  frames==+RTCLOK
  WHILE frames#RTCLOK DO OD
RETURN

PROC UpdateStatus()
  Position(9,3) Print("Game status: ")
  IF solved THEN
    Print("SOLVED !")
    IF first=0 THEN
      Sound(0,100,10,5) Wait(5)
      Sound(0,60,10,5) Wait(5)
      Sound(0,40,10,5) Wait(5)
      Sound(0,0,0,0)
    FI
    first=0
  ELSE
    Print("Shuffled")
  FI
RETURN

PROC InitBoard()
  BYTE i
  
  FOR i=1 TO BOARDSIZE
  DO
    board(i-1)=i MOD 16
  OD
  FindEmpty()
  solved=1
  UpdateStatus()
RETURN

BYTE FUNC IsSolved()
  BYTE i

  FOR i=1 TO BOARDSIZE
  DO
    IF board(i-1)#i MOD 16 THEN
      RETURN (0)
    FI
  OD
RETURN (1)

PROC CheckStatus()
  BYTE tmp

  tmp=IsSolved()
  IF solved#tmp THEN
    solved=tmp
    UpdateStatus()
  FI
RETURN

PROC Swap(BYTE x1,y1,x2,y2)
  BYTE tmp,i1,i2

  i1=Index(x1,y1)
  i2=Index(x2,y2)
  tmp=board(i1)
  board(i1)=board(i2)
  board(i2)=tmp
  UpdateItem(x1,y1)
  UpdateItem(x2,y2)
  CheckStatus()
RETURN

PROC Shuffle()
  BYTE i,j,tmp

  i=BOARDSIZE-1
  WHILE i>0
  DO
    j=Rand(i)
    tmp=board(i)
    board(i)=board(j)
    board(j)=tmp
    i==-1
  OD
  FindEmpty()
  UpdateBoard()
  CheckStatus()
RETURN

PROC MoveLeft()
  IF emptyX=0 THEN RETURN FI
  Swap(emptyX,emptyY,emptyX-1,emptyY)
  emptyX==-1
RETURN

PROC MoveRight()
  IF emptyX=3 THEN RETURN FI
  Swap(emptyX,emptyY,emptyX+1,emptyY)
  emptyX==+1
RETURN

PROC MoveUp()
  IF emptyY=0 THEN RETURN FI
  Swap(emptyX,emptyY,emptyX,emptyY-1)
  emptyY==-1
RETURN

PROC MoveDown()
  IF emptyY=3 THEN RETURN FI
  Swap(emptyX,emptyY,emptyX,emptyY+1)
  emptyY==+1
RETURN

PROC Main()
  BYTE k,lastStick=[255],currStick,
    CH=$02FC, ;Internal hardware value for last key pressed
    CRSINH=$02F0 ;Controls visibility of cursor

  Graphics(0)
  SetColor(2,0,2)
  CRSINH=1 ;hide cursor
  Position(10,18) Print("Joystick - move tiles")
  Position(9,19) Print("Space bar - shuffle")
  Position(15,20) Print("ESC - exit")
  InitBoard()
  DrawBoard()
  DO
    currStick=Stick(0)
    IF currStick#lastStick THEN
      IF currStick=11 THEN MoveRight()
      ELSEIF currStick=7 THEN MoveLeft()
      ELSEIF currStick=13 THEN MoveUp()
      ELSEIF currStick=14 THEN MoveDown()
      FI
    FI
    lastStick=currStick
    k=CH
    IF k#$FF THEN CH=$FF FI
    IF k=33 THEN Shuffle()
    ELSEIF k=28 THEN EXIT
    FI
  OD
RETURN
Output:

Screenshot from Atari 8-bit computer

Ada

We fist define a generic package Generic_Puzzle. Upon instantiation, it can take any number of rows, any number of columns for a rows*columns-1 game. Instead of plain numbers, the tiles on the board can have arbitrary names (but they should all be of the same length). The package user can request the name for the tile at a certain (row,column)-point, and the set of possible moves. The user can move the empty space up, down, left and right (if possible). If the user makes the attempt to perform an impossible move, a Constraint_Error is raised.

generic
   Rows, Cols: Positive;
   with function Name(N: Natural) return String; -- with Pre => (N < Rows*Cols);
   -- Name(0) shall return the name for the empty tile
package Generic_Puzzle is

   subtype Row_Type is Positive range 1 .. Rows;
   subtype Col_Type is Positive range 1 .. Cols;
   type Moves is (Up, Down, Left, Right);
   type Move_Arr is array(Moves) of Boolean;
   
   function Get_Point(Row: Row_Type; Col: Col_Type) return String;
   function Possible return Move_Arr;
   procedure Move(The_Move: Moves);

end Generic_Puzzle;

The package implementation is as follows.

package body Generic_Puzzle is
   
   Field: array(Row_Type, Col_Type) of Natural;
   Current_R: Row_Type := Rows;
   Current_C: Col_Type := Cols;
   -- invariant: Field(Current_R, Current_C=0) 
   -- and for all R, C: Field(R, C) < R*C
   -- and for all (R, C) /= (RR, CC): Field(R, C) /= Field(RR, CC)
   
   function Get_Point(Row: Row_Type; Col: Col_Type) return String is
      (Name(Field(Row, Col)));
      
   function Possible return Move_Arr is
      (Up => Current_R > 1, Down => Current_R < Rows,
       Left => Current_C > 1, Right => Current_C < Cols);
      
   procedure Move(The_Move: Moves) is
      Old_R: Row_Type; Old_C: Col_Type; N: Natural;
   begin
      if not Possible(The_Move) then
	 raise Constraint_Error with "attempt to make impossible move";
      else
	 -- remember current row and column
	 Old_R := Current_R;
	 Old_C := Current_C;
	 
	 -- move the virtual cursor to a new position
	 case The_Move is 
	   when Up    => Current_R := Current_R - 1;
	   when Down  => Current_R := Current_R + 1;
	   when Left  => Current_C := Current_C - 1;
	   when Right => Current_C := Current_C + 1;
	 end case;
	 
	 -- swap the tiles on the board
	 N := Field(Old_R, Old_C);
	 Field(Old_R, Old_C) := Field(Current_R, Current_C);
	 Field(Current_R, Current_C) := N;
      end if;
   end Move;

begin
   declare   -- set field to its basic setting
      N: Positive := 1;
   begin
      for R in Row_Type loop
	 for C in Col_Type loop
	    if (R /= Current_R) or else (C /= Current_C) then 
	       Field(R, C) := N;
	       N := N + 1;
	    else
	       Field(R, C) := 0;
	    end if;
	 end loop;
      end loop;
   end;
end Generic_Puzzle;

The main program reads the level from the command line. A larger level implies a more difficult instance. The default level is 10, which is fairly simple. After randomizing the board, the user can move the tiles.

with Generic_Puzzle, Ada.Text_IO, 
     Ada.Numerics.Discrete_Random, Ada.Command_Line;

procedure Puzzle_15 is
   
   function Image(N: Natural) return String is
      (if N=0 then "   " elsif N < 10 then " " & Integer'Image(N)
	else Integer'Image(N));
	
   package Puzzle is new Generic_Puzzle(Rows => 4, Cols => 4, Name => Image);
    
   package Rnd is new Ada.Numerics.Discrete_Random(Puzzle.Moves);
   Rand_Gen: Rnd.Generator;
    
   Level: Natural := (if Ada.Command_Line.Argument_Count = 0 then 10 
                      else Natural'Value(Ada.Command_Line.Argument(1)));
   Initial_Moves: Natural := (2**(Level/2) + 2**((1+Level)/2))/2;
   Texts: constant array(Puzzle.Moves) of String(1..9) :=
       ("u,U,^,8: ", "d,D,v,2: ", "l,L,<,4: ", "r,R,>,6: ");
   Move_Counter: Natural := 0;    
   Command: Character;
       
 begin
    -- randomize board
    for I in 1 .. Initial_Moves loop
       declare
	  M: Puzzle.Moves := Rnd.Random(Rand_Gen);
       begin
	  if Puzzle.Possible(M) then
	     Puzzle.Move(M);
	  end if;
       end;
    end loop;
    
    -- read command and perform move	  
    loop
      -- Print board
      for R in Puzzle.Row_Type loop
	 for C in Puzzle.Col_Type loop
	    Ada.Text_IO.Put(Puzzle.Get_Point(R, C));
	 end loop;
	 Ada.Text_IO.New_Line;
      end loop;
      Ada.Text_IO.Get(Command);
      begin
	 case Command is
	    when 'u' | 'U' | '^' | '8' =>
	       Ada.Text_IO.Put_Line("Up!"); Puzzle.Move(Puzzle.Up);
	    when 'd' | 'D' | 'v' | '2' =>
	       Ada.Text_IO.Put_Line("Down!"); Puzzle.Move(Puzzle.Down);
	    when 'l' | 'L' | '<' | '4' =>
	       Ada.Text_IO.Put_Line("Left!"); Puzzle.Move(Puzzle.Left);
	    when 'r' | 'R' | '>' | '6' =>
	       Ada.Text_IO.Put_Line("Right!"); Puzzle.Move(Puzzle.Right);
	    when '!' => 
	       Ada.Text_IO.Put_Line(Natural'Image(Move_Counter) & " moves!"); 
	       exit;
	    when others => 
	       raise Constraint_Error with "wrong input";
	 end case;
	 Move_Counter := Move_Counter + 1;
      exception when Constraint_Error => 
	 Ada.Text_IO.Put_Line("Possible Moves and Commands:");
	 for M in Puzzle.Moves loop
	    if Puzzle.Possible(M) then
	       Ada.Text_IO.Put(Texts(M) & Puzzle.Moves'Image(M) & "   ");
	    end if;
	 end loop;
	 Ada.Text_IO.Put_Line("!: Quit");
      end;
   end loop;
end Puzzle_15;
Output:
>./puzzle_15 4
  1  2  3  4
  5  6  7  8
  9 14 10 11
 13    15 12
8
Up!
  1  2  3  4
  5  6  7  8
  9    10 11
 13 14 15 12
6
Right!
  1  2  3  4
  5  6  7  8
  9 10    11
 13 14 15 12
5
Possible Moves and Commands:
u,U,^,8: UP   d,D,v,2: DOWN   l,L,<,4: LEFT   r,R,>,6: RIGHT   !: Quit
  1  2  3  4
  5  6  7  8
  9 10    11
 13 14 15 12
6
Right!
  1  2  3  4
  5  6  7  8
  9 10 11   
 13 14 15 12
2
Down!
  1  2  3  4
  5  6  7  8
  9 10 11 12
 13 14 15   
!
 4 moves!

For other puzzles, one must just the single line with the package instantiation. E.g., for an 8-puzzle, we would write the following.

   package Puzzle is new Generic_Puzzle(Rows => 3, Cols => 3, Name => Image);

Amazing Hopper

#include <jambo.h>

#define FILATABLA            5
#define COLUMNATABLA         10
#define Imprimelamatriz      Gosub 'Pone la matriz'
#define Imprimelascasillas   Gosub 'Pone las casillas'
#define Imprimeelíndiceen(_X_,_Y_)  Set '_X_,_Y_',  Gosub 'Pone el índice'

Main
   Set break

   Void (casilla, índice, números)
   Link gosub( Crea una casilla, Crea el índice, Crea la matriz de números )
   
   Cls
   x=4, y=4, Tok sep '""', Gosub 'Imprime escenario'
   
  /* INICIA EL JUEGO */
   SW = 1, GANADOR = 0
   c=0, cero x=4, cero y=4
   
   Loop
       Let ( c:=Getch )
       Switch ( c )
           Case 'KRIGHT'  { #( y < 4 ) do{ ++y }, Exit }
           Case 'KDOWN'   { #( x < 4 ) do{ ++x }, Exit }
           Case 'KLEFT'   { #( y > 1 ) do{ --y }, Exit }
           Case 'KUP'     { #( x > 1 ) do{ --x }, Exit }
           Case 'KRETURN' { If ( Gosub 'Chequear si movimiento es válido' )
                               Gosub 'Mover las casillas'
                            End If
                            Exit
                          }
           Case 'KESCAPE' { SW=0 }
       End switch
       
       Gosub 'Imprime escenario'
       Break if ( Gosub 'Verificar puzzle resuelto' --- Backup to 'GANADOR' )
   Back if 'SW' is not zero

  /* FIN DEL JUEGO */
   If ( GANADOR )
       Locate (18,15), Printnl("LO RESOLVISTE!")
   End If
   Locate (19,1), Prnl
End

Subrutines

/* CHEQUEO DE MOVIMIENTO */

Define ( Verificar puzzle resuelto )
   ret = 0
   Clr all marks
   Tnúmeros=números
   Redim (Tnúmeros,0), N = 0, Let ( N := Length(Tnúmeros) Minus (1))
   i=1
   Iterator ( ++i, Less equal ( i, N ) And( Not(ret) ), \
           Let ( ret := Bit xor(i, [i] Get 'Tnúmeros') ) )
   Clr all marks
   Clear 'Tnúmeros'

Return 'Not (ret); And( Equals(i, Plus one(N)) ) '

Define ( Chequear si movimiento es válido )
Return 'Only one ( Equals (x, cero x), Equals(y, cero y ) )'

Define ( Mover las casillas )
   If ( Equals (y, cero y) )
      If ( Less (x, cero x) )      // mueve hacia abajo
         Loop for ( i = cero x, #( i >= x ) , --i )
             If ( Greater ( i, 1 ) )
                 [{i} Minus(1), y] Get 'números', [i,y] Put 'números'
             Else
                 [{i} Plus(1), y] Get 'números', [i,y] Put 'números'
             End If
         Next
      Else                         // por defecto: mueve hacia arriba
         Loop for ( i = cero x, #( i <= x ) , ++i )
             If ( Less ( i, 4 ) )
                 [{i} Plus(1), y] Get 'números', [i,y] Put 'números'
             Else
                 [i,y] Get 'números', [{i} Minus(1),y] Put 'números'
             End If
         Next
      End If
      [x,y] Set '0', Put 'números'
      Set 'x', Move to 'cero x'
   Else                           // por defecto: está en la misma fila  
      If ( Less ( y, cero y ) )   // mueve hacia la derecha
         Loop for ( i = cero y, #( i >= y ) , --i )
             If ( Greater ( i, 1) )
                 [x, {i} Minus(1)] Get 'números', [x,i] Put 'números'
             Else
                 [x, y] Get 'números', [x, {i} Plus(1)] Put 'números'
             End If
         Next
      Else                        // por defecto: mueve hacia la izquierda
         Loop for ( i = cero y, #( i <= y ) , ++i )
             If ( Less ( i, 4 ) )
                 [x, {i} Plus(1)] Get 'números', [x,i] Put 'números'
             Else
                 [x,i] Get 'números', [x,{i} Minus(1)] Put 'números'
             End If
         Next
      End If
      [x,y] Set '0', Put 'números'
      Set 'y', Move to 'cero y'
   End If
   Clr all marks
Return

/* DESPLIEGUE DE CUADRITOS Y NUMEROS */

Define ( Imprime escenario )
   Imprime las casillas
   Imprime el índice en 'x,y'
   Imprime la matriz
Return

Define ( Pone la matriz )
   i=4, col = COLUMNA TABLA, celda=""
   Clr all marks
   py=1
   Loop
      j=4, fil = FILA TABLA, px=1
      Loop
         Locate 'Plus one(fil), Plus two (col)' 
         Printnl( Get if ([px,py] Get 'números' ---Backup to (celda)---, celda, "  ") )
         fil += 3 
         --j, ++px
      Back if (j) is not zero
      col += 6, --i, ++py
   Back if (i) is not zero
Return

Define ( Pone las casillas )
   i=4, col = COLUMNA TABLA
   Clr all marks
   Loop
      j=4, fil = FILA TABLA
      Loop
         Set 'fil, col', Gosub 'Pone un cuadrito'
         fil += 3, --j
      Back if (j) is not zero
      col += 6, --i
   Back if (i) is not zero
Return

Define (Pone un cuadrito, fil, col)
   Locate 'fil, col', Print table 'casilla'
Return

Define ( Pone el índice, fil, col )
   /* 5+(fil-1)*3 fila
      10+(col-1)*6 col */
   Clr all marks
   Locate 'Minus one(fil) Mul by (3) Plus (FILA TABLA), Minus one(col) Mulby(6) Plus(COLUMNA TABLA)' 
   Print table 'índice'
Return

/* CONFIGURACION DEL JUEGO */

Define ( Crea la matriz de números )
   Sequence ( 0, 1, 16, números )
   Gosub 'Barajar el array'
   Redim ( números, 4,4 )
Return

/* algoritmo de Fisher-Yates */
Define ( Barajar el array )
  N = 0, Let ( N := Length(números) )
  R = 0, aux = 0
  Loop
     Let (R := Ceil(Rand(N)))
     Let (aux := [R] Get 'números' )
     [N] Get 'números', [R] Put 'números'
     Set 'aux', [N] Put 'números'
     --N
  Back if 'N' is positive
  If ( [16] Get 'números' ---Backup to 'aux'---, Not (Is zero?) )
     [aScan(1,0,números)] Set 'aux', Put 'números'
     [16] Set '0', Put 'números'
  End If
Return

Define ( Crea una casilla )
   Set 'Utf8(Chr(218)),Utf8(Chr(196)),Utf8(Chr(196)),Utf8(Chr(196)),Utf8(Chr(196)),Utf8(Chr(191))', Apnd row 'casilla'
   Set 'Utf8(Chr(179))," "," "," "," ",Utf8(Chr(179))', Apnd row 'casilla'
   Set 'Utf8(Chr(192)),Utf8(Chr(196)),Utf8(Chr(196)),Utf8(Chr(196)),Utf8(Chr(196)),Utf8(Chr(217))', Apnd row 'casilla'
Return

Define ( Crea el índice )
   Set 'Utf8(Chr(220)),Utf8(Chr(220)),Utf8(Chr(220)),Utf8(Chr(220)),Utf8(Chr(220)),Utf8(Chr(220))', Apnd row 'índice'
   Set 'Utf8(Chr(219))," "," "," "," ",Utf8(Chr(219))', Apnd row 'índice'
   Set 'Utf8(Chr(223)),Utf8(Chr(223)),Utf8(Chr(223)),Utf8(Chr(223)),Utf8(Chr(223)),Utf8(Chr(223))', Apnd row 'índice'
Return
Output:
$ hopper jm/puzzle.jambo
         ┌────┐┌────┐┌────┐┌────┐
         │ 14 ││ 5  ││ 3  ││ 12 │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐┌────┐
         │ 13 ││ 9  ││ 6  ││ 11 │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐┌────┐
         │ 15 ││ 10 ││ 8  ││ 2  │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐▄▄▄▄▄▄
         │ 4  ││ 1  ││ 7  │█    █
         └────┘└────┘└────┘▀▀▀▀▀▀
         ..... (muchos click)
         ┌────┐┌────┐┌────┐┌────┐
         │ 7  ││ 10 ││ 14 ││ 12 │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐┌────┐
         │ 15 ││    ││ 4  ││ 2  │
         └────┘└────┘└────┘└────┘
         ┌────┐▄▄▄▄▄▄┌────┐┌────┐
         │ 1  │█ 8  █│ 6  ││ 11 │
         └────┘▀▀▀▀▀▀└────┘└────┘
         ┌────┐┌────┐┌────┐┌────┐
         │ 3  ││ 13 ││ 5  ││ 9  │
         └────┘└────┘└────┘└────┘
         ....( muy muchos clicks )
         ┌────┐┌────┐┌────┐┌────┐
         │ 1  ││ 2  ││ 3  ││ 4  │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐┌────┐
         │ 5  ││ 6  ││ 7  ││ 8  │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐┌────┐
         │ 9  ││ 10 ││ 11 ││ 12 │
         └────┘└────┘└────┘└────┘
         ┌────┐┌────┐┌────┐▄▄▄▄▄▄
         │ 13 ││ 14 ││ 15 │█    █
         └────┘└────┘└────┘▀▀▀▀▀▀

              LO RESOLVISTE!

APL

Works with: Dyalog APL version 16.0
fpg{⎕IO0
    4 4
    (s.<0)2≠⍴s⍺:'invalid shape:'s
    0≠⍴⍴⍵:'invalid shuffle count:'
    dd,-d2 231
    e¯1+⍴c'↑↓←→○'
    bwsw1⌽⍳×/s
    z{
        z p
        n(?⍴p)p(p¨(s)|p)/p(d~p)+⊂z
        b[z n]b[n z]
        -⍨\n z
    }(s-1)0
    b
    {
        bw:'win'
        0=⍴⍺: 
        e=icm⍺:'quit'
        i>e: 'invalid direction:'m
        ns|n+id: 'out of bounds:'m
        b[ n]b[n ]
        (s×0≠⍴)b
        (1) n
    }z
}
Output:
      fpg 10
 1  3  0  4
 5  2  6  8
 9 10  7 12
13 14 11 15
←
 1  0  3  4
 5  2  6  8
 9 10  7 12
13 14 11 15
↓
 1  2  3  4
 5  0  6  8
 9 10  7 12
13 14 11 15
→
 1  2  3  4
 5  6  0  8
 9 10  7 12
13 14 11 15
↓↓
 1  2  3  4
 5  6  7  8
 9 10 11 12
13 14  0 15
→
 1  2  3  4
 5  6  7  8
 9 10 11 12
13 14 15  0
win


      2 5 fpg 2
1 2 3 0 4
6 7 8 9 5
→
1 2 3 4 0
6 7 8 9 5
↓
1 2 3 4 5
6 7 8 9 0
win

ARM Assembly

Works with: as version Raspberry Pi
/* ARM assembly Raspberry PI  */
/*  program puzzle15.s   */
 
/************************************/
/* Constantes                       */
/************************************/
.equ STDIN,  0     @ Linux input console
.equ STDOUT, 1     @ Linux output console
.equ EXIT,   1     @ Linux syscall
.equ READ,   3     @ Linux syscall
.equ WRITE,  4     @ Linux syscall

.equ IOCTL,     0x36  @ Linux syscall
.equ SIGACTION, 0x43  @ Linux syscall
.equ SYSPOLL,   0xA8  @ Linux syscall

.equ TCGETS,    0x5401
.equ TCSETS,    0x5402
.equ ICANON,    2
.equ ECHO,     10
.equ POLLIN,    1

.equ SIGINT,   2    @ Issued if the user sends an interrupt signal (Ctrl + C)
.equ SIGQUIT,  3    @ Issued if the user sends a quit signal (Ctrl + D)
.equ SIGTERM, 15    @ Software termination signal (sent by kill by default)
.equ SIGTTOU, 22    @ 

.equ NBBOX,  16
.equ TAILLEBUFFER,   10

/*******************************************/
/* Structures                               */
/********************************************/
/* structure termios see doc linux*/
    .struct  0
term_c_iflag:                    @ input modes
    .struct  term_c_iflag + 4 
term_c_oflag:                    @ output modes
    .struct  term_c_oflag + 4 
term_c_cflag:                    @ control modes
    .struct  term_c_cflag + 4 
term_c_lflag:                    @ local modes
    .struct  term_c_lflag + 4 
term_c_cc:                       @ special characters
    .struct  term_c_cc + 20      @ see length if necessary 
term_fin:

/* structure sigaction see doc linux */
    .struct  0
sa_handler:
    .struct  sa_handler + 4 
sa_mask:
    .struct  sa_mask + 4 
sa_flags:
    .struct  sa_flags + 4 
sa_sigaction:
    .struct  sa_sigaction + 4 
sa_fin:

/* structure poll see doc linux */
    .struct  0
poll_fd:                            @   File Descriptor
    .struct  poll_fd + 4 
poll_events:                        @  events mask
    .struct  poll_events + 4 
poll_revents:                       @ events returned
    .struct  poll_revents + 4 
poll_fin:
/*********************************/
/* Initialized data              */
/*********************************/
.data
sMessResult:           .ascii " "
sMessValeur:           .fill 11, 1, ' '             @ size => 11
szCarriageReturn:      .asciz "\n"
szMessGameWin:         .ascii "You win in "
sMessCounter:           .fill 11, 1, ' '            @ size => 11
                       .asciz " move number !!!!\n"
szMessMoveError:       .asciz "Huh... Impossible move !!!!\n"
szMessErreur:          .asciz "Error detected.\n"
szMessSpaces:          .asciz "    "
iGraine:               .int 123456
/*************************************************/
szMessErr: .ascii	"Error code hexa : "
sHexa: .space 9,' '
         .ascii "  decimal :  "
sDeci: .space 15,' '
         .asciz "\n"
szClear:     .byte 0x1B 
		     .byte 'c'                         @ console clear
		     .byte 0
/*********************************/
/* UnInitialized data            */
/*********************************/
.bss
.align 4
iCodeError:     .skip 4
ibox:          .skip 4 * NBBOX                 @ game boxes
iEnd:           .skip 4                        @ 0 loop  1 = end loop
iTouche:        .skip 4                        @ value key pressed
stOldtio:       .skip term_fin                 @ old terminal state
stCurtio:       .skip term_fin                 @ current terminal state
stSigAction:    .skip sa_fin                   @ area signal structure
stSigAction1:   .skip sa_fin
stPoll1:        .skip poll_fin                 @ area poll structure
stPoll2:        .skip poll_fin
/*********************************/
/*  code section                 */
/*********************************/
.text
.global main 
main:                                @ entry of program 
    mov r0,#0
    ldr r2,iAdribox
    mov r9,#0                        @ move counter 
1:                                   @ loop init boxs
    add r1,r0,#1                     @ box value
    str r1,[r2,r0, lsl #2]           @ store value
    add r0,#1                        @ increment counter
    cmp r0,#NBBOX - 2                @ end ?
    ble 1b
    mov r10,#15                      @ empty box location 
    ldr r0,iAdribox
    bl shuffleGame
2:                                   @ loop moves
    ldr r0,iAdribox
    bl displayGame
    //ldr r0,iAdribox
    //bl gameOK                      @ end game ?
    //cmp r0,#1
    //beq 50f
    bl readKey                       @ read key 
    cmp r0,#-1
    beq 100f                         @ error or control-c
    mov r1,r0                        @ key
    ldr r0,iAdribox
    bl keyMove
    ldr r0,iAdribox
    bl gameOK                        @ end game ?
    cmp r0,#1
    bne 2b                           @ no -> loop
50:                                  @ win
    mov r0,r9                        @ move counter
    ldr r1,iAdrsMessCounter
    bl conversion10
    ldr r0,iAdrszMessGameWin
    bl affichageMess

100:                                 @ standard end of the program 
    mov r0, #0                       @ return code
    mov r7, #EXIT                    @ request to exit program
    svc #0                           @ perform the system call
 
iAdrsMessValeur:          .int sMessValeur
iAdrszCarriageReturn:     .int szCarriageReturn
iAdrsMessResult:          .int sMessResult
iAdribox:                 .int ibox
iAdrszMessGameWin:        .int szMessGameWin
iAdrsMessCounter:         .int sMessCounter
/******************************************************************/
/*     key move                                                   */ 
/******************************************************************/
/* r0 contains boxs address           */
/* r1 contains key value               */
/* r9 move counter                     */
/* r10 contains location empty box    */
keyMove:
    push {r1-r8,lr}                  @ save  registers
    mov r8,r0
    cmp r1,#0x42                     @ down arrow 
    bne 1f
    cmp r10,#4                       @ if r10 < 4   error
    blt 80f
    sub r2,r10,#4                    @ compute location
    b 90f
1:
    cmp r1,#0x41                     @ high arrow
    bne 2f
    cmp r10,#11                      @ if r10 > 11   error
    bgt 80f
    add r2,r10,#4                    @ compute location
    b 90f
2:
    cmp r1,#0x43                     @ right arrow
    bne 3f
    tst r10,#0b11                    @ if r10 = 0,4,8,12   error
    beq 80f
    sub r2,r10,#1                    @ compute location
    b 90f
3:
    cmp r1,#0x44                     @ left arrow
    bne 100f
    and r3,r10,#0b11                 @ error if r10 = 3 7 11 and 15
    cmp r3,#3
    beq 80f
    add r2,r10,#1                    @ compute location
    b 90f

80:                                  @ move error
    ldr r0,iAdriCodeError
    mov r1,#1
    str r1,[r0]
    b 100f
90:                                  @ white box and move box inversion
    ldr r3,[r8,r2,lsl #2]
    str r3,[r8,r10,lsl #2]
    mov r10,r2
    mov r3,#0
    str r3,[r8,r10,lsl #2]
    add r9,#1                        @ increment move counter
100:
    pop {r1-r8,lr}                   @ restaur registers 
    bx lr                            @return
iAdriCodeError:             .int iCodeError
/******************************************************************/
/*     shuffle game                                       */ 
/******************************************************************/
/* r0 contains boxs address           */
shuffleGame:
    push {r1-r6,lr}                     @ save  registers
    mov r1,r0
    mov r0,#4
    bl genereraleas
    lsl r4,r0,#1
    mov r0,r8
1:
    mov r0,#14
    bl genereraleas
    add r6,r0,#1
    mov r0,#14
    bl genereraleas
    add r5,r0,#1
    ldr r2,[r1,r6,lsl #2]
    ldr r3,[r1,r5,lsl #2]
    str r2,[r1,r5,lsl #2]
    str r3,[r1,r6,lsl #2]
    subs r4,#1
    bgt 1b

100:
    pop {r1-r6,lr}                      @ restaur registers 
    bx lr                               @return
/******************************************************************/
/*     game Ok ?                                      */ 
/******************************************************************/
/* r0 contains boxs address           */
gameOK:
    push {r1-r8,lr}                     @ save  registers
    mov r8,r0
    mov r2,#0
    ldr r3,[r8,r2,lsl #2]
    add r2,#1
1:
    ldr r4,[r8,r2,lsl #2]
    cmp r4,r3
    movlt r0,#0                         @ game mot Ok
    blt 100f
    mov r3,r4
    add r2,#1
    cmp r2,#NBBOX -2
    ble 1b
    mov r0,#1                           @ game Ok

100:
    pop {r1-r8,lr}                      @ restaur registers 
    bx lr                               @return
/******************************************************************/
/*     display game                                       */ 
/******************************************************************/
/* r0 contains boxs address           */
displayGame:
    push {r1-r5,lr}                     @ save  registers
    @ clear !
    mov r4,r0
    ldr r0,iAdrszClear
    bl affichageMess 
    mov r2,#0
    ldr r1,iAdrsMessValeur
1:
    ldr r0,[r4,r2,lsl #2]
    cmp r0,#0
    ldreq r0,iSpaces                    @ store spaces
    streq r0,[r1]
    beq 2f
    bl conversion10                     @ call conversion decimal
    mov r0,#0
    strb r0,[r1,#3]                     @ zéro final
2:

    ldr r0,iAdrsMessResult
    bl affichageMess                    @ display message
    add r0,r2,#1
    tst r0,#0b11
    bne 3f
    ldr r0,iAdrszCarriageReturn
    bl affichageMess                    @ display message
3:
    add r2,#1
    cmp r2,#NBBOX - 1
    ble 1b
    ldr r0,iAdrszCarriageReturn
    bl affichageMess                    @ display line return
    ldr r0,iAdriCodeError               @ error detected ?
    ldr r1,[r0]
    cmp r1,#0
    beq 100f
    mov r1,#0                           @ raz error code
    str r1,[r0]
    ldr r0,iAdrszMessMoveError          @ display error message
    bl affichageMess
100:
    pop {r1-r5,lr}                      @ restaur registers 
    bx lr                               @return
iSpaces:                       .int 0x00202020       @ spaces
iAdrszClear:                   .int szClear          
iAdrszMessMoveError:           .int szMessMoveError
/******************************************************************/
/*     display text with size calculation                         */ 
/******************************************************************/
/* r0 contains the address of the message */
affichageMess:
    push {r0,r1,r2,r7,lr}                          @ save  registres
    mov r2,#0                                      @ counter length 
1:                                                 @ loop length calculation 
    ldrb r1,[r0,r2]                                @ read octet start position + index 
    cmp r1,#0                                      @ if 0 its over 
    addne r2,r2,#1                                 @ else add 1 in the length 
    bne 1b                                         @ and loop 
                                                   @ so here r2 contains the length of the message 
    mov r1,r0                                      @ address message in r1 
    mov r0,#STDOUT                                 @ code to write to the standard output Linux 
    mov r7, #WRITE                                 @ code call system "write" 
    svc #0                                         @ call systeme 
    pop {r0,r1,r2,r7,lr}                           @ restaur des  2 registres */ 
    bx lr                                          @ return  
/******************************************************************/
/*     Converting a register to a decimal unsigned                */ 
/******************************************************************/
/* r0 contains value and r1 address area   */
/* r0 return size of result (no zero final in area) */
/* area size => 11 bytes          */
.equ LGZONECAL,   10
conversion10:
    push {r1-r4,lr}                                 @ save registers 
    mov r3,r1
    mov r2,#LGZONECAL
1:                                                  @ start loop
    bl divisionpar10U                               @ unsigned  r0 <- dividende. quotient ->r0 reste -> r1
    add r1,#48                                      @ digit
    strb r1,[r3,r2]                                 @ store digit on area
    cmp r0,#0                                       @ stop if quotient = 0 
    subne r2,#1                                     @ else previous position
    bne 1b                                          @ and loop
                                                    @ and move digit from left of area
    mov r4,#0
2:
    ldrb r1,[r3,r2]
    strb r1,[r3,r4]
    add r2,#1
    add r4,#1
    cmp r2,#LGZONECAL
    ble 2b
                                                      @ and move spaces in end on area
    mov r0,r4                                         @ result length 
    mov r1,#' '                                       @ space
3:
    strb r1,[r3,r4]                                   @ store space in area
    add r4,#1                                         @ next position
    cmp r4,#LGZONECAL
    ble 3b                                            @ loop if r4 <= area size
 
100:
    pop {r1-r4,lr}                                    @ restaur registres 
    bx lr                                             @return
 
/***************************************************/
/*   division par 10   unsigned                    */
/***************************************************/
/* r0 dividende   */
/* r0 quotient    */
/* r1 remainder   */
divisionpar10U:
    push {r2,r3,r4, lr}
    mov r4,r0                                          @ save value
    ldr r3,iMagicNumber                                @ r3 <- magic_number    raspberry 1 2
    umull r1, r2, r3, r0                               @ r1<- Lower32Bits(r1*r0) r2<- Upper32Bits(r1*r0) 
    mov r0, r2, LSR #3                                 @ r2 <- r2 >> shift 3
    add r2,r0,r0, lsl #2                               @ r2 <- r0 * 5 
    sub r1,r4,r2, lsl #1                               @ r1 <- r4 - (r2 * 2)  = r4 - (r0 * 10)
    pop {r2,r3,r4,lr}
    bx lr                                              @ leave function 
iMagicNumber:  	.int 0xCCCCCCCD
/***************************************************/
/*   Generation random number                  */
/***************************************************/
/* r0 contains limit  */
genereraleas:
    push {r1-r4,lr}                                    @ save registers 
    ldr r4,iAdriGraine
    ldr r2,[r4]
    ldr r3,iNbDep1
    mul r2,r3,r2
    ldr r3,iNbDep1
    add r2,r2,r3
    str r2,[r4]                                        @ maj de la graine pour l appel suivant 
    cmp r0,#0
    beq 100f
    mov r1,r0                                          @ divisor
    mov r0,r2                                          @ dividende
    bl division
    mov r0,r3                                          @ résult = remainder
  
100:                                                   @ end function
    pop {r1-r4,lr}                                     @ restaur registers
    bx lr                                              @ return
/*****************************************************/
iAdriGraine: .int iGraine
iNbDep1: .int 0x343FD
iNbDep2: .int 0x269EC3 
/***************************************************/
/* integer division unsigned                       */
/***************************************************/
division:
    /* r0 contains dividend */
    /* r1 contains divisor */
    /* r2 returns quotient */
    /* r3 returns remainder */
    push {r4, lr}
    mov r2, #0                                         @ init quotient
    mov r3, #0                                         @ init remainder
    mov r4, #32                                        @ init counter bits
    b 2f
1:                                                     @ loop 
    movs r0, r0, LSL #1                                @ r0 <- r0 << 1 updating cpsr (sets C if 31st bit of r0 was 1)
    adc r3, r3, r3                                     @ r3 <- r3 + r3 + C. This is equivalent to r3 ? (r3 << 1) + C 
    cmp r3, r1                                         @ compute r3 - r1 and update cpsr 
    subhs r3, r3, r1                                   @ if r3 >= r1 (C=1) then r3 <- r3 - r1 
    adc r2, r2, r2                                     @ r2 <- r2 + r2 + C. This is equivalent to r2 <- (r2 << 1) + C 
2:
    subs r4, r4, #1                                    @ r4 <- r4 - 1 
    bpl 1b                                             @ if r4 >= 0 (N=0) then loop
    pop {r4, lr}
    bx lr
/***************************************************/
/* read touch                                      */
/***************************************************/
readKey:
    push {r1-r7,lr}
    mov r5,#0
    /* read terminal state */
    mov r0,#STDIN                                @ input console
    mov r1,#TCGETS
    ldr r2,iAdrstOldtio
    mov r7, #IOCTL                               @ call system Linux
    svc #0 
    cmp r0,#0                                    @ error ?
    beq 1f
    ldr r1,iAdrszMessErreur                      @ error message
    bl   displayError
    mov r0,#-1
    b 100f
1:
    adr r0,sighandler                            @ adresse routine traitement signal
    ldr r1,iAdrstSigAction                       @ adresse structure sigaction
    str r0,[r1,#sa_handler]                      @ maj handler
    mov r0,#SIGINT                               @ signal type
    ldr r1,iAdrstSigAction
    mov r2,#0                                    @ NULL
    mov r7, #SIGACTION                           @ call system
    svc #0 
    cmp r0,#0                                    @ error ?
    bne 97f
    mov r0,#SIGQUIT
    ldr r1,iAdrstSigAction
    mov r2,#0                                    @ NULL
    mov r7, #SIGACTION                           @ call system 
    svc #0 
    cmp r0,#0                                    @ error ?
    bne 97f
    mov r0,#SIGTERM
    ldr r1,iAdrstSigAction
    mov r2,#0                                    @ NULL
    mov r7, #SIGACTION                           @ appel systeme 
    svc #0 
    cmp r0,#0
    bne 97f
    @
    adr r0,iSIG_IGN                              @ address signal ignore function
    ldr r1,iAdrstSigAction1
    str r0,[r1,#sa_handler]
    mov r0,#SIGTTOU                              @invalidate other process signal
    ldr r1,iAdrstSigAction1
    mov r2,#0                                    @ NULL
    mov r7,#SIGACTION                            @ call system 
    svc #0 
    cmp r0,#0
    bne 97f
    @
    /* read terminal current state  */
    mov r0,#STDIN
    mov r1,#TCGETS
    ldr r2,iAdrstCurtio                          @ address current termio
    mov r7,#IOCTL                                @ call systeme 
    svc #0 
    cmp r0,#0                                    @ error ?
    bne 97f
    mov r2,#ICANON | ECHO                        @ no key pressed echo on display
    mvn r2,r2                                    @ and one key 
    ldr r1,iAdrstCurtio
    ldr r3,[r1,#term_c_lflag]
    and r3,r2                                    @ add flags 
    str r3,[r1,#term_c_lflag]                    @ and store
    mov r0,#STDIN                                @ maj terminal current state 
    mov r1,#TCSETS
    ldr r2,iAdrstCurtio
    mov r7, #IOCTL                               @ call system
    svc #0 
    cmp r0,#0
    bne 97f
    @
2:                                               @ loop waiting key
    ldr r0,iAdriEnd                              @ if signal ctrl-c  -> end
    ldr r0,[r0]
    cmp r0,#0
    movne r5,#-1
    bne 98f
    ldr r0,iAdrstPoll1                            @ address structure poll
    mov r1,#STDIN
    str r1,[r0,#poll_fd]                          @ maj FD
    mov r1,#POLLIN                                @ action code
    str r1,[r0,#poll_events]
    mov r1,#1                                     @ items number structure poll
    mov r2,#0                                     @ timeout = 0 
    mov r7,#SYSPOLL                               @ call system POLL
    svc #0 
    cmp r0,#0                                     @ key pressed ?
    ble 2b                                        @ no key pressed -> loop
                                                  @ read key
    mov r0,#STDIN                                 @ File Descriptor
    ldr r1,iAdriTouche                            @ buffer address
    mov r2,#TAILLEBUFFER                          @ buffer size
    mov r7,#READ                                  @ read key
    svc #0
    cmp r0,#0                                     @ error ?
    bgt 98f

97:                                               @ error detected
    ldr r1,iAdrszMessErreur                       @ error message
    bl   displayError
    mov r5,#-1
98:                                               @ end then restaur begin state terminal
    mov r0,#STDIN
    mov r1,#TCSETS
    ldr r2,iAdrstOldtio
    mov r7,#IOCTL                                 @ call system  
    svc #0
    cmp r0,#0
    beq 99f                                       @ restaur ok
    ldr r1,iAdrszMessErreur                       @ error message
    bl   displayError
    mov r0,#-1
    b 100f
99:
    cmp r5,#0                                     @ error or control-c
    ldreq r2,iAdriTouche                          @ key address
    ldreqb r0,[r2,#2]                             @ return key byte
    movne r0,r5                                   @ or error
100:
    pop {r1-r7, lr}
    bx lr
iSIG_IGN:                 .int 1
iAdriEnd:                 .int iEnd
iAdrstPoll1:              .int stPoll1
iAdriTouche:              .int iTouche
iAdrstOldtio:             .int stOldtio
iAdrstCurtio:             .int stCurtio
iAdrstSigAction:          .int stSigAction
iAdrstSigAction1:         .int stSigAction1
iAdrszMessErreur :        .int szMessErreur 
/******************************************************************/
/*     traitement du signal                                       */ 
/******************************************************************/
sighandler:
    push {r0,r1}
    ldr r0,iAdriEnd
    mov r1,#1                 @ maj zone end
    str r1,[r0]
    pop {r0,r1}
    bx lr
/***************************************************/
/*   display error message                         */
/***************************************************/
/* r0 contains error code  r1 : message address */
displayError:
    push {r0-r2,lr}                         @ save registers
    mov r2,r0                               @ save error code
    mov r0,r1
    bl affichageMess
    mov r0,r2                               @ error code
    ldr r1,iAdrsHexa
    bl conversion16                         @ conversion hexa
    mov r0,r2                               @ error code
    ldr r1,iAdrsDeci                        @ result address
    bl conversion10                         @ conversion decimale
    ldr r0,iAdrszMessErr                    @ display error message
    bl affichageMess
100:
    pop {r0-r2,lr}                          @ restaur registers
    bx lr                                   @ return 
iAdrszMessErr:                 .int szMessErr
iAdrsHexa:                     .int sHexa
iAdrsDeci:                     .int sDeci
/******************************************************************/
/*     Converting a register to hexadecimal                      */ 
/******************************************************************/
/* r0 contains value and r1 address area   */
conversion16:
    push {r1-r4,lr}                                    @ save registers
    mov r2,#28                                         @ start bit position
    mov r4,#0xF0000000                                 @ mask
    mov r3,r0                                          @ save entry value
1:                                                     @ start loop
    and r0,r3,r4                                       @value register and mask
    lsr r0,r2                                          @ move right 
    cmp r0,#10                                         @ compare value
    addlt r0,#48                                       @ <10  ->digit	
    addge r0,#55                                       @ >10  ->letter A-F
    strb r0,[r1],#1                                    @ store digit on area and + 1 in area address
    lsr r4,#4                                          @ shift mask 4 positions
    subs r2,#4                                         @  counter bits - 4 <= zero  ?
    bge 1b                                             @  no -> loop

100:
    pop {r1-r4,lr}                                     @ restaur registers 
    bx lr                                              @return

Arturo

;; ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~
;; ===>> ~~ Game's functions ~~ <<===
;; --->> ~~ Init functions ~~ <<---

;; This is a solved sample that is used to
;; init and finish the game
solvedTable: @[ "  1  " "  2  " "  3  " "  4  "
                "  5  " "  6  " "  7  " "  8  "
                "  9  " "  10 " "  11 " "  12 "
                "  13 " "  14 " "  15 " "     " ]

;; Use this once in :game's init, to get a player position
;; Q: Why use it once?
;; A: This algorithm is slower than just get a stored varible
;; yet this searches for a string for every value from :game
getPlayerPosition: $[table :block][
    return index table "     "
]

;; This is the object that represents the game
;; 'table » The sample table to generate the game
define :game [
    table :block
][

    init: [
        ; checks if 'table has 16 elements
        ensure [16 = size this\table]

        ;; The game's table itself
        this\table: (shuffle this\table) ; creates a random game
        ;; The current movement. When less, better is your punctuation
        this\movements: 0
        ;; The current 'playerPosition in table
        ;; Used to evaluate if certain movement is possible or not
        this\playerPosition: getPlayerPosition this\table
        ;; Defines it the gameLoop still running
        this\running?: true
    ]

    ;; A builtin print function that simplifies the use
    print: [
        render {
            Movements: |this\movements|, Position: |this\playerPosition|
            *-----*-----*-----*-----*
             |this\table\0| |this\table\1| |this\table\2| |this\table\3|
            *-----*-----*-----*-----*
             |this\table\4| |this\table\5| |this\table\6| |this\table\7|
            *-----*-----*-----*-----*
             |this\table\8| |this\table\9| |this\table\10| |this\table\11|
            *-----*-----*-----*-----*
             |this\table\12| |this\table\13| |this\table\14| |this\table\15|
            *-----*-----*-----*-----*
        }
    ]

    ;; Compares the internal's 'table with another :block
    compare: [
        if this\table = that
            -> return true
    ]

]

;; These are the commands used internally on game
;; To avoid ambiguity, User's input'll to be translated to this
gameActions: ['up, 'left, 'down, 'right, 'quit]


;; ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~
;; -->> Print funnctions <<---

;; A template for print instructions
printInstructions: [
    color #cyan "Type (WASD) to move and (Q) to quit."
]

;; A template for print input warning
;; 'input: the wrong input itself that will be printed
printWrongInput: $[inp :string][
    print color #red
    ~"Wrong input: '|inp|'"
]

;; A template for print input warning
;; 'action: could be 'up, 'down, 'left or 'right
printWrongMovement: $[action :literal][
    print color #red
    ~"Wrong movement. Can't go |action|"
]


;; ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~
;; --->> Validators/Checkers functions <<---

;; Checks if a 'input is in 'gameActions
;; Valids for: 'up, 'down, 'left, 'right and 'quit
validInput?: $[inp :any][
    return (in? inp gameActions)
]

;; Checks if the current movement tried is possible
;; 'game » is the current game
;; 'movement » must be in 'gameActions, but can't be 'quit
validMovement?: $[
    game     :game
    movement :literal
][
    pos: game\playerPosition
    case [movement]
        when? [='up]
            -> return (not? in? pos [0..3])
        when? [='down]
            -> return (not? in? pos [12..15])
        when? [='left]
            -> return (not? in? pos [0 4 8 12])
        when? [='right]
            -> return (not? in? pos [3 7 11 15])
    else
        -> return false
]


;; ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~
;; --->> Action functions <<---

;; Gets user input from terminal
;; returning a :literal from 'gameActions
;; Raises: In case of wrong input,
;; will be returned the same input as a :string
parseInput: $[inp :string][
    lowerInp: lower inp
    case [lowerInp]
        when? [="w"] -> return 'up
        when? [="a"] -> return 'left
        when? [="s"] -> return 'down
        when? [="d"] -> return 'right
        when? [="q"] -> return 'quit
    else -> return inp
]

;; Moves the player in Game's Table
;; Note that this's a unsafe function,
;; use 'validMovement? to check a 'movement given a game,
;; and then use this
movePlayer: $[
    game     :game
    movement :literal
][

    position: game\playerPosition

    updateGame: $[
        game             :game
        playerPosition   :integer
        relativePosition :integer
    ][
        try [

            ; 'otherPosition is the real index of the 'relativePosition
            otherPosition: + playerPosition relativePosition

            ; -- Updates the table, swaping the positions
            temp: game\table\[playerPosition]
            game\table\[playerPosition]: game\table\[otherPosition]
            game\table\[otherPosition]: temp

            ; -- Updates player's status
            game\playerPosition: otherPosition
            game\movements: inc game\movements
        ] else -> panic "'movement didn't checked."
    ]

    case [movement]
    when? [='up]
        -> (updateGame game position (neg 4))
    when? [='down]
        -> (updateGame game position (4))
    when? [='left]
        -> (updateGame game position (neg 1))
    when? [='right]
        -> (updateGame game position (1))
    else -> panic "'movement didn't checked."

]

endGame: $[
    message :string
][
    print message
    exit
]


;; ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~
;; --->> Run function <<---

;; Inits ans runs the game
;; 'sampleTable must be already solved
runGame: $[sampleTable :block][
    game: to :game [sampleTable]

    while [game\running?] [
        print game
        print printInstructions
        command: parseInput input ">> "

        if command = 'quit
            -> endGame "Exiting game..."

        validInp: validInput? command
        if? validInp [
            validMov: validMovement? game command
            (validMov)?
                -> movePlayer game command
                -> printWrongMovement command
        ] else
            -> printWrongInput command

        if sampleTable = game
            -> endGame "Congratulations! You won!"
        print ""
    ]
]


runGame solvedTable

Astro

type Puzzle(var items: {}, var position: -1)

fun mainframe(puz):
    let d = puz.items
    print('+-----+-----+-----+-----+')
    print(d[1], d[2], d[3], d[4], first: '|', sep: '|', last: '|')
    print('+-----+-----+-----+-----+')
    print(d[5], d[6], d[7], d[8], first: '|', sep: '|', last: '|')
    print('+-----+-----+-----+-----+')
    print(d[9], d[10], d[11], d[12], first: '|', sep: '|', last: '|')
    print('+-----+-----+-----+-----+')
    print(d[13], d[14], d[15], d[16], first: '|', sep: '|', last: '|')
    print('+-----+-----+-----+-----+')

fun format(puz, ch):
    match ch.trim().length:
        1 => '  $ch  '
        2 => '  $ch '
        0 => '     '

fun change(puz, to):
    let fro = puz.position
    for a, b in puz.items where b == puz.format(str i):
        to = a
        break

    swap(puz.items[fro], :[to])
    puz.position = to;

fun buildboard(puz, difficulty):
    for i in 1..16:
        puz.items[i] = puz.format(str i)

    var tmp = a
    for a, b in puz.items where b == '  16 ':
        puz.items[a] = '     '
            tmp = a
            break

    puz.position = tmp
    let diff = match difficulty:
        0 => 10
        1 => 50
        _ => 100

    for i in 1..diff:
        let lst = puz.validmoves()
        let lst1 = []
        for j in lst:
            lst1.push! j.trim().int()
        puz.change(lst1[random(1, lst1.length - 1)])

fun validmoves(puz):
    match puz.position:
        6 | 7 | 10 | 11 =>
            puz.items[pos - 4], :[pos - 1], :[pos + 1], :[pos + 4]
        5 | 9 =>
            puz.items[pos - 4], :[pos + 4], :[pos + 1]
        8 | 12 =>
            puz.items[pos - 4], :[pos + 4], :[pos - 1]
        2 | 3 =>
            puz.items[pos - 1], :[pos + 1], :[pos + 4]
        14 | 15 =>
            puz.items[pos - 1], :[pos + 1], :[pos - 4]
        1 =>
            puz.items[pos + 1], :[pos + 4]
        4 =>
            puz.items[pos - 1], :[pos + 4]
        13 =>
            puz.items[pos + 1], :[pos - 4]
        16 =>
            puz.items[pos - 1], :[pos - 4]

fun mainframe(puz):
    var flag = false
    for a, b in puz.items:
        if b == '     ':
            pass
        else:
            flag = (a == b.trim().int())
    ..
    return flag

let game = Puzzle()
game.buildboard(
    int(input('Enter the difficulty : 0 1 2\n2 => highest 0=> lowest\n'))
)
game.mainframe()

print 'Enter 0 to exit'

loop:
    print 'Hello user:\nTo change the position just enter the no. near it'

    var lst = game.validmoves()
    var lst1 = []
    for i in lst:
        lst1.push! i.trim().int()
        print(i.strip(), '\t', last: '')

    print()

    let value = int(input())
    if value == 0:
        break
    elif x not in lst1:
        print('Wrong move')
    else:
        game.change(x)

    game.mainframe()
    if g.gameover():
        print 'You WON'
        break

AutoHotkey

Size := 20
Grid := [], Deltas := ["-1,0","1,0","0,-1","0,1"], Width := Size * 2.5
Gui, font, S%Size%
Gui, add, text, y1
loop, 4
{
	Row := A_Index
	loop, 4
	{
		Col := A_Index
		Gui, add, button, % (Col=1 ? "xs y+1" : "x+1 yp") " v" Row "_" Col " w" Width " gButton -TabStop", % Grid[Row,Col] := Col + (Row-1)*4 ; 1-16
	}
}
GuiControl, Hide, % Row "_" Col	; 4_4
Gui, add, Button, % "xs gShuffle w" 4 * Width + 3, Shuffle
Gui, show,, 15 Puzzle
return
;------------------------------
GuiClose:
ExitApp
return
;------------------------------
Shuffle:
Shuffle := true
loop, 1000
{
	Random, Rnd, 1,4
	Move(StrSplit(Deltas[Rnd], ",").1, StrSplit(Deltas[Rnd], ",").2)
}
Shuffle := false
return
;------------------------------
Button:
buttonRow := SubStr(A_GuiControl, 1, 1), ButtonCol := SubStr(A_GuiControl, 3, 1)
if Abs(buttonRow-Row) > 1 || Abs(ButtonCol-Col) > 1 || Abs(buttonRow-Row) = Abs(ButtonCol-Col)
	return
Move(buttonRow-Row, ButtonCol-Col)
return
;------------------------------
#IfWinActive, 15 Puzzle
;------------------------------
Down::
Move(-1, 0)
return
;------------------------------
Up::
Move(1, 0)
return
;------------------------------
Right::
Move(0, -1)
return
;------------------------------
Left::
Move(0, 1)
return
;------------------------------
#IfWinActive
;------------------------------
Move(deltaRow, deltaCol){
	global
	if (Row+deltaRow=0) || (Row+deltaRow=5) || (Col+deltaCol=0) || (Col+deltaCol=5)
		return
	GuiControl, Hide, % Row+deltaRow "_" Col+deltaCol
	GuiControl, Show, % Row "_" Col
	GuiControl,, %Row%_%Col%, % Grid[Row+deltaRow, Col+deltaCol]
	Grid[Row, Col] := Grid[Row+deltaRow, Col+deltaCol]
	Grid[Row+=deltaRow, Col+=deltaCol] := 16
	if Shuffle
		return
	gridCont := ""
	for m, obj in grid
		for n, val in obj
			gridCont .= val ","
	if (Trim(gridCont, ",") = "1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16")
		MsgBox, 262208, 15 Puzzle, You solved 15 Puzzle
}

BASIC

Applesoft BASIC

 100  GOSUB 500INITIALIZE
 110  FOR Q = 1 TO 1
 120      IF I <> X  OR J <> Y THEN GOSUB 200MOVE
 130      ON W GOSUB 330,450
 140      LET I = K(0, K) + X
 150      LET J = K(1, K) + Y
 160      LET Q = K(2, K) OR W = 3
 170  NEXT Q
 180  VTAB T + 3
 190  END

 REM MOVE
 200  IF I < 0 THEN RETURN
 210  IF I > 3 THEN RETURN
 220  IF J < 0 THEN RETURN
 230  IF J > 3 THEN RETURN
 240  LET M = (I + J * 4) * 3
 250  LET N = (X + Y * 4) * 3
 260  IF N > M GOTO 290SWAP
 270      LET N = M
 280      LET M = (X + Y * 4) * 3
 REM SWAP
 290  LET A$ = MID$(A$, 1, M) + MID$(A$, N + 1, 2) + MID$(A$,M + 3, N - M - 2) + MID$(A$, M + 1, 2) + MID$(A$, N + 3)
 300  LET X = I
 310  LET Y = J
 320  ON W GOTO 440,400

 REM RANDOM MOVE
 330  VTAB T + 3
 340  HTAB 2
 350  PRINT MID$(S$, S + 1, 10);
 360  LET S = NOT S
 370  LET K = INT(RND(1) * 4) + 1
 380  IF PEEK(49152) < 128 OR A$ = W$ THEN RETURN
 390  LET K = PEEK(49168) * 0
 REM SHOW
 400  VTAB T
 410  HTAB 1
 420  PRINT A$;
 430  LET W = (A$ = W$) + 2
 REM DON'T SHOW
 440  RETURN

 REM GET KEY
 450  VTAB T + Y
 460  HTAB X * 3 + 2
 470  GET K$
 480  LET K =  ASC (K$)
 490  RETURN

 REM INITIALIZE
 500  PRINT " 15-PUZZLE"

 REM KEYBOARD

 REM ARROW KEYS  TWO HANDED  CLASSIC T  REVERSE T  SEQUENCED
 REM    ^K           A           I          G         ^C
 REM ^H ^J ^U     ,  Z  .     J  K  L    H  T  F   ^B ^D ^A

 REM RIGHT    ,  J      H   ^A
 510  DATA8,44,74,106,72,104,1

 REM LEFT    .  L      F     ^B
 520  DATA21,46,76,108,70,102,2

 REM DOWN    A     I      G     ^C
 530  DATA11,65,97,73,105,71,103,3

 REM UP      Z      K      T     ^D
 540  DATA10,90,122,75,107,84,116,4

 REM QUIT   ^Q ESC
 550  DATA0,17,27,0
 
 560  DIM K(2,127)
 570  FOR V = 0 TO 2
 580      FOR D =  - 1 TO 1 STEP 2
 590          FOR R = 1 TO 1
 600              READ K
 610              LET K(V,K) = D
 620              LET R = K < 5
 630  NEXT R,D,V
 640  LET A$ = " 1  2  3  4"
 650  LET M$ =  CHR$ (13)
 660  LET L$ = " 5  6  7  8"
 670  LET A$ = A$ + M$ + L$
 680  LET L$ = " 9 10 11 12"
 690  LET A$ = A$ + M$ + L$
 700  LET L$ = "13 14 15   "
 710  LET A$ = A$ + M$ + L$
 720  LET W$ = A$
 730  DATA3,3,3,3,1,0
 740  READ X,Y,I,J,W,k(2, 0)
 750  PRINT "PRESS A KEY"
 760  PRINT " TO STOP"
 770  LET S$ = " SHUFFLING "
 780  LET T = PEEK(37) - 2
 790  RETURN

Commodore BASIC

10 REM 15-PUZZLE GAME
20 REM COMMODORE BASIC 2.0
30 REM ********************************
40 GOSUB 400 : REM INTRO AND LEVEL
50 GOSUB 510 : REM SETUP BOARD
60 GOSUB 210 : REM PRINT PUZZLE
70 PRINT "TO MOVE A PIECE, ENTER ITS NUMBER:"
80 INPUT X
90 GOSUB 760 : REM CHECK IF MOVE IS VALID
100 IF MV=0 THEN PRINT "WRONG MOVE" : GOSUB 1130 : GOTO 60
110 D(Z)=X : D(Y)=0
120 GOSUB 210 : REM PRINT PUZZLE
130 GOSUB 1030: REM CHECK IF PUZZLE COMPLETE
140 IF PC THEN 160
150 GOTO 70
160 PRINT"YOU WON!"
170 END
180 REM
190 REM *******************************
200 REM PRINT/DRAW THE PUZZLE
210 FOR P=1 TO 16
220   IF D(P)=0 THEN D$(P)="     " : GOTO 260
230   S$=STR$(D(P))
240   N=LEN(S$)
250   D$(P) = LEFT$("   ",3-N)+S$+"  "
260 NEXT
270 PRINT "+-----+-----+-----+-----+"
280 PRINT "!"D$(1)"!"D$(2)"!"D$(3)"!"D$(4)"!"
290 PRINT "+-----+-----+-----+-----+"
300 PRINT "!"D$(5)"!"D$(6)"!"D$(7)"!"D$(8)"!"
310 PRINT "+-----+-----+-----+-----+"
320 PRINT "!"D$(9)"!"D$(10)"!"D$(11)"!"D$(12)"!"
330 PRINT "+-----+-----+-----+-----+"
340 PRINT "!"D$(13)"!"D$(14)"!"D$(15)"!"D$(16)"!"
350 PRINT "+-----+-----+-----+-----+"
360 RETURN
370 REM
380 REM *******************************
390 REM INTRO AND LEVEL OF DIFFICULTY
400 PRINT CHR$(147)
410 DIM SH(3) : SH(1)=10 : SH(2)=50 : SH(3)=100
420 PRINT "15 PUZZLE GAME FOR COMMODORE BASIC 2.0" : PRINT : PRINT
430 PRINT "PLEASE ENTER LEVEL OF DIFFICULTY,"
440 PRINT "1(EASY), 2(MEDIUM) OR 3(HARD):";
450 INPUT V
460 IF V<1 OR V>3 THEN 440
470 RETURN
480 REM
490 REM *******************************
500 REM BUILD THE BOARD
510 DIM D(16) : DIM D$(16) : REM BOARD PIECES
520 REM SET PIECES IN CORRECT ORDER FIRST
530 FOR P=1 TO 15
540   D(P) = P
550 NEXT
560 D(16) = 0 : REM 0 = EMPTY PIECE/SLOT
570 Z=16      : REM Z = EMPTY POSITION
580 PRINT: PRINT "SHUFFLING PIECES";
590 FOR N=1 TO SH(V)
600   PRINT".";
610   X = INT(RND(0)*4)+1
620   IF X=1 THEN R=Z-4
630   IF X=2 THEN R=Z+4
640   IF (X=3) AND (INT((Z-1)/4)<>(Z-1)/4) THEN R=Z-1
650   IF (X=4) AND (INT(Z/4)<>Z/4) THEN R=Z+1
660   IF R<1 OR R>16 THEN 610
670   D(Z)=D(R)
680   Z=R
690   D(Z)=0
700 NEXT
710 PRINT CHR$(147)
720 RETURN
730 REM
740 REM *******************************
750 REM CHECK IF MOVE IS VALID
760 MV = 0
770 IF X<1 OR X>15 THEN RETURN
780 REM FIND POSITION OF PIECE X AND OF EMPTY PIECE
790 AX=X
800 GOSUB 940 : REM FIND POSITION OF PIECE AX
810 Y=P
820 AX=0
830 GOSUB 940 : REM FIND POSITION OF PIECE AX
840 Z=P
850 REM CHECK IF EMPTY PIECE IS ABOVE, BELOW, LEFT OR RIGHT TO PIECE X
860 IF Y-4=Z THEN MV=1 : RETURN
870 IF Y+4=Z THEN MV=1 : RETURN
880 IF (Y-1=Z) AND (INT(Z/4)<>Z/4) THEN MV=1 : RETURN
890 IF (Y+1=Z) AND (INT(Y/4)<>Y/4) THEN MV=1 : RETURN
900 RETURN
910 REM
920 REM *******************************
930 REM FIND POSITION OF PIECE AX
940 P=1
950 IF D(P)=AX THEN 990
960   P=P+1
970   IF P>16 THEN PRINT "UH OH!" : STOP
980 GOTO 950
990 RETURN
1000 REM
1010 REM *******************************
1020 REM CHECK IF PUZZLE IS COMPLETE / GAME OVER
1030 PC = 0
1040 P=1
1050 IF (P>=16) OR (D(P)<>P) THEN 1080
1060   P=P+1
1070 GOTO 1050
1080 IF P=16 THEN PC=1
1090 RETURN
1100 REM
1110 REM ******************************
1120 REM A SMALL DELAY
1130 FOR T=0 TO 400
1140 NEXT
1150 RETURN

BBC BASIC

Works with: ARM BBC BASIC
Works with: Brandy BASIC version Matrix Brandy
      IF INKEY(-256)=77 OR (INKEY(-256) AND &F0)=&A0 THEN MODE 1: COLOUR 0: COLOUR 143: *FX4,1

      SIZE=4 : DIFFICULTY=3

      MAX=SIZE * SIZE - 1
      DIM Board(MAX)
      FOR I%=1 TO MAX : Board(I% - 1)=I% : NEXT
      Gap=MAX
      WHILE N% < DIFFICULTY ^ 2 PROCSlide(RND(4)) : ENDWHILE : REM Shuffle
      N%=0

      @%=2 + LOG(MAX + 1)
      PROCShowAndTest
      WHILE NOT Solved
        PRINT "Use arrow keys to move the gap around. Moves taken: ";N%
        PROCSlide(GET - 135)
        PROCShowAndTest
      ENDWHILE
      PRINT "Solved after ";N% LEFT$(" moves", 6 + (N% = 1)) "."
      END

      DEF PROCSlide(dir%)
      NewGap=Gap
      CASE dir% OF
        WHEN 1: IF Gap MOD SIZE > 0        NewGap=Gap - 1    : N%+=1 : REM Left
        WHEN 2: IF Gap MOD SIZE < SIZE - 1 NewGap=Gap + 1    : N%+=1 : REM Right
        WHEN 3: IF Gap < MAX - SIZE + 1    NewGap=Gap + SIZE : N%+=1 : REM Down
        WHEN 4: IF Gap > SIZE - 1          NewGap=Gap - SIZE : N%+=1 : REM Up
      ENDCASE
      SWAP Board(Gap), Board(NewGap)
      Gap=NewGap
      ENDPROC

      DEF PROCShowAndTest
      CLS
      Solved=TRUE
      FOR I%=0 TO MAX
        COLOUR 12 : COLOUR 135
        IF I% = Gap COLOUR 1 : COLOUR 129
        IF I% MOD SIZE = SIZE - 1 PRINT Board(I%) ELSE PRINT Board(I%),;
        IF Solved IF I% < MAX - 1 IF Board(I%) > Board(I% + 1) OR I% = Gap Solved=FALSE
      NEXT
      COLOUR 0 : COLOUR 143
      PRINT
      ENDPROC

BQN

Translation of: APL
_while_  {𝔽𝔾𝔽_𝕣_𝔾𝔽𝔾𝕩}
FPG{
  𝕊𝕩: 44𝕊𝕩;
  (´𝕨<0)2≠≠𝕨 ? •Out "Invalid shape: "∾•Fmt 𝕨;
  0≠=𝕩 ? •Out "Invalid shuffle count: "∾•Fmt 𝕩;
  s𝕊𝕩:
  d10¯10010¯1 # Directions
  w𝕨1⌽↕×´𝕨 # Solved grid
  bw        # Board
  z{
    zp𝕩
    p(⊢≡s|)¨/(<z)+d(¬∊/⊣)p # filter out invalid
    n(•rand.Range p)p
    b(zn) # switch places
    -`nz
  }𝕩 𝕨-1,⟨0⟩⟩
  {
    𝕊:
    bw ? •Show b, •Out "You win", 0;
    •Show b
    inp{
      Check 𝕩:
      •Out "Enter move: "
      x•GetLine@
      i"↑↓←→q"x
      {
        i=4 ? i; # quit
        i>4 ? •Out "Invalid direction: "x, Check x;
        (⊢≢s|)z+id ? •Out "Out of bounds: "x, Check x;
        i
      }
    } @
    {
      𝕩=4 ? •Out "Quitting", 0;
      mvz+𝕩d
      b(mvz)
      zmv
      1
    } inp
  } _while_  1
  @
}
   )ex 15_puzzle.bqn
   FPG 10
┌─             
  1  2  0  3  
   5  6  7  4  
   9 10 11  8  
  13 14 15 12  
              
Enter move: 
a
Invalid direction: a
Enter move: 

┌─             
  1  2  7  3  
   5  6  0  4  
   9 10 11  8  
  13 14 15 12  
              
Enter move: 

┌─             
  1  2  0  3  
   5  6  7  4  
   9 10 11  8  
  13 14 15 12  
              
Enter move: 

Out of bounds: 
...

C

C89, 22 lines version

The task, as you can see, can be resolved in 22 lines of no more than 80 characters. Of course, the source code in C is not very readable. The second example works exactly the same way, but it was written in much more human readable way. The program also works correctly for non-standard number of rows and/or columns.

/* RosettaCode: Fifteen puzle game, C89, plain vanillia TTY, MVC, § 22 */
#define _CRT_SECURE_NO_WARNINGS
#include <stdio.h>
#include <stdlib.h>
#include <time.h>
#define N 4
#define M 4
enum Move{UP,DOWN,LEFT,RIGHT};int hR;int hC;int cc[N][M];const int nS=100;int
update(enum Move m){const int dx[]={0,0,-1,1};const int dy[]={-1,1,0,0};int i=hR
+dy[m];int j=hC+dx[m];if(i>= 0&&i<N&&j>=0&&j<M){cc[hR][hC]=cc[i][j];cc[i][j]=0;
hR=i;hC=j;return 1;}return 0;}void setup(void){int i,j,k;for(i=0;i<N;i++)for(j=0
;j<M;j++)cc[i][j]=i*M+j+1;cc[N-1][M-1]=0;hR=N-1;hC=M-1;k=0;while(k<nS)k+=update(
(enum Move)(rand()%4));}int isEnd(void){int i,j; int k=1;for(i=0;i<N;i++)for(j=0
;j<M;j++)if((k<N*M)&&(cc[i][j]!=k++))return 0;return 1;}void show(){int i,j;
putchar('\n');for(i=0;i<N;i++)for(j=0;j<M;j++){if(cc[i][j])printf(j!=M-1?" %2d "
:" %2d \n",cc[i][j]);else printf(j!=M-1?" %2s ":" %2s \n", "");}putchar('\n');}
void disp(char* s){printf("\n%s\n", s);}enum Move get(void){int c;for(;;){printf
("%s","enter u/d/l/r : ");c=getchar();while(getchar()!='\n');switch(c){case 27:
exit(0);case'd':return UP;case'u':return DOWN;case'r':return LEFT;case'l':return
RIGHT;}}}void pause(void){getchar();}int main(void){srand((unsigned)time(NULL));
do setup();while(isEnd());show();while(!isEnd()){update(get());show();}disp(
"You win"); pause();return 0;}

C89, short version, TTY mode

/*
 * RosettaCode: Fifteen puzle game, C89, plain vanillia TTY, MVC
 */

#define _CRT_SECURE_NO_WARNINGS /* unlocks printf etc. in MSVC */
#include <stdio.h>
#include <stdlib.h>
#include <time.h>

enum Move { MOVE_UP = 0, MOVE_DOWN = 1, MOVE_LEFT = 2, MOVE_RIGHT = 3 };

/* *****************************************************************************
 * Model
 */

#define NROWS     4
#define NCOLLUMNS 4
int holeRow;       
int holeCollumn;   
int cells[NROWS][NCOLLUMNS];
const int nShuffles = 100;

int Game_update(enum Move move){
    const int dx[] = {  0,  0, -1, +1 };
    const int dy[] = { -1, +1,  0,  0 };
    int i = holeRow     + dy[move];
    int j = holeCollumn + dx[move];    
    if ( i >= 0 && i < NROWS && j >= 0 && j < NCOLLUMNS ){
        cells[holeRow][holeCollumn] = cells[i][j];
        cells[i][j] = 0; holeRow = i; holeCollumn = j;
        return 1;
    }
    return 0;
}

void Game_setup(void){
    int i,j,k;
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ )
            cells[i][j] = i * NCOLLUMNS + j + 1;
    cells[NROWS-1][NCOLLUMNS-1] = 0;
    holeRow = NROWS - 1;
    holeCollumn = NCOLLUMNS - 1;
    k = 0;
    while ( k < nShuffles )
        k += Game_update((enum Move)(rand() % 4));
}

int Game_isFinished(void){
    int i,j; int k = 1;
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ ) 
            if ( (k < NROWS*NCOLLUMNS) && (cells[i][j] != k++ ) )
                return 0;
    return 1;        
}


/* *****************************************************************************
 * View 
 */

void View_showBoard(){
    int i,j;
    putchar('\n');
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ ){
            if ( cells[i][j] )
                printf(j != NCOLLUMNS-1 ? " %2d " : " %2d \n", cells[i][j]);
            else
                printf(j != NCOLLUMNS-1 ? " %2s " : " %2s \n", "");
        }
    putchar('\n');
}

void View_displayMessage(char* text){
    printf("\n%s\n", text);
}


/* *****************************************************************************
 * Controller
 */

enum Move Controller_getMove(void){
    int c;
    for(;;){
        printf("%s", "enter u/d/l/r : ");
        c = getchar();
        while( getchar() != '\n' )
            ;
        switch ( c ){
            case 27: exit(EXIT_SUCCESS);
            case 'd' : return MOVE_UP;   
            case 'u' : return MOVE_DOWN;
            case 'r' : return MOVE_LEFT;
            case 'l' : return MOVE_RIGHT;
        }
    }
}

void Controller_pause(void){
    getchar();
}

int main(void){

    srand((unsigned)time(NULL));

    do Game_setup(); while ( Game_isFinished() );

    View_showBoard();
    while( !Game_isFinished() ){ 
        Game_update( Controller_getMove() ); 
        View_showBoard(); 
    }

    View_displayMessage("You win");
    Controller_pause();

    return EXIT_SUCCESS;
}
Output:
  9   1   4   7
  6   5   3   2
 13  10       8
 14  15  11  12

enter u/d/l/r : u

  9   1   4   7
  6   5   3   2
 13  10  11   8
 14  15      12

enter u/d/l/r : l

  9   1   4   7
  6   5   3   2
 13  10  11   8
 14  15  12

enter u/d/l/r : d

  9   1   4   7
  6   5   3   2
 13  10  11
 14  15  12   8

enter u/d/l/r :

C89, long version, TTY/Winapi/ncurses modes

/**
 * RosettaCode: Fifteen puzle game, C89, MS Windows Console API, MVC
 *
 * @version 0.2 (added TTY and ncurses modes)
 */

#define UNDEFINED_WIN32API_CONSOLE
#define UNDEFINED_NCURSES_CONSOLE
#if !defined (TTY_CONSOLE) && !defined(WIN32API_CONSOLE) && !defined(NCURSES_CONSOLE)
#define TTY_CONSOLE
#endif

#define _CRT_SECURE_NO_WARNINGS    /* enable printf etc. */
#define _CRT_NONSTDC_NO_DEPRECATE  /* POSIX functions enabled */

#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <time.h>
#if defined(NCURSES_CONSOLE)
#include "curses.h"  /* see http://pdcurses.sourceforge.net/ */
#elif defined(WIN32API_CONSOLE)
#define NOGDI                   /* we don't need GDI */
#define WIN32_LEAN_AND_MEAN     /* we don't need OLE etc. */
#include <windows.h>            /* MS Windows stuff */
#include <conio.h>              /* kbhit() and getch() */
#endif

enum Move { MOVE_UP = 0, MOVE_DOWN = 1, MOVE_LEFT = 2, MOVE_RIGHT = 3 };

/* *****************************************************************************
 * Model
 */

#define NROWS     4
#define NCOLLUMNS 4
int holeRow;       
int holeCollumn;   
int cells[NROWS][NCOLLUMNS];
const int nShuffles = 100;

int Game_update(enum Move move){
    const int dx[] = {  0,  0, -1, +1 };
    const int dy[] = { -1, +1,  0,  0 };
    int i = holeRow     + dy[move];
    int j = holeCollumn + dx[move];    
    if ( i >= 0 && i < NROWS && j >= 0 && j < NCOLLUMNS ){
        cells[holeRow][holeCollumn] = cells[i][j];
        cells[i][j] = 0; holeRow = i; holeCollumn = j;
        return 1;
    }
    return 0;
}

void Game_setup(void){
    int i,j,k;
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ )
            cells[i][j] = i * NCOLLUMNS + j + 1;
    cells[NROWS-1][NCOLLUMNS-1] = 0;
    holeRow = NROWS - 1;
    holeCollumn = NCOLLUMNS - 1;
    k = 0;
    while ( k < nShuffles )
        k += Game_update((enum Move)(rand() % 4));
}

int Game_isFinished(void){
    int i,j; int k = 1;
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ ) 
            if ( (k < NROWS*NCOLLUMNS) && (cells[i][j] != k++ ) )
                return 0;
    return 1;        
}


/* *****************************************************************************
 * View 
 */

int fieldWidth;
#ifdef WIN32API_CONSOLE
HANDLE hConsole;
CONSOLE_SCREEN_BUFFER_INFO csbi; 
#endif

void View_setup_base(void)
{
    int i;
    fieldWidth = 0;
    for ( i = NROWS * NCOLLUMNS - 1; i > 0; i /= 10 )
        fieldWidth++;
}

#if defined(TTY_CONSOLE)

void View_setup(void) {
    View_setup_base();
}

void View_showBoard()
{
    int i,j;
    putchar('\n');
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ ){
            if ( cells[i][j] )
                printf(j != NCOLLUMNS-1 ? " %*d " : " %*d \n", fieldWidth, cells[i][j]);
            else
                printf(j != NCOLLUMNS-1 ? " %*s " : " %*s \n", fieldWidth, "");
        }
    putchar('\n');
}

void View_displayMessage(char* text)
{
    printf("\n%s\n", text);
}

#elif defined(NCURSES_CONSOLE)

void View_setup(void) {
    View_setup_base();
    initscr();        
    clear();
}

void View_showBoard()
{
    int i,j;
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ ){
            int x = (fieldWidth+1)*j;
            int y = 2*i;
            if ( cells[i][j] ){
                attron(A_REVERSE);
                mvprintw(y,x,"%*d", fieldWidth, cells[i][j]);
            }else{
                attroff(A_REVERSE);
                mvprintw(y,x,"%*s", fieldWidth, " ");
            }
        }
    attrset(A_NORMAL);
}

void View_displayMessage(char* text)
{
    mvprintw(2*NROWS,0, "%s", text);
}

#elif defined(WIN32API_CONSOLE)

void View_setup(void) {
    const COORD coordHome = { 0, 0 }; 
    CONSOLE_CURSOR_INFO cci;
    DWORD size, nWritten;
    View_setup_base();
    hConsole = GetStdHandle(STD_OUTPUT_HANDLE);
    cci.bVisible = FALSE; 
    cci.dwSize = 1;
    SetConsoleCursorInfo(hConsole,&cci);    
    GetConsoleScreenBufferInfo(hConsole,&(csbi));
    size = csbi.dwSize.X*csbi.dwSize.Y;
    FillConsoleOutputCharacter(hConsole,' ',size,coordHome,&nWritten);
    FillConsoleOutputAttribute(hConsole,csbi.wAttributes,size,coordHome,&nWritten);

}

void View_showBoard()
{
    int i,j;
    char labelString[32];
    WORD attributes;
    DWORD nWritten;
    for ( i = 0; i < NROWS; i++ )
        for ( j = 0; j < NCOLLUMNS; j++ ){
            COORD coord = { ((SHORT)fieldWidth+1)*j, coord.Y = 2*i };
            if ( cells[i][j] ){
                sprintf(labelString,"%*d", fieldWidth, cells[i][j]);                
                attributes = BACKGROUND_BLUE | BACKGROUND_GREEN | BACKGROUND_RED;
            }else{
                sprintf(labelString,"%*s", fieldWidth, " ");
                attributes = csbi.wAttributes;
            }
            WriteConsoleOutputCharacter(hConsole,labelString,fieldWidth,coord,&nWritten);
            FillConsoleOutputAttribute (hConsole,attributes,fieldWidth,coord,&nWritten);
        }
}

void View_displayMessage(char* text)
{
    DWORD nWritten;
    COORD coord = { 0, 2 * NROWS };
    WriteConsoleOutputCharacter(hConsole,text,strlen(text),coord,&nWritten);
}

#endif


/* *****************************************************************************
 * Controller
 */

#if defined(TTY_CONSOLE)

void Controller_setup(void){
}

enum Move Controller_getMove(void){
    int c;
    for(;;){
        printf("%s", "enter u/d/l/r : ");
        c = getchar();
        while( getchar() != '\n' )
            ;
        switch ( c ){
            case 27: exit(EXIT_SUCCESS);
            case 'd' : return MOVE_UP;   
            case 'u' : return MOVE_DOWN;
            case 'r' : return MOVE_LEFT;
            case 'l' : return MOVE_RIGHT;
        }
    }
}

void Controller_pause(void)
{
    getchar();
}

#elif defined(NCURSES_CONSOLE)

void Controller_setup(void){
    noecho();
    cbreak();
    curs_set(0);
    keypad(stdscr,TRUE);
}

enum Move Controller_getMove(void){
    for(;;){
        switch ( wgetch(stdscr) ){
            case  27: exit(EXIT_SUCCESS);
            case KEY_DOWN  : return MOVE_UP;   
            case KEY_UP    : return MOVE_DOWN;
            case KEY_RIGHT : return MOVE_LEFT;
            case KEY_LEFT  : return MOVE_RIGHT;
            case ERR: /* NOP */;
        }
    }
}

void Controller_pause(void){
    while ( wgetch(stdscr) == ERR )
        ;
}


#elif defined(WIN32API_CONSOLE)

void Controller_setup(void){
}

enum Move Controller_getMove(void){
    for(;;){
        switch ( getch() ){
            case  27: exit(EXIT_SUCCESS);
            case   0:
            case 224: switch ( getch() ){
                case 80 : return MOVE_UP;   
                case 72 : return MOVE_DOWN;
                case 77 : return MOVE_LEFT;
                case 75 : return MOVE_RIGHT;
            }
        }
    }
}

void Controller_pause(void){
    while(  kbhit() ) getch();
    while( !kbhit() )   ;
    while(  kbhit() ) getch();
}

#endif


/* *****************************************************************************
 * Main function: create model, view and controller. Run main loop.
 */
int main(void) {

    srand((unsigned)time(NULL));

    do Game_setup(); while ( Game_isFinished() );
    View_setup(); 
    Controller_setup();

    View_showBoard();
    while( !Game_isFinished() ){ 
        Game_update( Controller_getMove() ); 
        View_showBoard(); 
    }

    View_displayMessage("You win");
    Controller_pause();

    return EXIT_SUCCESS;
}

C#

Works with: C sharp version 3+
using System;
using System.Collections.Generic;
using System.Drawing;
using System.Windows.Forms;

public class FifteenPuzzle
{
    const int GridSize = 4; //Standard 15 puzzle is 4x4
    const int BlockCount = 16;

    static readonly Random R = new Random();

    private List<Button> Puzzles = new List<Button>();
    private int Moves = 0;
    private DateTime Start;

    public class Puzzle
    {
        private int mOrderedNumer;

        public int CurrentNumber;

        public int X;
        public int Y;

        public int InvX
        {
            get { return (GridSize - 1) - X; }
        }
        public int InvY
        {
            get { return (GridSize - 1) - Y; }
        }

        public Puzzle(int OrderedNumer)
        {
            mOrderedNumer = OrderedNumer;

            CurrentNumber = OrderedNumer;

            X = OrderedNumer % GridSize;
            Y = OrderedNumer / GridSize;
        }
        public Puzzle(int OrderedNumer, int CurrentNumber)
            : this(OrderedNumer)
        {
            this.CurrentNumber = CurrentNumber;
        }

        public bool IsEmptyPuzzle
        {
            get { return CurrentNumber >= (BlockCount - 1); }
        }
        public bool IsTruePlace
        {
            get { return (CurrentNumber == mOrderedNumer); }
        }
        public bool NearestWith(Puzzle OtherPz)
        {
            int dx = (X - OtherPz.X);
            int dy = (Y - OtherPz.Y);

            if ((dx == 0) && (dy <= 1) && (dy >= -1)) return true;
            if ((dy == 0) && (dx <= 1) && (dx >= -1)) return true;

            return false;
        }

        public override string ToString()
        {
            return (CurrentNumber + 1).ToString();
        }
    }

    public static void Main(string[] args)
    {
        FifteenPuzzle Game = new FifteenPuzzle();
        Application.Run(Game.CreateForm());
    }

    private Form CreateForm()
    {
        int ButtonSize = 50;
        int ButtonMargin = 3;
        int FormEdge = 9;

        Font ButtonFont = new Font("Arial", 15.75F, FontStyle.Regular);

        Button StartButton = new Button();
        StartButton.Location = new Point(FormEdge, (GridSize * (ButtonMargin + ButtonSize)) + FormEdge);
        StartButton.Size = new Size(86, 23);
        StartButton.Font = new Font("Arial", 9.75F, FontStyle.Regular);
        StartButton.Text = "New Game";
        StartButton.UseVisualStyleBackColor = true;
        StartButton.TabStop = false;

        StartButton.Click += new EventHandler(NewGame);

        int FormWidth = (GridSize * ButtonSize) + ((GridSize - 1) * ButtonMargin) + (FormEdge * 2);
        int FormHeigth = FormWidth + StartButton.Height;

        Form Form = new Form();
        Form.Text = "Fifteen";
        Form.ClientSize = new Size(FormWidth, FormHeigth);
        Form.FormBorderStyle = FormBorderStyle.FixedSingle;
        Form.MaximizeBox = false;
        Form.SuspendLayout();

        for (int i = 0; i < BlockCount; i++)
        {
            Button Bt = new Button();
            Puzzle Pz = new Puzzle(i);

            int PosX = FormEdge + (Pz.X) * (ButtonSize + ButtonMargin);
            int PosY = FormEdge + (Pz.Y) * (ButtonSize + ButtonMargin);
            Bt.Location = new Point(PosX, PosY);

            Bt.Size = new Size(ButtonSize, ButtonSize);
            Bt.Font = ButtonFont;

            Bt.Text = Pz.ToString();
            Bt.Tag = Pz;
            Bt.UseVisualStyleBackColor = true;
            Bt.TabStop = false;

            Bt.Enabled = false;
            if (Pz.IsEmptyPuzzle) Bt.Visible = false;

            Bt.Click += new EventHandler(MovePuzzle);

            Puzzles.Add(Bt);
            Form.Controls.Add(Bt);
        }

        Form.Controls.Add(StartButton);
        Form.ResumeLayout();

        return Form;
    }

    private void NewGame(object Sender, EventArgs E)
    {
        do
        {
            for (int i = 0; i < Puzzles.Count; i++)
            {
                Button Bt1 = Puzzles[R.Next(i, Puzzles.Count)];
                Button Bt2 = Puzzles[i];
                Swap(Bt1, Bt2);
            }
        }
        while (!IsSolvable());

        for (int i = 0; i < Puzzles.Count; i++)
        {
            Puzzles[i].Enabled = true;
        }

        Moves = 0;
        Start = DateTime.Now;
    }

    private void MovePuzzle(object Sender, EventArgs E)
    {
        Button Bt1 = (Button)Sender;
        Puzzle Pz1 = (Puzzle)Bt1.Tag;

        Button Bt2 = Puzzles.Find(Bt => ((Puzzle)Bt.Tag).IsEmptyPuzzle);
        Puzzle Pz2 = (Puzzle)Bt2.Tag;

        if (Pz1.NearestWith(Pz2))
        {
            Swap(Bt1, Bt2);
            Moves++;
        }

        CheckWin();
    }

    private void CheckWin()
    {
        Button WrongPuzzle = Puzzles.Find(Bt => !((Puzzle)Bt.Tag).IsTruePlace);
        bool UWin = (WrongPuzzle == null);

        if (UWin)
        {
            for (int i = 0; i < Puzzles.Count; i++)
            {
                Puzzles[i].Enabled = false;
            }

            TimeSpan Elapsed = DateTime.Now - Start;
            Elapsed = TimeSpan.FromSeconds(Math.Round(Elapsed.TotalSeconds, 0));
            MessageBox.Show(String.Format("Solved in {0} moves. Time: {1}", Moves, Elapsed));
        }
    }

    private void Swap(Button Bt1, Button Bt2)
    {
        if (Bt1 == Bt2) return;

        Puzzle Pz1 = (Puzzle)Bt1.Tag;
        Puzzle Pz2 = (Puzzle)Bt2.Tag;

        int g = Pz1.CurrentNumber;
        Pz1.CurrentNumber = Pz2.CurrentNumber;
        Pz2.CurrentNumber = g;

        Bt1.Visible = true;
        Bt1.Text = Pz1.ToString();
        if (Pz1.IsEmptyPuzzle) Bt1.Visible = false;

        Bt2.Visible = true;
        Bt2.Text = Pz2.ToString();
        if (Pz2.IsEmptyPuzzle) Bt2.Visible = false;
    }

    private bool IsSolvable()
    {
        // WARNING: size of puzzle board MUST be even(like 4)!
        // For explain see: https://www.geeksforgeeks.org/check-instance-15-puzzle-solvable/

        int InvCount = 0;
        for (int i = 0; i < Puzzles.Count - 1; i++)
        {
            for (int j = i + 1; j < Puzzles.Count; j++)
            {
                Puzzle Pz1 = (Puzzle)Puzzles[i].Tag;
                if (Pz1.IsEmptyPuzzle) continue;

                Puzzle Pz2 = (Puzzle)Puzzles[j].Tag;
                if (Pz2.IsEmptyPuzzle) continue;

                if (Pz1.CurrentNumber > Pz2.CurrentNumber) InvCount++;
            }
        }

        Button EmptyBt = Puzzles.Find(Bt => ((Puzzle)Bt.Tag).IsEmptyPuzzle);
        Puzzle EmptyPz = (Puzzle)EmptyBt.Tag;

        bool Result = false;
        if ((EmptyPz.InvY + 1) % 2 == 0) // is even
        {
            // is odd
            if (InvCount % 2 != 0) Result = true;
        }
        else // is odd
        {
            // is even
            if (InvCount % 2 == 0) Result = true;
        }
        return Result;
    }
}

C++

#include <time.h>
#include <stdlib.h>
#include <vector>
#include <string>
#include <iostream>
class p15 {
public :
    void play() {
        bool p = true;
        std::string a;
        while( p ) {
            createBrd();
            while( !isDone() ) { drawBrd();getMove(); }
            drawBrd();
            std::cout << "\n\nCongratulations!\nPlay again (Y/N)?";
            std::cin >> a; if( a != "Y" && a != "y" ) break;
        }
    }
private:
    void createBrd() {
        int i = 1; std::vector<int> v;
        for( ; i < 16; i++ ) { brd[i - 1] = i; }
        brd[15] = 0; x = y = 3;
        for( i = 0; i < 1000; i++ ) {
            getCandidates( v );
            move( v[rand() % v.size()] );
            v.clear();
        }
    }
    void move( int d ) {
        int t = x + y * 4;
        switch( d ) {
            case 1: y--; break;
            case 2: x++; break;
            case 4: y++; break;
            case 8: x--;
        }
        brd[t] = brd[x + y * 4];
        brd[x + y * 4] = 0;
    }
    void getCandidates( std::vector<int>& v ) {
        if( x < 3 ) v.push_back( 2 ); if( x > 0 ) v.push_back( 8 );
        if( y < 3 ) v.push_back( 4 ); if( y > 0 ) v.push_back( 1 );
    }
    void drawBrd() {
        int r; std::cout << "\n\n";
        for( int y = 0; y < 4; y++ ) {
            std::cout << "+----+----+----+----+\n";
            for( int x = 0; x < 4; x++ ) {
                r = brd[x + y * 4];
                std::cout << "| ";
                if( r < 10 ) std::cout << " ";
                if( !r ) std::cout << "  ";
                else std::cout << r << " ";
            }
            std::cout << "|\n";
        }
        std::cout << "+----+----+----+----+\n";
    }
    void getMove() {
        std::vector<int> v; getCandidates( v );
        std::vector<int> p; getTiles( p, v ); unsigned int i;
        while( true ) {
            std::cout << "\nPossible moves: ";
            for( i = 0; i < p.size(); i++ ) std::cout << p[i] << " ";
            int z; std::cin >> z;
            for( i = 0; i < p.size(); i++ )
                if( z == p[i] ) { move( v[i] ); return; }
        }
    }
    void getTiles( std::vector<int>& p, std::vector<int>& v ) {
        for( unsigned int t = 0; t < v.size(); t++ ) {
            int xx = x, yy = y;
            switch( v[t] ) {
                case 1: yy--; break;
                case 2: xx++; break;
                case 4: yy++; break;
                case 8: xx--;
            }
            p.push_back( brd[xx + yy * 4] );
        }
    }
    bool isDone() {
        for( int i = 0; i < 15; i++ ) {
            if( brd[i] != i + 1 ) return false;
        }
        return true;
    }
    int brd[16], x, y;
};
int main( int argc, char* argv[] ) {
    srand( ( unsigned )time( 0 ) );
    p15 p; p.play(); return 0;
}
+----+----+----+----+
| 11 |  5 | 12 |  3 |
+----+----+----+----+
| 10 |  7 |  6 |  4 |
+----+----+----+----+
| 13 |    |  2 |  1 |
+----+----+----+----+
| 15 | 14 |  8 |  9 |
+----+----+----+----+

Possible moves: 2 13 14 7

COBOL

Tested with GnuCOBOL

         >>SOURCE FORMAT FREE
*> This code is dedicated to the public domain
*> This is GNUCOBOL 2.0
identification division.
program-id. fifteen.
environment division.
configuration section.
repository. function all intrinsic.
data division.
working-storage section.

01  r pic 9.
01  r-empty pic 9.
01  r-to pic 9.
01  r-from pic 9.

01  c pic 9.
01  c-empty pic 9.
01  c-to pic 9.
01  c-from pic 9.

01  display-table.
    03  display-row occurs 4.
        05  display-cell occurs 4 pic 99.

01  tile-number pic 99.
01  tile-flags pic x(16).

01  display-move value spaces.
    03  tile-id pic 99.

01  row-separator pic x(21) value all '.'.
01  column-separator pic x(3) value ' . '.

01  inversions pic 99.
01  current-tile pic 99.

01  winning-display pic x(32) value
        '01020304'
    &   '05060708'
    &   '09101112'
    &   '13141500'.

procedure division.
start-fifteen.
    display 'start fifteen puzzle'
    display '    enter a two-digit tile number and press <enter> to move'
    display '    press <enter> only to exit'

    *> tables with an odd number of inversions are not solvable
    perform initialize-table with test after until inversions = 0
    perform show-table
    accept display-move
    perform until display-move = spaces
        perform move-tile
        perform show-table
        move spaces to display-move
        accept display-move
    end-perform
    stop run
    .
initialize-table.
    compute tile-number = random(seconds-past-midnight) *> seed only
    move spaces to tile-flags
    move 0 to current-tile inversions
    perform varying r from 1 by 1 until r > 4
    after c from 1 by 1 until c > 4
        perform with test after
        until tile-flags(tile-number + 1:1) = space
            compute tile-number = random() * 100
            compute tile-number = mod(tile-number, 16)
        end-perform
        move 'x' to tile-flags(tile-number + 1:1)
        if tile-number > 0 and < current-tile
            add 1 to inversions
        end-if
        move tile-number to display-cell(r,c) current-tile
    end-perform
    compute inversions = mod(inversions,2)
    .
show-table.
    if display-table = winning-display
        display 'winning'
    end-if
    display space row-separator
    perform varying r from 1 by 1 until r > 4
        perform varying c from 1 by 1 until c > 4
            display column-separator with no advancing
            if display-cell(r,c) = 00
                display '  ' with no advancing
                move r to r-empty
                move c to c-empty
            else
                display display-cell(r,c) with no advancing
            end-if
        end-perform
        display column-separator
    end-perform
    display space row-separator
    .
move-tile.
    if not (tile-id numeric and tile-id >= 01 and <= 15)
        display 'invalid tile number'
        exit paragraph
    end-if

    *> find the entered tile-id row and column (r,c)
    perform varying r from 1 by 1 until r > 4
    after c from 1 by 1 until c > 4
        if display-cell(r,c) = tile-id
            exit perform
        end-if
    end-perform

    *> show-table filled (r-empty,c-empty)
    evaluate true
    when r = r-empty
        if c-empty < c
            *> shift left
            perform varying c-to from c-empty by 1 until c-to > c
                compute c-from = c-to + 1
                move display-cell(r-empty,c-from) to display-cell(r-empty,c-to)
            end-perform
        else
           *> shift right
           perform varying c-to from c-empty by -1 until c-to < c
               compute c-from = c-to - 1
               move display-cell(r-empty,c-from) to display-cell(r-empty,c-to)
           end-perform
       end-if
       move 00 to display-cell(r,c)
    when c = c-empty
        if r-empty < r
            *>shift up
            perform varying r-to from r-empty by 1 until r-to > r
                compute r-from = r-to + 1
                move display-cell(r-from,c-empty) to display-cell(r-to,c-empty)
            end-perform
        else
            *> shift down
            perform varying r-to from r-empty by -1 until r-to < r
                compute r-from = r-to - 1
                move display-cell(r-from,c-empty) to display-cell(r-to,c-empty)
            end-perform
        end-if
        move 00 to display-cell(r,c)
    when other
         display 'invalid move'
    end-evaluate
    .
end program fifteen.
Output:
prompt$ cobc -xj fifteen.cbl
start fifteen puzzle
    enter a two-digit tile number and press <enter> to move
    press <enter> only to exit
 .....................
 . 05 . 14 . 08 . 12 .
 . 01 . 10 . 03 . 09 .
 . 02 . 15 . 13 . 11 .
 . 06 .    . 07 . 04 .
 .....................

Common Lisp

Credit to this post for help with the inversions-counting function: [1]

Run it (after loading the file) with

|15|::main

.

(defpackage :15
  (:use :common-lisp))
(in-package :15)

(defvar +side+ 4)
(defvar +max+ (1- (* +side+ +side+))) ; 15

(defun make-board ()
  (make-array (list +side+ +side+)
              :initial-contents
              (loop :for i :below +side+ :collecting
                 (loop :for j :below +side+ :collecting
                    (mod (1+ (+ j (* i +side+))) (1+ +max+))))))
(defvar *board* (make-board))

(defun shuffle-board (board)
  (loop for i from (array-total-size board) downto 2
     do (rotatef (row-major-aref board (random i))
                 (row-major-aref board (1- i))))
  board)

(defun pb (stream object &rest args)
  (declare (ignorable args))
  (loop for i below (car (array-dimensions object)) do
       (loop for j below (cadr (array-dimensions object)) do
            (let ((cell (aref object i j)))
              (format stream "(~[  ~:;~:*~2d~])" cell)))
       (format stream "~%")))

(defun sortedp (board)
  (declare (ignorable board))
  (loop for i upto +max+
     when (eq (row-major-aref board i) (mod (1+ i) 16)) do
       (return-from sortedp nil))
  t)

(defun inversions (lst)
  (if (or (null lst) (null (cdr lst)))
      0
      (let* ((half (ceiling (/ (length lst) 2)))
             (left-list (subseq lst 0 half))
             (right-list (subseq lst half)))
        (+ (loop for a in left-list
              summing (loop for b in right-list
                         counting (not (< a b))))
           (inversions left-list)
           (inversions right-list)))))

(defun solvablep (board)
  (let ((inv (inversions (loop for i upto +max+ collecting
                              (row-major-aref board i))))
        (row (- +side+ (first (board-position board 0)))))
    (or (and (oddp +side+)
             (evenp inv))
        (and (evenp +side+)
             (evenp row)
             (oddp inv))
        (and (evenp +side+)
             (oddp row)
             (evenp inv)))))

(defun board-position (board dig)
  (loop for i below (car (array-dimensions board)) do
       (loop for j below (cadr (array-dimensions board))
          when (eq dig (aref board i j)) do
          (return-from board-position (list i j)))))

(defun in-bounds (y x)
  (and (< -1 y +side+)
       (< -1 x +side+)))

(defun get-adjacents (board pos)
  (let ((adjacents ()) (y (first pos)) (x (second pos)))
    (if (in-bounds y (1+ x))
        (push (aref board y (1+ x)) adjacents))
    (if (in-bounds (1+ y) x)
        (push (aref board (1+ y) x) adjacents))
    (if (in-bounds y (1- x))
        (push (aref board y (1- x)) adjacents))
    (if (in-bounds (1- y) x)
        (push (aref board (1- y) x) adjacents))
    adjacents))

(defun main (&rest argv)
  (declare (ignorable argv))
  (setf *random-state* (make-random-state t))
  (loop until (solvablep *board*) do
       (shuffle-board *board*))
  (loop until (sortedp *board*) do
       (format t "~/15:pb/~%" *board*)
       (format t "Which number do you want to swap the blank with?~%> ")
       (let* ((in (read))
              (zpos (board-position *board* 0))
              (pos (board-position *board* in))
              (adj (get-adjacents *board* zpos)))
         (if (find in adj)
             (rotatef (aref *board* (first pos) (second pos))
                      (aref *board* (first zpos) (second zpos))))))
  (format t "You win!~%"))

Craft Basic

rem 15 Puzzle example game
rem written in Craft Basic
rem by Gemino Smothers 2023
rem www.lucidapogee.com

define size = 16, correct = 0, moves = 0
define click = 0, start = 0

dim list[size]

gosub setup
gosub game

end

sub setup

	title "15 Puzzle"

	bgcolor 0,128,0
	cls graphics

	resize 0, 0, 170, 270
	center

	let x = 0
	let y = 30

	for i = 0 to size - 1

		if x = 112 then

			let x = 0
			let y = y + 25

		endif

		let x = x + 28

		formid i + 1
		formtext ""
		buttonform x, y, 25, 20

	next i

	formid 17
	formtext "
	staticform 40, 130, 100, 20
	bgcolor 0, 128, 0
	fgcolor 255, 255, 0
	colorform

	formid 18
	formtext ""
	staticform 40, 150, 100, 20
	bgcolor 0, 128, 0
	fgcolor 255, 255, 0
	colorform

	formid 19
	formtext "New"
	buttonform 1, 1, 50, 20

	formid 20
	formtext "Help"
	buttonform 55, 1, 50, 20

	formid 21
	formtext "About"
	buttonform 110, 1, 50, 20

	formid 22
	formtext "Welcome."
	staticform 40, 170, 120, 20
	bgcolor 0, 128, 0
	fgcolor 255, 255, 0
	colorform

return

sub shuffle

	let start = 1

	formid 22
	formtext "shuffling..."
	updateform

	for i = 0 to size - 1

		formid i + 1
		formtext ""
		updateform

		let list[i] = 0

	next i

	let t = 0
	let i = 0

	do

		if i = 14 then

			let n = 120 - t

			formid i + 1
			formtext n
			updateform

			let list[i] = n

			break

		endif

		for f = 0 to size - 1

			let n = int(rnd * 15) + 1
			let s = 0

			for c = 0 to i - 1

				if n = list[c] then

					let s = 1
					break c

				endif

			next c

			if s = 0 and list[i] = 0 then

				formid i + 1
				formtext n
				updateform

				let list[i] = n
				let t = t + n
				let i = i + 1

			endif

			wait

		next f

	loop i < size - 1

	formid 22
	formtext ""
	updateform

return

sub game

	do

		let click = forms

		if click > 0 and click < 17 and start = 1 then

			let moves = moves + 1

			formid 17
			formtext "Moves: ", moves
			updateform

			gosub checkspaces
			gosub checkorder

		endif

		if click = 19 then

			gosub shuffle

			let moves = 0
			let correct = 0

			formid 17
			formtext "Moves:"
			updateform

			formid 18
			formtext "Correct:"
			updateform

		endif

		if click = 20 then

			alert "Click the numbers to move them in the correct order."

		endif

		if click =  21 then

			alert "15 Puzzle", newline, "by Gemino Smothers 2023 ", newline, " www.lucidapogee.com"

		endif

		button k, 27

		wait

	loop k = 0

return

sub checkspaces

	let click = click - 1
	let top = click - 4
	let right = click + 1
	let bottom = click + 4
	let left = click - 1

	if top >= 0 then

		if list[top] = 0 then

			let n = top
			gosub swap

		endif

	endif

	if right <= size - 1 then

		if list[right] = 0 then

			let n = right
			gosub swap

		endif

	endif

	if bottom <= size - 1 then

		if list[bottom] = 0 then

			let n = bottom
			gosub swap

		endif

	endif

	if left >= 0 then

		if list[left] = 0 then

			let n = left
			gosub swap

		endif

	endif

return

sub swap

	let t = list[click]
	let list[n] = list[click]
	let list[click] = 0

	let click = click + 1
	formid click
	formtext ""
	updateform

	let n = n + 1
	formid n
	formtext t
	updateform

return

sub checkorder

	let correct = 0

	for i = 0 to size - 2

		if list[i] = i + 1 then

			let correct = correct + 1

		endif

	next i

	formid 18
	formtext "Correct: ", correct
	updateform

	if correct = size - 1 then 

		wait
		alert "You win! Moves: ", moves

	endif

return

Delphi

Works with: Delphi version 6.0

This is a pure Delphi version of the program. Rather than use a console based display, this version uses a Delphi Form for the game and a string grid for the display. The users selects a move by clicking on the a particular cell in the grid.

const BoardWidth = 4; BoardHeight = 4;
const CellCount = BoardWidth * BoardHeight;

var GameBoard: array [0..BoardWidth-1,0..BoardHeight-1] of integer;


procedure BuildBoard;
{Put all number in the game board}
var I,X,Y: integer;
begin
for I:=0 to CellCount-1 do
	begin
	Y:=I div BoardHeight;
	X:=I mod BoardWidth;
	GameBoard[X,Y]:=I;
	end;
end;


function IsWinner: boolean;
{Check to see if tiles are winning in order}
var I,X,Y: integer;
begin
Result:=False;
for I:=1 to CellCount-1 do
	begin
	Y:=(I-1) div BoardHeight;
	X:=(I-1) mod BoardWidth;
	if GameBoard[X,Y]<>I then exit;
	end;
Result:=True;
end;


procedure DisplayGameBoard(Grid: TStringGrid);
{Display game on TStringGrid component}
var Tile,X,Y: integer;
var S: string;
begin
for Y:=0 to High(GameBoard) do
	begin
	S:='';
	for X:=0 to High(GameBoard[0]) do
		begin
		Tile:=GameBoard[X,Y];
		if Tile=0 then Form1.GameGrid.Cells[X,Y]:=''
		else Grid.Cells[X,Y]:=IntToStr(GameBoard[X,Y]);
		end;
	end;
end;



procedure ExchangePieces(P1,P2: TPoint);
{Exchange the pieces specified by P1 and P2}
var T: integer;
begin
T:=GameBoard[P1.X,P1.Y];
GameBoard[P1.X,P1.Y]:=GameBoard[P2.X,P2.Y];
GameBoard[P2.X,P2.Y]:=T;
end;


procedure Randomize;
{Scramble piece by exchanging random pieces}
var I: integer;
var P1,P2: TPoint;
begin
for I:=0 to 100 do
	begin
	P1:=Point(Random(BoardWidth),Random(BoardHeight));
	P2:=Point(Random(BoardWidth),Random(BoardHeight));
	ExchangePieces(P1,P2);
	end;
end;


procedure NewGame;
{Initiate new game by randomizing tiles}
begin
BuildBoard;
Randomize;
DisplayGameBoard(Form1.GameGrid);
end;



function FindEmptyNeighbor(P: TPoint): TPoint;
{Find the empty neighbor cell if any}
{Returns Point(-1,-1) if none found}
begin
Result:=Point(-1,-1);
if (P.X>0) and (GameBoard[P.X-1,P.Y]=0) then Result:=Point(P.X-1,P.Y)
else if (P.X<(BoardWidth-1)) and (GameBoard[P.X+1,P.Y]=0) then Result:=Point(P.X+1,P.Y)
else if (P.Y>0) and (GameBoard[P.X,P.Y-1]=0) then Result:=Point(P.X,P.Y-1)
else if (P.Y<(BoardHeight-1)) and (GameBoard[P.X,P.Y+1]=0) then Result:=Point(P.X,P.Y+1);
end;



procedure ShowStatus(S: string; BellCount: integer);
{Display status string and ring bell specified number of times}
var I: integer;
begin
Form1.StatusMemo.Lines.Add(S);
for I:=1 to BellCount do PlaySound('DeviceFail', 0, SND_SYNC);
end;



procedure HandleMouseClick(X,Y: integer; Grid: TStringGrid);
{Handle mouse click on specified grid}
var Pos,Empty: TPoint;
var Item: integer;
begin
Grid.MouseToCell(X, Y,Pos.X, Pos.Y);
Item:=GameBoard[Pos.X,Pos.Y];
Empty:=FindEmptyNeighbor(Pos);
if (Item>0) and (Empty.X>=0) then
	begin
	ExchangePieces(Empty,Pos);
	DisplayGameBoard(Grid);
	if IsWinner then ShowStatus('Winner', 5);
	end
else ShowStatus('Invalid Command.', 1);
end;



procedure TForm1.NewGameBtnClick(Sender: TObject);
{Create new game when button pressed}
begin
NewGame;
end;


procedure TForm1.GameGridMouseDown(Sender: TObject; Button: TMouseButton;
  Shift: TShiftState; X, Y: Integer);
{Use the mouse click event to select a move}
begin
HandleMouseClick(X,Y,GameGrid);
end;

procedure TForm1.FormCreate(Sender: TObject);
{Start new game when the program starts running}
begin
NewGame;
end;
Output:

EasyLang

Run it

sysconf topleft
background 432
textsize 13
len f[] 16
proc draw . .
   clear
   for i = 1 to 16
      h = f[i]
      if h < 16
         x = (i - 1) mod 4 * 24 + 3
         y = (i - 1) div 4 * 24 + 3
         color 210
         move x y
         rect 22 22
         move x + 4 y + 6
         if h < 10
            move x + 6 y + 6
         .
         color 885
         text h
      .
   .
.
global done .
proc smiley . .
   s = 3.5
   x = 86
   y = 86
   move x y
   color 983
   circle 2.8 * s
   color 000
   move x - s y - s
   circle s / 3
   move x + 3.5 y - 3.5
   circle s / 3
   linewidth s / 3
   curve [ x - s y + s x y + 2 * s x + s y + s ]
.
proc init . .
   done = 0
   for i = 1 to 16
      f[i] = i
   .
   # shuffle
   for i = 15 downto 2
      r = random i
      swap f[r] f[i]
   .
   # make it solvable
   inv = 0
   for i = 1 to 15
      for j = 1 to i - 1
         if f[j] > f[i]
            inv += 1
         .
      .
   .
   if inv mod 2 <> 0
      swap f[1] f[2]
   .
   textsize 12
   draw
.
proc move_tile . .
   c = mouse_x div 25
   r = mouse_y div 25
   i = r * 4 + c + 1
   if c > 0 and f[i - 1] = 16
      swap f[i] f[i - 1]
   elif r > 0 and f[i - 4] = 16
      swap f[i] f[i - 4]
   elif r < 3 and f[i + 4] = 16
      swap f[i] f[i + 4]
   elif c < 3 and f[i + 1] = 16
      swap f[i] f[i + 1]
   .
   draw
   for i = 1 to 15
      if f[i] > f[i + 1]
         return
      .
   .
   done = 1
   timer 0.5
.
on mouse_down
   if done = 0
      move_tile
   elif done = 3
      init
   .
.
on timer
   if done = 1
      smiley
      done = 2
      timer 2
   else
      done = 3
   .
.
init

F#

// 15 Puzzle Game. Nigel Galloway: August 9th., 2020
let Nr,Nc,RA,rnd=[|3;0;0;0;0;1;1;1;1;2;2;2;2;3;3;3|],[|3;0;1;2;3;0;1;2;3;0;1;2;3;0;1;2|],[|for n in [1..16]->n%16|],System.Random()
let rec fN g Σ=function h::t->fN g (Σ+List.sumBy(fun n->if h>n then 1 else 0)t) t|_->(Σ-g/4)%2=1
let rec fI g=match if System.Console.IsInputRedirected then char(System.Console.Read()) else System.Console.ReadKey(true).KeyChar with
               n when Seq.contains n g->printf "%c" n; (match n with 'l'-> -1|'r'->1|'d'->4|_-> -4)|_->System.Console.Beep(); fI g 
let rec fG n Σ=function 0->(List.findIndex((=)0)Σ,Σ)|g->let i=List.item(rnd.Next(g)) n in fG(List.except [i] n)(i::Σ)(g-1)
let rec fE()=let n,g=fG [0..15] [] 16 in if fN n 0 (List.except [0] g) then (n,Array.ofList g) else fE()
let rec fL(n,g) Σ=let fa=printfn "";Array.chunkBySize 4 g|>Array.iter(fun n->Array.iter(printf "%3d")n;printfn "")
                  match g=RA with true->printfn "Solved in %d moves" Σ; fa; 0
                                 |_->let vM=match n/4,n%4 with (0,0)->"rd"|(0,3)->"ld"|(0,_)->"lrd"|(3,0)->"ru"|(3,3)->"lu"|(3,_)->"lru"|(_,0)->"rud"|(_,3)->"lud"|_->"lrud"
                                     fa; printf "Move Number: %2d; Manhatten Distance: %2d; Choose move from %4s: " Σ
                                         ([0..15]|>List.sumBy(fun n->match g.[n] with 0->0 |i->(abs(n/4-Nr.[i]))+(abs(n%4-Nc.[i])))) vM
                                     let v=fI vM in g.[n]<-g.[n+v];g.[n+v]<-0;fL(n+v,g)(Σ+1)
[<EntryPoint>]
let main n = fL(match n with [|n|]->let g=[|let g=uint64 n in for n in 60..-4..0->int((g>>>n)&&&15UL)|] in (Array.findIndex((=)0)g,g) |_->fE()) 0

3 uses:

15 game with no parameters will generate a random game which may be solved.
A solution in the form suggested in 15_puzzle_solver may be piped into 15game. "dddrurdruuulllddrulddrrruuullddruulldddrrurulldrruulldlddrurullddrrruullulddrdrr" | .\15game 0x0c9dfbae37254861 produces the output here: 15_puzzle_solver/extra_credit/solution.
Optionally a start position may be supplied. 15game 0x123450689a7bdefc may be solved:
Output:
  1  2  3  4
  5  0  6  8
  9 10  7 11
 13 14 15 12
Move Number:  0; Manhatten Distance:  4; Choose move from lrud: r
  1  2  3  4
  5  6  0  8
  9 10  7 11
 13 14 15 12
Move Number:  1; Manhatten Distance:  3; Choose move from lrud: d
  1  2  3  4
  5  6  7  8
  9 10  0 11
 13 14 15 12
Move Number:  2; Manhatten Distance:  2; Choose move from lrud: r
  1  2  3  4
  5  6  7  8
  9 10 11  0
 13 14 15 12
Move Number:  3; Manhatten Distance:  1; Choose move from  lud: d
  1  2  3  4
  5  6  7  8
  9 10 11 12
 13 14 15  0
Solved in 4 moves

Factor

USING: accessors combinators combinators.extras
combinators.short-circuit grouping io kernel literals math
math.matrices math.order math.parser math.vectors prettyprint qw
random sequences sequences.extras ;
IN: rosetta-code.15-puzzle-game

<<

TUPLE: board matrix zero ;

: <board> ( -- board )
    16 <iota> 1 rotate 4 group { 3 3 } board boa ;

>>

CONSTANT: winning $[ <board> matrix>> ]

: input>dir ( str -- pair )
    {
        { "u" [ { 1 0 } ] }
        { "d" [ { -1 0 } ] }
        { "l" [ { 0 1 } ] }
        { "r" [ { 0 -1 } ] }
    } case ;

: get-index ( loc matrix -- elt ) [ first2 swap ] dip nth nth ;

: mexchange ( loc1 loc2 matrix -- )
    tuck [ [ [ get-index ] keepd ] 2bi@ ] keep [ spin ] 2dip
    [ set-index ] keep set-index ;

: vclamp+ ( seq1 seq2 -- seq ) v+ { 0 0 } { 3 3 } vclamp ;

: slide-piece ( board str -- )
    over zero>> [ vclamp+ ] keep rot matrix>> mexchange ;

: move-zero ( board str -- )
    [ vclamp+ ] curry change-zero drop ;

: move ( board str -- )
    input>dir [ slide-piece ] [ move-zero ] 2bi ;

: rand-move ( board -- ) qw{ u d l r } random move ;

: shuffle-board ( board n -- board' ) [ dup rand-move ] times ;

: .board ( board -- ) matrix>> simple-table. ;

: get-input ( -- str )
    "Your move? (u/d/l/r/q) " write flush readln dup
    qw{ u d l r q } member? [ drop get-input ] unless ;

: won? ( board -- ? ) matrix>> winning = ;

DEFER: game
: process-input ( board -- board' )
    get-input dup "q" = [ drop ] [ game ] if ;

: check-win ( board -- board' )
    dup won? [ "You won!" print ] [ process-input ] if ;

: game ( board str -- board' )
    [ move ] keepd dup .board check-win ;

: valid-difficulty? ( obj -- ? )
    { [ fixnum? ] [ 3 100 between? ] } 1&& ;

: choose-difficulty ( -- n )
    "How many shuffles? (3-100) " write flush readln
    string>number dup valid-difficulty?
    [ drop choose-difficulty ] unless ;

: main ( -- )
    <board> choose-difficulty shuffle-board dup .board check-win
    drop ;

MAIN: main
Output:
How many shuffles? (3-100) 5
1  2  3  4
5  6  7  8
9  0  10 12
13 14 11 15
Your move? (u/d/l/r/q) apple
Your move? (u/d/l/r/q) l
1  2  3  4
5  6  7  8
9  10 0  12
13 14 11 15
Your move? (u/d/l/r/q) u
1  2  3  4
5  6  7  8
9  10 11 12
13 14 0  15
Your move? (u/d/l/r/q) l
1  2  3  4
5  6  7  8
9  10 11 12
13 14 15 0
You won!

Forth

Works with: gforth version 0.7.2

The code tested with gforth 0.7.2. It required a 64-bit system.

See 15_puzzle_solver#Forth for a solver based on the same code.

#! /usr/bin/gforth

cell 8 <> [if] s" 64-bit system required" exception throw [then]

\ In the stack comments below,
\ "h" stands for the hole position (0..15),
\ "s" for a 64-bit integer representing a board state,
\ "t" a tile value (0..15, 0 is the hole),
\ "b" for a bit offset of a position within a state,
\ "m" for a masked value (4 bits selected out of a 64-bit state),
\ "w" for a weight of a current path,
\ "d" for a direction constant (0..3)

\ Utility
: 3dup   2 pick 2 pick 2 pick ;
: 4dup   2over 2over ;
: shift   dup 0 > if lshift else negate rshift then ;

hex 123456789abcdef0 decimal constant solution
: row   2 rshift ;   : col   3 and ;

: up-valid?    ( h -- f ) row 0 > ;
: down-valid?  ( h -- f ) row 3 < ;
: left-valid?  ( h -- f ) col 0 > ;
: right-valid? ( h -- f ) col 3 < ;

\ To iterate over all possible directions, put direction-related functions into arrays:
: ith ( u addr -- w ) swap cells + @ ;
create valid? ' up-valid? , ' left-valid? , ' right-valid? , ' down-valid? , does> ith execute ;
create step -4 , -1 , 1 , 4 , does> ith ;

\ Advance from a single state to another:
: bits ( h -- b ) 15 swap - 4 * ;
: tile ( s b -- t ) rshift 15 and ;
: new-state ( s h d -- s' ) step dup >r + bits 2dup tile ( s b t ) swap lshift tuck - swap r> 4 * shift + ;

: hole? ( s u -- f ) bits tile 0= ;
: hole ( s -- h ) 16 0 do dup i hole? if drop i unloop exit then loop drop ;

0 constant up 1 constant left 2 constant right 3 constant down

\ Print a board:
: .hole   space space space ;
: .tile ( u -- ) ?dup-0=-if .hole else dup 10 < if space then . then ;
: .board ( s -- ) 4 0 do cr 4 0 do dup j 4 * i + bits tile .tile loop loop drop ;
: .help   cr ." ijkl move, q quit" ;

\ Pseudorandom number generator:
create (rnd)   utime drop ,
: rnd   (rnd) @ dup 13 lshift xor dup 17 rshift xor dup dup 5 lshift xor (rnd) ! ;

: move ( s u -- s' ) >r dup hole r> new-state ;
: ?move ( s u -- s' ) >r dup hole r@ valid? if r> move else rdrop then ;
: shuffle ( s u -- s' ) 0 do rnd 3 and ?move loop ;

: win   cr ." you won!" bye ;
: turn ( s -- )
	page dup .board .help
	key case
		[char] q of bye endof
		[char] i of down ?move endof
		[char] j of right ?move endof
		[char] k of up ?move endof
		[char] l of left ?move endof
	endcase ;

: play  begin dup solution <> while turn repeat win ;

solution 1000 shuffle play

Fortran

The initial version had me so enamoured by the notion of consecutive cells for the solution having the number of their index as their value (as in CELL(0) = 0 (the blank square), CELL(1) = 1, ... CELL(15) = 15) and the prospect of the check for this being simple, that I failed to perceive that the nice big diagram of the board shown at the head of the article in fact clearly shows the solution state having the blank cell at the end, not the start. Once again it is demonstrated that what you see is ... influenced ... by what you would like to see. After that diversion, the cells shall now be numbered one to sixteen, not zero to fifteen, and so there is no need for the ability introduced by F90 whereby arrays can have a lower bound other than one.

The plan is to use parameters for the board size, which need not be square. As often with Fortran, messing with arrays is the key, though not without opportunities for confusion. Because Fortran stores arrays in column-major order, the arrays are accessed as BOARD(column,row) even though the arrangement is treated as rows down the page and columns across as is usual. By this means, consecutive elements in storage of array BOARD(c,r) are such that the same storage accessed via array BORED(i) thanks to EQUIVALENCE(BOARD,BORED) indexes them as consecutive elements, and so the test that the values are in consecutive order becomes delightfully simple, though alas there is no equivalent of the iota function of APL whereby the test could be ALL(BORED(1:N - 1) .EQ. IOTA(N - 1))

Column-major ordering also applies to array WAY, which lists the offsets needed to locate squares deemed adjacent to a given location, such as that of the blank square, located by LOCI = LOCZ + WAY(i). Adjacent LOCI are checked for being in range, and if so, added to the list in array LOCM with the moveable piece identified in array MOVE.

It transpires that the F90 compiler will not allow a PARAMETER statement to define values for items appearing in an EQUIVALENCE statement; so much for an attempt to do so in a systematic manner employing related names.

The game plan is to start with an ordered array so that each cell definitely has a unique code, then jumble them via "random" swaps. Possible arrangements turn out to have either odd or even parity based on the number of out-of-sequence squares, and as the allowed transformations do not change the parity and the solution state has even parity, odd parity starting states should not be presented except by those following Franz Kafka. The calculation is simplified by always having the blank square in the last position, thus in the last row. Once an even-parity starting state is floundered upon, the blank square is re-positioned using allowable moves so that the parity is not altered thereby. Then the game begins: single-square moves only are considered, though in practice groups of squares could be moved horizontally or vertically rather than one-step-at-a-time - a possible extension.

The source style uses F90 for its array arithmetic abilities, especially the functions ALL, ANY and COUNT. A statement

LOCZ = MINLOC(BOARD)	!Find the zero. 0 = BOARD(LOCZ(1),LOCZ(2)) == BOARD(ZC,ZR)

could be used but is unnecessary thanks to tricks with EQUIVALENCE. For earlier Fortran, various explicit DO-loops would have to be used. This would at least make clear whether or not the equivalents of ANY and ALL terminated on the first failure or doggedly scanned the entire array no matter what.

      SUBROUTINE SWAP(I,J)	!Alas, furrytran does not provide this.
       INTEGER I,J,T		!So, we're stuck with supplying the obvious.
        T = I			!And, only for one type at a go.
        I = J			!One could define a MODULE containing a collection
        J = T			!And thence a "generic" routine,
      END SUBROUTINE SWAP	!But this will do for now.

      SUBROUTINE SHOW(NR,NC,BOARD)	!The layout won't work for NC > 99...
       INTEGER NR,NC		!Number of rows and columns.
       INTEGER BOARD(NC,NR)	!The board is stored transposed!
       INTEGER I		!A stepper.
       COMMON/IODEV/ MSG	!I talk to the trees...
        WRITE (MSG,1) (I,I = 1,NC)	!Prepare a heading.
    1   FORMAT ("Row|",9("__",I1,:),90("_",I2,:))	!This should suffice.
        DO I = 1,NR		!Chug down the rows.
          WRITE (MSG,2) I,BOARD(1:NC,I)	!The columns of the row. Usage is BOARD(column,row).
    2     FORMAT (I3,"|",99I3)	!Could use parameters, but enough.
        END DO			!On to the next row.
      END SUBROUTINE SHOW	!That was nice.

      PROGRAM PUZZLE
      INTEGER LOCN(2),NR,NC,N	!Describes the shape of the board.
      INTEGER LOCZ(2),ZC,ZR	!Fingers the location of the "blank" square.
      INTEGER LOCI(2),IC,IR	!Fingers a location.
Can't EQUIVALENCE (LOCN(1),NC),(LOCN(2),NR)	!This usage and a PARAMETER statement is too scary.
      EQUIVALENCE (LOCZ(1),ZC),(LOCZ(2),ZR)	!Annotate my (column,row) usage.
      EQUIVALENCE (LOCI(1),IC),(LOCI(2),IR)	!Rather than the displayed (row,column) style.
      PARAMETER (NR = 4, NC = 4, N = NR*NC)	!Determine the shape of the board.
      INTEGER BOARD(NC,NR)		!Thus transpose furrytran's column-major usage. Beware!!!
      INTEGER BORED(N)			!This allows for consecutive comparisons.
      EQUIVALENCE (BOARD,BORED)		!Because the arrays are in the same place.
      INTEGER WAYS			!Now define adjacency.
      PARAMETER (WAYS = 4)		!Just orthogonal neghbours.
      INTEGER WAY(2,WAYS)		!Now list the allowed adjacencies.
      PARAMETER (WAY = (/1,0, 0,1, -1,0, 0,-1/))	!W(1,1), W(2,1), W(1,2), W(2,2), W(1,3), ...
      INTEGER M,MOVE(WAYS),LOCM(2,WAYS)	!Move possibilities.
      INTEGER SPACE			!Document the empty square's code number.
      PARAMETER (SPACE = 0)		!Zero will do.
      INTEGER I,IT,PARITY,TRY		!Odds and ends.
      REAL VALUE			!Humph. Yet another interface to a "random" number generator.
      COMMON/IODEV/ MSG,KBD	!Pass the word.

      KBD = 5	!Standard input. (Keyboard -> Display screen)
      MSG = 6	!Standard output. (Display screen)
      WRITE (MSG,1) NR,NC	!Announce.
    1 FORMAT ("To play 'slide-square' with ",I0," rows and ",
     1 I0," columns.",/,"The game is to slide a square into the space",/
     2 "(thus leaving a space behind) until you attain"/
     3 "the nice orderly layout as follows:",/)
Concoct a board layout.
   10 FOR ALL (I = 1:N - 1) BORED(I) = I	!Prepare the board. Definitely unique values.
      BORED(N) = SPACE	        !The empty square is not at the start! Oh well.
      CALL SHOW(NR,NC,BOARD)	!Reveal the nice layout.
   11 DO I = 1,N - 1		!Now shuffle the squares a bit.
        CALL RANDOM(VALUE)		!0 <= VALUE < 1.
        IT = VALUE*(N - 1) + 1		!1 <= IT < N. Don't round up!
        IF (I.NE.IT) CALL SWAP(BORED(I),BORED(IT))	!Whee!
      END DO			!On to the next victim, leaving the last cell alone.
Calculate the parity, knowing the space is at the end. The target state has even parity, with zero inversions.
      PARITY = 0	!There are two classes of arrangements, that can't mix.
      DO I = 1,N - 2	!Skipping the blank cell still at BORED(N).
        PARITY = PARITY + COUNT(BORED(I) > BORED(I + 1:N - 1))	!For each square,
      END DO		!Count the inversions following.
      IF (MOD(PARITY,2).NE.0) GO TO 11	!No transition can change the parity, so, try for another arrangement.
Choose a new position for the space. Using approved moves will not change the parity.
      CALL RANDOM(VALUE)		!0 <= VALUE < 1.
      ZC = VALUE*(NC - 2) + 1		!1 <= ZC < NC: Choose a random column other than the last.
      BOARD(ZC + 1:NC,NR) = BOARD(ZC:NC - 1,NR)	!Shift the end of the last row back one place.
      BOARD(ZC,NR) = SPACE			!Put the space in the hole.
      CALL RANDOM(VALUE)			!So the parity doesn't change.
      ZR = VALUE*(NR - 2) + 1		!1 <= ZR < NR: Choose a random row, other than the last.
      BOARD(ZC,ZR + 1:NR) = BOARD(ZC,ZR:NR - 1)	!Shift the end of column ZC up one.
      BOARD(ZC,ZR) = SPACE			!Revive the space again.
Cast forth the starting position.
      WRITE (MSG,12)		!Announce the result.
   12 FORMAT (/,"But, your board looks like this...")	!Alas. Almost certainly not in order.
      CALL SHOW(NR,NC,BOARD)	!Just so.
      TRY = 0		!No moves made yet.

Consider possible moves.
   20 TRY = TRY + 1	!Here we go again.
      M = 0		!No moveable pieces are known.
      DO I = 1,WAYS	!So scan the possible ways away from LOCZ.
        LOCI = LOCZ + WAY(1:2,I)	!Finger an adjacent location, via the adjacency offsets in array WAY.
        IF (ALL(LOCI > 0) .AND. ALL(LOCI <= (/NC,NR/))) THEN	!Within bounds?
          M = M + 1			!Yes. We have a candidate.
          MOVE(M) = BOARD(IC,IR)	!Record the piece's name.
          LOCM(:,M) = LOCI		!And, remember where it is...
        END IF			!So much for that location.
      END DO		!Try another offset.
   21 WRITE (MSG,22,ADVANCE="no") MOVE(1:M)	!Two-stage output.
   22 FORMAT ("Moveable pieces: ",<WAYS>(I0:","))	!Since M is not necessarily WAYS, a trailing $ may not be reached..
      WRITE (MSG,23)		!Now for the question. Always at least two moveable squares.
   23 FORMAT(". Choose one: ",$)	!Continue the line, presuming screen and keyboard->screen.
      READ (KBD,*) IT		!Now request the answer. Rather doggedly: blank lines won't do.
      DO I = M,1,-1		!There are at least two possible moves.
        IF (MOVE(I) .EQ. IT) EXIT	!Perhaps this piece was selected.
      END DO			!The INDEX function is alas, only for CHARACTER variables. Grr.
      IF (I .LE. 0) THEN	!I'm suspicious.
        WRITE (MSG,*) "Huh? That is not a moveable piece!"	!Justified!
        IF (IT.GT.0) GO TO 21		!Try again.
        STOP "Oh well."			!Or quit, on negative vibrations.
      END IF			!So much for selecting a piece.
Complete the selected move.
   30 BOARD(ZC,ZR) = IT		!Place the named piece where the space was.
      LOCZ = LOCM(:,I)		!The space is now where that piece came from.
      BOARD(ZC,ZR) = SPACE		!And now holds a space.
c      write (6,*)
c     1 "disorder=",COUNT(BORED(1:N - 2) + 1 .NE. BORED(2:N - 1))
      IF (TRY.LE.6) WRITE (MSG,31)	!Set off with a nice heading.
   31 FORMAT (/"The new layout...")	!Just for clarity.
      CALL SHOW(NR,NC,BOARD)		!Perhaps it will be good.
Check for success.
      IF (BORED(N).NE.SPACE) GO TO 20	!Is the space at the end?
      IF (ANY(BORED(1:N - 2) + 1 .NE. BORED(2:N - 1))) GO TO 20	!Are we there yet?
      WRITE (MSG,*) TRY,"Steps to success!"	!Yes!
      END	!That was fun.

Output: Not so good. As ever, the character cell sizes are not square so a square game board comes out as a rectangle. Similarly, underlining is unavailable (no overprints!) so the layout is not pleasing. There are special "box-drawing" glyphs available, but they are not standardised and there is still no overprinting so that a flabby waste of space results. Further, there is no ability to re-write the display, even though one could easily regard the output to the screen as a random-access file: WRITE (MSG,REC = 6) STUFF would rewrite the sixth line of the display. Instead, output relentlessly rolls forwards, starting as follows:

To play 'slide-square' with 4 rows and 4 columns.
The game is to slide a square into the space
(thus leaving a space behind) until you attain
the nice orderly layout as follows:

Row|__1__2__3__4
  1|  1  2  3  4
  2|  5  6  7  8
  3|  9 10 11 12
  4| 13 14 15  0

But, your board looks like this...
Row|__1__2__3__4
  1| 15  0 14 11
  2|  8 13  5  3
  3|  4  1  7  9
  4| 10  6  2 12
Moveable pieces: 14,13,15. Choose one: 15

The new layout...
Row|__1__2__3__4
  1|  0 15 14 11
  2|  8 13  5  3
  3|  4  1  7  9
  4| 10  6  2 12
Moveable pieces: 15,8. Choose one:

The display here turns out to be less rectangular than that of the "console" screen's usual setting, which changes with the typeface and sizing anyway. Endless variation. As for playing the game, it is much easier to get a "feel" for the possibilities when manipulating the actual physical object. The digital world is less real.

FreeBASIC

sub drawboard( B() as ubyte )
    dim as string outstr = ""
    for i as ubyte = 0 to 15
        if B(i) = 0 then 
            outstr = outstr + " XX "
        elseif B(i) < 10 then
            outstr = outstr + "  "+str(B(i))+" "
        else
            outstr = outstr + " " +str(B(i))+" "
        end if
        if i mod 4 = 3 then 
            print outstr
            print
            outstr = ""
        end if
    next i
    print
end sub

function move( B() as ubyte, byref gap as ubyte, direction as ubyte ) as ubyte
    dim as integer targ = gap
    select case direction
        case 1  'UP
            targ = gap - 4
        case 2  'RIGHT
            if gap mod 4 = 3 then return gap
            targ = gap + 1
        case 3  'DOWN
            targ = gap + 4
        case 4
            if gap mod 4 = 0 then return gap
            targ = gap - 1
        case else
            return gap
    end select
    if targ > 15 or targ < 0 then return gap
    swap B(targ), B(gap)
    return targ
end function

sub shuffle( B() as ubyte, byref gap as ubyte )
    for i as ubyte = 0 to 100
        gap = move(B(), gap, int(rnd*4) + 1)
    next i
end sub

function solved( B() as ubyte ) as boolean
    dim as integer i
    for i = 0 to 14
        if B(i)>B(i+1) then return false
    next i
    return true
end function

dim as ubyte i, B(15), direction, gap
for i = 0 to 15
    B(i) = i
next i
shuffle B(), gap


while not solved( B() )
    cls
    drawboard B()
    print gap
    print "1 = up, 2=right, 3=down, 4=left"
    input direction
    gap = move( B(), gap, direction )
wend

cls
print "Congratulations! You win!"
print
drawboard B()


FutureBasic

// 15 Puzzle // 26 september 2023 //

begin globals
CFMutableStringRef board : board = fn MutableStringNew
end globals


void local fn buildUI
  Long i, j, k = 1 // k is button number
  window 1, @"15 Puzzle", ( 0, 0, 200, 200 ), 3
  for j = 3 to 0 step -1 : for i = 0 to 3 // Top to bottom, left to right
    button k, Yes, 1, @"",  ( 20 + 40 * i, 20 + 40 * j , 40, 40 ), , NSBezelStyleShadowlessSquare
    ControlSetFont(k, fn FontSystemFontOfSize( 21 ) )
    ControlSetAlignment( k, NSTextAlignmentCenter )
    k ++
  next : next
  menu 1, , 1, @"File": menu 1, 1, , @"Close", @"w" : MenuItemSetAction( 1, 1, @"performClose:" )
  editmenu 2 : menu 2, 0, No : menu 3, , , @"Level"
  for i = 1 to 8 : menu 3, i, , str( i ) : next
  MenuSetOneItemOnState( 3, 3 )
end fn


void local fn newGame
  CFStringRef s
  Long i, m, n = 16, p = 0 // n is empty starting tile, p holds previous move
  Bool ok
  MutableStringSetString (board, @" 123456789ABCDEF " )
  for i = 1 to fn MenuSelectedItem( 3 )^2 // Number of shuffles is square of level
    do : ok = Yes
      m = n + int( 2.6 * rnd( 4 ) - 6.5 )       // Choose a random move, but
      if m < 1 or m > 16 or m == p then ok = No // not of bounds or previous,
      if n mod 4 = 0 and m = n + 1 then ok = No // and don't exchange eg tile 4 and 5
      if n mod 4 = 1 and m = n - 1 then ok = No // or 9 and 8
    until ok = Yes // Found a move, swap in board string
    s = mid( board, m, 1 ) : mid( board, m, 1 ) = @" " : mid( board, n, 1 ) = s
    p = n : n = m
  next
  for i = 1 to 16 // Stamp the buttons, p is unicode of board char, s is button title
    p = (Long) fn StringCharacterAtIndex( board, i )
    if p > 64 then s = fn StringWithFormat ( @"%d", p - 55 ) else s = mid( board, i, 1 )
    button i, Yes, 1, s
    if fn StringIsEqual( s, @" ") == Yes then button i, No
  next
end fn


void local fn move ( n as Long )
  CFStringRef s
  Long i, m, x = -1 // x is empty plot
  Bool ok
  for i = 1 to 4 // see if clicked button is next to empty plot
    m = n + int( 2.6 * i - 6.5 ) // -4. -1, +1, +4
    ok = Yes
    if m < 1 or m > 16 then ok = No // Not out of bounds etc
    if n mod 4 = 0 and m = n + 1 then ok = No
    if n mod 4 = 1 and m = n - 1 then ok = No
    if ok == Yes
      if fn StringIsEqual( mid( board, m, 1 ), @" " ) then x = m
    end if    
  next
  if x > -1 // Swap places in board string and button titles
    s = mid( board, n, 1 ) : mid( board, n, 1 ) = @" " : mid( board, x, 1 ) = s
    button x, Yes, 1 , fn ButtonTitle( n ) : button n, No, 1, @" "
  end if
  if fn StringIsEqual( board, @" 123456789ABCDEF " )
    alert 112, , @"Well done.", @"Another game?", @"Yes;No", Yes
  end if
end fn


void local fn doMenu( mnu as Long, itm as Long )
  if mnu == 3 then MenuSetOneItemOnState( 3, itm ) : fn newGame
end fn


void local fn DoDialog( evt as Long, tag as Long )
  select evt
    case _btnClick : fn move( tag )
    case _alertDidEnd : if tag == NSAlertFirstButtonReturn then fn newGame else end
  end select
end fn

fn buildUI
fn newGame

on dialog fn doDialog
on menu fn doMenu
handleevents

Gambas

'Charlie Ogier (C) 15PuzzleGame 24/04/2017 V0.1.0 Licenced under MIT
'Inspiration came from: -
''http://rosettacode.org/wiki/15_Puzzle_Game
''Bugs or comments to bugs@cogier.com
'Written in Gambas 3.9.2 - Updated on the Gambas Farm 01/05/2017
'Updated so that the message and the Title show the same amount of moves 01/06/2017
'Form now expandable. Font height automated. Form size and position saved 06/06/2107

'Simulate playing the 15 - game(puzzle)         Yes in GUI
'Generate a random start position               Yes
'Prompt the user for which piece To move        No
'Validate if the move is legal(possible)        Yes
'Display the game(puzzle) as pieces are moved   Yes in GUI
'Announce when the puzzle is solved             Yes
'Possibly keep track of the number of moves     Yes

byPos As New Byte[]                                             'Stores the position of the 'Tiles'
siMoves As Short                                                'Stores the amount of moves
hTimer As Timer                                                 'Timer
dTimerStart As Date                                             'Stores the start time 
dTimerDiff As Date                                              'Stores the time from the start to now
bTimerOn As Boolean                                             'To know if the Timer is running

Public Sub Form_Open()                                          'Form opens

Settings.read(Me, "Window")                                     'Get details of the last window position and size
With Me                                                         'With the Form..
  .Padding = 5                                                  'Pad the edges
  .Arrangement = Arrange.Row                                    'Arrange the Form
  .Title = "15PuzzleGame v0.3.0"                                'Set the Form Title
End With

BuildForm                                                       'Go to the BuildForm routine

End

Public Sub BuildForm()                                          'To add items to the Form
Dim hButton As Button                                           'We need some Buttons
Dim byRand, byTest As Byte                                      'Various variables
Dim bOK As Boolean                                              'Used to stop duplicate numbers being added
Dim bSolvable As Boolean

Repeat                                                          'Repeat until the puzzle is solvable    
  Do                                                            'Start of a Do loop to create 0 to 15 in random order
    byRand = Rand(0, 15)                                        'Get a random number between 0 and 15
    If byRand = 0 Then byRand = 99                              'Change 0 to 99 for the Blank space
    bOK = True                                                  'Set bOK to True
    For Each byTest In byPos                                    'For each number stored in the array byPos
      If byRand = byTest Then bOK = False                       'Check to see if it already exists, if it does set bOK to False
    Next
    If bOK Then byPos.Add(byRand)                               'If not a duplicate then add it to the array
    If byPos.max = 15 Then Break                                'Once the array has 16 numbers get out of here. 99 is used for the blank space
  Loop
  bSolvable = IsItSolvable()                                    'Go to the 'check if puzzle is solvable' routine
  If Not bSolvable Then byPos.clear                             'If it's not solvable then clear byPos
Until bSolvable = True                                          'Repeat until the puzzle is solvable

For byRand = 0 To 15                                            'Loop
  If byPos[byRand] = 99 Then                                    'Check if value is 99 as this is where the blank space will go
    AddPanel                                                    'Go to the AddPanel routine to add the blank space
    Continue                                                    'Skip to the end of the loop
  Endif
  hButton = New Button(Me) As "AllButtons"                      'Add a new button to the Form, all buttons grouped as 'AllButtons'
  With hButton                                                  'With the following properties
    .Text = Str(byPos[byRand])                                  'Add Button text 
    .Tag = Str(byPos[byRand])                                   'Add a Tag
    .Height = (Me.Height - 10) / 4                              'Set the Button height
    .Width = (Me.Width - 10) / 4                                'Set the Button width
    .Font.Bold = True                                           'Set the font to Bold
    .Font.Size = 16                                             'Set Font size
  End With
Next

AddTimer                                                        'Go to the AddTimer routine

End


Public Sub AddPanel()                                           'Routine to add an invisible panel that is the blank area
Dim hPanel As Panel                                             'We need a Panel

HPanel = New Panel(Me)                                          'Add the Panel to the Form
With HPanel                                                     'With the following Properties
  .Tag = 99                                                     'Set a Tag to 99
  .Height = (Me.Height - 10) / 4                                'Set the height
  .Width = (Me.Width - 10) / 4                                  'Set the width
End With

End

Public Sub AddTimer()                                           'To add a Timer

hTimer = New Timer As "MyTimer"                                 'Add a Timer
hTimer.Delay = 1000                                             'Set the timer delay 

End

Public Sub MyTimer_Timer()                                      'Timer

Me.Title = siMoves & " Moves "                                  'Set the Form Title to show the amount of moves taken

If dTimerStart Then                                             'If a start time has been set then
  dTimerDiff = Time(Now) - dTimerStart                          'Calculate the time difference between StartTime and Now
  Me.Title &= " - " & Str(dTimerDiff)                           'Add the time taken to the Form Title
End If

End

Public Sub AllButtons_Click()                                   'What to do when a Button is clicked
Dim byLast As Byte = Last.Tag                                   'Get the Tag of the Button clicked
Dim byTemp, byCount As Byte                                     'Various variables
Dim byCheck As Byte[] = [88, 88, 88, 88]                        'Used for checking for the blank space
Dim byWChgeck As New Byte[16, 4]
Dim oObj As Object                                              'We need to enumerate Objects

For Each oObj In Me.Children                                    'For each Object (Buttons in this case) that are Children of the Form..
  If oObj.Tag = byLast Then Break                               'If the Tag of the Button matches then we know the position of the Button on the form so get out of here
  Inc byCount                                                   'Increase the value of byCount
Next

Select Case byCount                                             'Depending on the position of the Button
  Case 0                                                        'e.g 0 then we need to check positions 1 & 4 for the blank
    byCheck[0] = 1
    byCheck[1] = 4
  Case 1
    byCheck[0] = 0
    byCheck[1] = 2
    byCheck[2] = 5
  Case 2
    byCheck[0] = 1
    byCheck[1] = 3
    byCheck[2] = 6
  Case 3
    byCheck[0] = 2
    byCheck[1] = 7
  Case 4
    byCheck[0] = 0
    byCheck[1] = 5
    byCheck[2] = 8
  Case 5                                                        'e.g 5 then we need to check positions 1, 4, 6 & 9 for the blank
    byCheck[0] = 1
    byCheck[1] = 4
    byCheck[2] = 6
    byCheck[3] = 9
  Case 6
    byCheck[0] = 2
    byCheck[1] = 5
    byCheck[2] = 7
    byCheck[3] = 10
  Case 7
    byCheck[0] = 3
    byCheck[1] = 6
    byCheck[2] = 11
  Case 8
    byCheck[0] = 4
    byCheck[1] = 9
    byCheck[2] = 12
  Case 9
    byCheck[0] = 5
    byCheck[1] = 8
    byCheck[2] = 10
    byCheck[3] = 13
  Case 10
    byCheck[0] = 6
    byCheck[1] = 9
    byCheck[2] = 11
    byCheck[3] = 14
  Case 11
    byCheck[0] = 7
    byCheck[1] = 10
    byCheck[2] = 15
  Case 12
    byCheck[0] = 8
    byCheck[1] = 13
  Case 13
    byCheck[0] = 9
    byCheck[1] = 12
    byCheck[2] = 14
  Case 14
    byCheck[0] = 10
    byCheck[1] = 13
    byCheck[2] = 15
  Case 15
    byCheck[0] = 11
    byCheck[1] = 14
End Select

For Each byTemp In byCheck                                      'For each value in byCheck
  If byTemp = 88 Then Break                                     'If byTemp = 88 then get out of here
  If byPos[byTemp] = 99 Then                                    'If the position checked is 99 (the blank) then..
    byPos[byTemp] = Last.Text                                   'Set the new position of the Tile in byPos
    byPos[byCount] = 99                                         'Set the existing Tile position to = 99 (blank)
    Inc siMoves                                                 'Inc the amount of moves made
    If Not bTimerOn Then                                        'If the Timer is now needed then 
      dTimerStart = Time(Now)                                   'Set the Start time to NOW
      hTimer.start                                              'Start the Timer
      bTimerOn = True                                           'Set bTimerOn to True 
    Endif
    Break                                                       'Get out of here
  End If
Next

RebuildForm                                                     'Go to the RebuilForm routine
CheckIfPuzzleCompleted                                          'Check to see if the puzzle has been solved

End

Public Sub CheckIfPuzzleCompleted()                             'Is the puzzle is complete
Dim byTest As Byte[] = [1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 99] 'byPos will equal this if it is completed
Dim siCount As Short                                            'Counter
Dim bCompleted As Boolean = True                                'Completed?
Dim sMessage As String                                          'String to store the display message

For siCount = 0 To 15                                           'Loop through the byPos
  If byPos[siCount] <> byTest[siCount] Then                     'If the position does not match the completed position then..
    bCompleted = False                                          'Set bCompleted to False
    Break                                                       'Get out of here
  Endif
Next

If bCompleted Then                                              'If the puzzle is completed then
  hTimer.Stop                                                   'Stop the timer
  Me.Title = siMoves & " Moves "                                'Set the Form Title to show the amount of moves taken
  sMessage = "Congratulations!!\n"                              'Build sMessage
  sMessage &= Str(siMoves) & " Moves\n"                         'Build sMessage
  sMessage &= "Time = " & Str(dTimerDiff)                       'Build sMessage
  Message(sMessage, "OK")                                       'Put up a congratulatory message
  Me.Close                                                      'Close the form
Endif

End

Public Sub RebuildForm()                                        'To clear the Form and rebuild with the Tiles in the new postion
Dim hButton As Button                                           'We need Buttons
Dim byCount, byTemp As Byte                                     'Various variables
Dim siFontH As Short

Me.Children.clear                                               'Clear the Form of all Objects

For Each byTemp In byPos                                        'For each 'Position'
  If byTemp = 99 Then                                           'If the Position's value is 99 then it's the space
    AddPanel                                                    'Go to the AddPanel routine
  Else                                                          'If the Position's value is NOT 99 then 
    hButton = New Button(Me) As "AllButtons"                    'Create a new Button
  With hButton                                                  'With the following properties
    .Text = Str(byPos[byCount])                                 'Text as stored in byPos
    .Tag = Str(byPos[byCount])                                  'Tag as stored in byPos
    .Height = (Me.Height - 10) / 4                              'Set the Button height
    .Width = (Me.Width - 10) / 4                                'Set the Button width
    .Font.Bold = True                                           'Set the Font to Bold
      End With
    If Me.Width > Me.Height Then                                'If Form Width is greater than Form Width then..
      siFontH = Me.Height                                       'siFontH = Form Height
    Else                                                        'Else..
      siFontH = Me.Width                                        'siFontH = Form Width
    End If
  hButton.Font.size = siFontH / 16                              'Set Font height
  Endif
  
  Inc byCount                                                   'Increase counter
Next

End

Public Sub Form_Resize()                                        'If the form is resized

RebuildForm                                                     'Rebuild the Form

End

Public Sub IsItSolvable() As Boolean                            'To check if the puzzle is solvable
Dim bSolvable, bBlankOnEven As Boolean                          'Triggers
Dim siCount0, siCount1, siInversion As Short                    'Counters

For siCount0 = 0 To byPos.Max                                   'Loop through the positions
  If byPos[siCount0] = 99 Then                                  'The blank
    If InStr("0,1,2,3,8,9,10,11,", Str(siCount0 & ",")) Then    'Is the blank on an even row (counting from the bottom) if so..
      bBlankOnEven = True                                       'bBlankOnEven = True
    End If
    Continue                                                    'Go to the end of the loop
  End If
  For siCount1 = siCount0 + 1 To byPos.Max                      'Loop through the positions 
    If byPos[siCount0] > byPos[siCount1] Then Inc siInversion   'Counts the inversions
  Next                                                          'See https://www.cs.bham.ac.uk/~mdr/teaching/modules04/java2/TilesSolvability.html
Next

If bBlankOnEven And Odd(siInversion) Then bSolvable = True      'Blank is on an even row (counting from the bottom) then the number of inversions in a solvable situation is odd
If Not bBlankOnEven And Even(siInversion) Then bSolvable = True 'Blank is on an odd row (counting from the bottom) then the number of inversions in a solvable situation is even

Return bSolvable                                                'Return the value

End

Public Sub Form_Close()

Settings.Write(Me, "Window")                                    'Store the window position and size

End

Click here for image of game in play

Go

package main

import (
	"fmt"
	"math/rand"
	"strings"
	"time"
)

func main() {
	rand.Seed(time.Now().UnixNano())
	p := newPuzzle()
	p.play()
}

type board [16]cell
type cell uint8
type move uint8

const (
	up move = iota
	down
	right
	left
)

func randMove() move { return move(rand.Intn(4)) }

var solvedBoard = board{1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 0}

func (b *board) String() string {
	var buf strings.Builder
	for i, c := range b {
		if c == 0 {
			buf.WriteString("  .")
		} else {
			_, _ = fmt.Fprintf(&buf, "%3d", c)
		}
		if i%4 == 3 {
			buf.WriteString("\n")
		}
	}
	return buf.String()
}

type puzzle struct {
	board board
	empty int // board[empty] == 0
	moves int
	quit  bool
}

func newPuzzle() *puzzle {
	p := &puzzle{
		board: solvedBoard,
		empty: 15,
	}
	// Could make this configurable, 10==easy, 50==normal, 100==hard
	p.shuffle(50)
	return p
}

func (p *puzzle) shuffle(moves int) {
	// As with other Rosetta solutions, we use some number
	// of random moves to "shuffle" the board.
	for i := 0; i < moves || p.board == solvedBoard; {
		if p.doMove(randMove()) {
			i++
		}
	}
}

func (p *puzzle) isValidMove(m move) (newIndex int, ok bool) {
	switch m {
	case up:
		return p.empty - 4, p.empty/4 > 0
	case down:
		return p.empty + 4, p.empty/4 < 3
	case right:
		return p.empty + 1, p.empty%4 < 3
	case left:
		return p.empty - 1, p.empty%4 > 0
	default:
		panic("not reached")
	}
}

func (p *puzzle) doMove(m move) bool {
	i := p.empty
	j, ok := p.isValidMove(m)
	if ok {
		p.board[i], p.board[j] = p.board[j], p.board[i]
		p.empty = j
		p.moves++
	}
	return ok
}

func (p *puzzle) play() {
	fmt.Printf("Starting board:")
	for p.board != solvedBoard && !p.quit {
		fmt.Printf("\n%v\n", &p.board)
		p.playOneMove()
	}
	if p.board == solvedBoard {
		fmt.Printf("You solved the puzzle in %d moves.\n", p.moves)
	}
}

func (p *puzzle) playOneMove() {
	for {
		fmt.Printf("Enter move #%d (U, D, L, R, or Q): ", p.moves+1)
		var s string
		if n, err := fmt.Scanln(&s); err != nil || n != 1 {
			continue
		}

		s = strings.TrimSpace(s)
		if s == "" {
			continue
		}

		var m move
		switch s[0] {
		case 'U', 'u':
			m = up
		case 'D', 'd':
			m = down
		case 'L', 'l':
			m = left
		case 'R', 'r':
			m = right
		case 'Q', 'q':
			fmt.Printf("Quiting after %d moves.\n", p.moves)
			p.quit = true
			return
		default:
			fmt.Println(`
Please enter "U", "D", "L", or "R" to move the empty cell
up, down, left, or right. You can also enter "Q" to quit.
Upper or lowercase is accepted and only the first non-blank
character is important (i.e. you may enter "up" if you like).
`)
			continue
		}

		if !p.doMove(m) {
			fmt.Println("That is not a valid move at the moment.")
			continue
		}

		return
	}
}

Harbour

#include "inkey.ch"
#include "Box.ch"


procedure Main()
    // console init
    SET SCOREBOARD OFF
    SetMode(30,80) 
    ret := 0

    // main loop
    yn := .F.  
    DO WHILE yn == .F.
        // draw console
        cls
        @ 0, 0 TO MaxRow(), MaxCol() DOUBLE
        SetColor("BG+/B,W/N")
        @ 0, 4 SAY "  Slidng puzzle game  "
        SetColor()

        // input size of grid
        tam := 0           
        @ MaxRow() - 2, 4 SAY "Size of grid: " GET tam PICTURE "9"
        READ 

        // Initialize numbers
        lista := ARRAY (tam * tam)
        FOR z := 1 TO tam * tam
            lista[z] := z
        NEXT
        lista1 := lista
        grid := ARRAY (tam,tam)

        // populate grid with numbers
        FOR i := 1 TO tam 
            FOR j := 1 TO tam 
                grid[i,j] := lista1[ (i-1) * tam + j] 
            NEXT 
        NEXT
        Mostra(@grid)
        InKey(0)

        // initialize the game
        n := 0
        t := 0
        lista := lista1     // lista for scrambling, lista1 preserve numbers in order
        DO WHILE .T.
            // scrambling numbers
            FOR i := 1 TO tam*tam
                n := Int ( ft_Rand1(tam * tam - 1) + 1 )
                t := lista[n]
                lista[n] := lista[i]
                lista[i] := t
            NEXT
            // have solution?
            possp := 0
            invct := 0  // change counter
            FOR i := 1 TO tam * tam -1
                IF lista[i] != tam*tam 
                    FOR j := i + 1 TO tam * tam 
                        IF lista[j] != tam*tam
                            IF lista[i] > lista[j]
                                invct++ 
                            ENDIF 
                        ENDIF
                    NEXT
                ELSE
                    possp := i
                ENDIF
            NEXT
            linv := If( ( (invct % 2) == 0 ), .T., .F.)
            lkin := If( ( (tam - Int( (possp -1) / tam )) % 2) == 0, .T., .F. )
            
            IF ( (tam % 2) != 0)    // if grid size is odd
                IF linv                 // if number of positions changes is even, solvable
                    EXIT
                ELSE 
                    LOOP                // if is odd, not solvable, scramble more
                ENDIF               // if grid size is even
            ELSE                    
                                        // If changes is even and space position is in odd line
                                        // or changes is odd and space position is in even line
                                        // (XOR condition) is solvable 
                IF (linv .AND. !lkin) .OR. (!linv .AND. lkin) // XOR !!! 
                    EXIT
                ElSE                    // else scramble more
                    LOOP    
                ENDIF
            ENDIF

        ENDDO

        // populate the grid with scrambled numbers
        FOR i := 1 TO tam 
            FOR j := 1 TO tam 
                grid[i,j] := lista[ (i-1) * tam + j] 
            NEXT 
        NEXT
        ret := Mostra(@grid)

    // play
        key := 0
        DO WHILE LastKey() != K_ESC
            key := 0 
            // find the space coords
            xe := 0
            ye := 0
            lv := tam*tam
            FOR i := 1 TO tam 
                FOR j := 1 TO tam 
                    IF grid[i,j] == lv 
                        xe :=i
                        ye :=j
                    ENDIF
                NEXT
            NEXT
            // the direction keys
            key := inkey(0)
            DO CASE 
                CASE key == K_UP
                    IF xe > 1
                        grid[xe,ye] := grid[xe-1,ye]
                        grid[xe-1,ye] := lv
                    ENDIF
                    ret := Mostra(@grid)            
                CASE key == K_DOWN
                    IF xe < tam
                        grid[xe,ye] := grid[xe+1,ye]
                        grid[xe+1,ye] := lv
                    ENDIF
                    ret := Mostra(@grid)   
                CASE key == K_LEFT
                    IF ye > 1
                        grid[xe,ye] := grid[xe,ye-1]
                        grid[xe,ye-1] := lv
                    ENDIF
                    ret := Mostra(@grid)   
                CASE key == K_RIGHT
                    IF ye < tam
                        grid[xe,ye] := grid[xe,ye+1]
                        grid[xe,ye+1] := lv
                    ENDIF
                    ret := Mostra(@grid)   
            ENDCASE  
            IF ret == tam*tam-1                             // ret is qtty numbers in position
                @ MaxRow() - 3, 4 SAY "Fim de jogo!"        // if ret == (size*size) -1
                key := K_ESC                                // all numbers in position
                EXIT                                        // game solved
            ENDIF
        ENDDO
        @ MaxRow() - 2, 4 SAY "Deseja sair? (yn): " GET yn PICTURE "Y"
        READ 
        @ MaxRow() - 3, 4 SAY "              "
    ENDDO
return NIL

FUNCTION Mostra(grid)
    // Show the gris
    fim := 0                                                    // how many numbers in position?
    SetColor("BG+/B,W/N") 
    @ 5,10 , 5 + tam * 2, 9 + tam * 4 BOX B_SINGLE + Space(1)
    i := 0
    FOR y := 1 TO tam
        FOR x := 1 TO tam
            IF grid[x,y] == tam * tam                           // show space
                SetColor(" B/GR+, W/N")
                @ x*2 + 4, i + 11 SAY "  " 
                SetColor("BG+/B,W/N")
            ELSE 
                IF ( (x-1) * tam + y ) == grid[x,y]             // show number in position
                    SetColor("W/G,W/N")
                    @ x*2 + 4, i + 11 SAY grid[x,y] PICTURE "99" 
                    fim++
                ELSE                                            // show number out position
                    SetColor("BG+/B,W/N")
                    @ x*2 + 4, i + 11 SAY grid[x,y] PICTURE "99"
                ENDIF
            ENDIF
        NEXT
        i = i + 4
    NEXT
    SetColor(" W/N, BG+/B")
RETURN fim

Haskell

import Data.Array
import System.Random

type Puzzle = Array (Int, Int) Int

main :: IO ()
main = do
    putStrLn "Please enter the difficulty level: 0, 1 or 2"
    userInput <- getLine
    let diffLevel = read userInput
    if userInput == "" || any (\c -> c < '0' || c > '9') userInput || diffLevel > 2 || diffLevel < 0
        then putStrLn "That is not a valid difficulty level." >> main
        else shufflePuzzle ([10, 50, 100] !! diffLevel) solvedPuzzle >>= gameLoop

gameLoop :: Puzzle -> IO ()
gameLoop puzzle
    | puzzle == solvedPuzzle = putStrLn "You solved the puzzle!" >> printPuzzle puzzle
    | otherwise = do
    printPuzzle puzzle
    putStrLn "Please enter number to move"
    userInput <- getLine
    if any (\c -> c < '0' || c > '9') userInput
        then putStrLn "That is not a valid number." >> gameLoop puzzle
        else let move = read userInput in
            if move `notElem` validMoves puzzle
                then putStrLn "This move is not available." >> gameLoop puzzle
                else gameLoop (applyMove move puzzle)

validMoves :: Puzzle -> [Int]
validMoves puzzle = [puzzle ! (row', column') |
                     row' <- [rowEmpty-1..rowEmpty+1], column' <- [columnEmpty-1..columnEmpty+1],
                     row' < 4, row' >= 0, column' < 4, column' >= 0,
                     (row' == rowEmpty) /= (column' == columnEmpty)]
    where (rowEmpty, columnEmpty) = findIndexOfNumber 16 puzzle

applyMove :: Int -> Puzzle -> Puzzle
applyMove numberToMove puzzle = puzzle // [(indexToMove, 16), (emptyIndex, numberToMove)]
    where indexToMove = findIndexOfNumber numberToMove puzzle
          emptyIndex = findIndexOfNumber 16 puzzle

findIndexOfNumber :: Int -> Puzzle -> (Int, Int)
findIndexOfNumber number puzzle = case filter (\idx -> number == puzzle ! idx)
                                              (indices puzzle) of
                                      [idx] -> idx
                                      _ -> error "BUG: number not in puzzle"

printPuzzle :: Puzzle -> IO ()
printPuzzle puzzle = do
    putStrLn "+--+--+--+--+"
    putStrLn $ "|" ++ formatCell (0, 0) ++ "|" ++ formatCell (0, 1) ++ "|" ++ formatCell (0, 2) ++ "|" ++ formatCell (0, 3) ++ "|"
    putStrLn "+--+--+--+--+"
    putStrLn $ "|" ++ formatCell (1, 0) ++ "|" ++ formatCell (1, 1) ++ "|" ++ formatCell (1, 2) ++ "|" ++ formatCell (1, 3) ++ "|"
    putStrLn "+--+--+--+--+"
    putStrLn $ "|" ++ formatCell (2, 0) ++ "|" ++ formatCell (2, 1) ++ "|" ++ formatCell (2, 2) ++ "|" ++ formatCell (2, 3) ++ "|"
    putStrLn "+--+--+--+--+"
    putStrLn $ "|" ++ formatCell (3, 0) ++ "|" ++ formatCell (3, 1) ++ "|" ++ formatCell (3, 2) ++ "|" ++ formatCell (3, 3) ++ "|"
    putStrLn "+--+--+--+--+"
    where formatCell idx
              | i == 16 = "  "
              | i > 9 = show i
              | otherwise = " " ++ show i
              where i = puzzle ! idx

solvedPuzzle :: Puzzle
solvedPuzzle = listArray ((0, 0), (3, 3)) [1..16]

shufflePuzzle :: Int -> Puzzle -> IO Puzzle
shufflePuzzle 0 puzzle = return puzzle
shufflePuzzle numOfShuffels puzzle = do
    let moves = validMoves puzzle
    randomIndex <- randomRIO (0, length moves - 1)
    let move = moves !! randomIndex
    shufflePuzzle (numOfShuffels - 1) (applyMove move puzzle)

Output:

Please enter the difficulty level: 0, 1 or 2
0
+--+--+--+--+
| 1| 6| 2| 4|
+--+--+--+--+
| 5|10| 3| 8|
+--+--+--+--+
| 9|14| 7|11|
+--+--+--+--+
|13|  |15|12|
+--+--+--+--+
Please enter number to move
14
+--+--+--+--+
| 1| 6| 2| 4|
+--+--+--+--+
| 5|10| 3| 8|
+--+--+--+--+
| 9|  | 7|11|
+--+--+--+--+
|13|14|15|12|
+--+--+--+--+
Please enter number to move

J

Implementation:

require'general/misc/prompt'

genboard=:3 :0
  b=. ?~16
  if. 0<C.!.2 b do.
    b=. (<0 _1)C. b
  end.
  a: (b i.0)} <"0 b
)

done=: (<"0]1+i.15),a:

shift=: |.!._"0 2
taxi=: |:,/"2(_1 1 shift i.4 4),_1 1 shift"0 1/ i.4 4

showboard=:3 :0
  echo 'current board:'
  echo 4 4$y
)

help=:0 :0

  Slide a number block into the empty space
  until you get:
┌──┬──┬──┬──┐
│1 │2 │3 │4 │
├──┼──┼──┼──┤
│5 │6 │7 │8 │
├──┼──┼──┼──┤
│9 │10│11│12│
├──┼──┼──┼──┤
│13│14│15│  │
└──┴──┴──┴──┘
  Or type 'q' to quit.
)

getmove=:3 :0
  showboard y
  blank=. y i. a:
  options=. /:~ ;y {~ _ -.~ blank { taxi
  whilst. -. n e. options do.
    echo 'Valid moves: ',":options
    t=. prompt 'move which number? '
    if. 'q' e. t do.
      echo 'giving up'
      throw.
    elseif. 'h' e. t do.
      echo help
      showboard y
    end.
    n=. {._".t
  end.
  (<blank,y i.<n) C. y
)

game=: 3 :0
  echo '15 puzzle'
  echo 'h for help, q to quit'
  board=. genboard''
  whilst. -. done-:board do.
    board=. getmove board
  end.
  showboard board
  echo 'You win.'
)

Most of this is user interface code. We initially shuffle the numbers randomly, then check their parity and swap the first and last squares if needed. Then, for each move, we allow the user to pick one of the taxicab neighbors of the empty square.

A full game would be too big to be worth showing here, so for the purpose of giving a glimpse of what this looks like in action we replace the random number generator with a constant:

   game''
15 puzzle
h for help, q to quit
current board:
┌──┬──┬──┬──┐
1 2 3 4 
├──┼──┼──┼──┤
5 6 7 8 
├──┼──┼──┼──┤
9 10  11
├──┼──┼──┼──┤
13141512
└──┴──┴──┴──┘
Valid moves: 7 10 11 15
move which number? 11
current board:
┌──┬──┬──┬──┐
1 2 3 4 
├──┼──┼──┼──┤
5 6 7 8 
├──┼──┼──┼──┤
9 1011  
├──┼──┼──┼──┤
13141512
└──┴──┴──┴──┘
Valid moves: 8 11 12
move which number? 12
current board:
┌──┬──┬──┬──┐
1 2 3 4 
├──┼──┼──┼──┤
5 6 7 8 
├──┼──┼──┼──┤
9 101112
├──┼──┼──┼──┤
131415  
└──┴──┴──┴──┘
You win.

Java

Works with: Java version 8
package fifteenpuzzle;

import java.awt.*;
import java.awt.event.*;
import java.util.Random;
import javax.swing.*;

class FifteenPuzzle extends JPanel {

    private final int side = 4;
    private final int numTiles = side * side - 1;

    private final Random rand = new Random();
    private final int[] tiles = new int[numTiles + 1];
    private final int tileSize;
    private int blankPos;
    private final int margin;
    private final int gridSize;
    private boolean gameOver;

    private FifteenPuzzle() {
        final int dim = 640;

        margin = 80;
        tileSize = (dim - 2 * margin) / side;
        gridSize = tileSize * side;

        setPreferredSize(new Dimension(dim, dim + margin));
        setBackground(Color.WHITE);
        setForeground(new Color(0x6495ED)); // cornflowerblue
        setFont(new Font("SansSerif", Font.BOLD, 60));

        gameOver = true;

        addMouseListener(new MouseAdapter() {
            @Override
            public void mousePressed(MouseEvent e) {
                if (gameOver) {
                    newGame();

                } else {

                    int ex = e.getX() - margin;
                    int ey = e.getY() - margin;

                    if (ex < 0 || ex > gridSize || ey < 0 || ey > gridSize) {
                        return;
                    }

                    int c1 = ex / tileSize;
                    int r1 = ey / tileSize;
                    int c2 = blankPos % side;
                    int r2 = blankPos / side;

                    int clickPos = r1 * side + c1;

                    int dir = 0;
                    if (c1 == c2 && Math.abs(r1 - r2) > 0) {
                        dir = (r1 - r2) > 0 ? 4 : -4;
                        
                    } else if (r1 == r2 && Math.abs(c1 - c2) > 0) {
                        dir = (c1 - c2) > 0 ? 1 : -1;
                    }

                    if (dir != 0) {
                        do {
                            int newBlankPos = blankPos + dir;
                            tiles[blankPos] = tiles[newBlankPos];
                            blankPos = newBlankPos;
                        } while (blankPos != clickPos);
                        tiles[blankPos] = 0;
                    }
                    
                    gameOver = isSolved();
                }
                repaint();
            }
        });

        newGame();
    }

    private void newGame() {
        do {
            reset();
            shuffle();
        } while (!isSolvable());
        gameOver = false;
    }

    private void reset() {
        for (int i = 0; i < tiles.length; i++) {
            tiles[i] = (i + 1) % tiles.length;
        }
        blankPos = tiles.length - 1;
    }

    private void shuffle() {
        // don't include the blank space in the shuffle, leave it
        // in the home position
        int n = numTiles;
        while (n > 1) {
            int r = rand.nextInt(n--);
            int tmp = tiles[r];
            tiles[r] = tiles[n];
            tiles[n] = tmp;
        }
    }

    /*  Only half the permutations of the puzzle are solvable.

        Whenever a tile is preceded by a tile with higher value it counts
        as an inversion. In our case, with the blank space in the home
        position, the number of inversions must be even for the puzzle
        to be solvable.

        See also:
        www.cs.bham.ac.uk/~mdr/teaching/modules04/java2/TilesSolvability.html
     */
    private boolean isSolvable() {
        int countInversions = 0;
        for (int i = 0; i < numTiles; i++) {
            for (int j = 0; j < i; j++) {
                if (tiles[j] > tiles[i]) {
                    countInversions++;
                }
            }
        }
        return countInversions % 2 == 0;
    }

    private boolean isSolved() {
        if (tiles[tiles.length - 1] != 0) {
            return false;
        }
        for (int i = numTiles - 1; i >= 0; i--) {
            if (tiles[i] != i + 1) {
                return false;
            }
        }
        return true;
    }

    private void drawGrid(Graphics2D g) {
        for (int i = 0; i < tiles.length; i++) {
            int r = i / side;
            int c = i % side;
            int x = margin + c * tileSize;
            int y = margin + r * tileSize;

            if (tiles[i] == 0) {
                if (gameOver) {
                    g.setColor(Color.GREEN);
                    drawCenteredString(g, "\u2713", x, y);
                }
                continue;
            }

            g.setColor(getForeground());
            g.fillRoundRect(x, y, tileSize, tileSize, 25, 25);
            g.setColor(Color.blue.darker());
            g.drawRoundRect(x, y, tileSize, tileSize, 25, 25);
            g.setColor(Color.WHITE);

            drawCenteredString(g, String.valueOf(tiles[i]), x, y);
        }
    }

    private void drawStartMessage(Graphics2D g) {
        if (gameOver) {
            g.setFont(getFont().deriveFont(Font.BOLD, 18));
            g.setColor(getForeground());
            String s = "click to start a new game";
            int x = (getWidth() - g.getFontMetrics().stringWidth(s)) / 2;
            int y = getHeight() - margin;
            g.drawString(s, x, y);
        }
    }

    private void drawCenteredString(Graphics2D g, String s, int