-----------------------------------------------------------------------------
-- |
-- Module      :  HCube.Template
-- Copyright   :  (c) Todd Wegner 2012
-- License     :  BSD-style (see the LICENSE file)
-- 
-- Maintainer  :  echbar137@yahoo.co.in
-- Stability   :  provisional
-- Portability :  portable
-- 
-- Console visualization of virtual cube.
-----------------------------------------------------------------------------
{-# LANGUAGE Trustworthy #-}

module HCube.Template (render) where

import Data.Text (Text, pack, unpack, replace, splitOn)
import Data.List (unlines)
import HCube.Data
import HCube.Lib (Rubik(..), Cube(..), getFaceColor, getCubeFromPos, getCubeFromPos)
import HCube.Utility ( (~|) )
import HCube.OrientGroup (eid)

render			:: Rubik -> IO Rubik
render rk		= f ( view rk) 
			>>= g renderInternal where
    f LeftV		= g renderLeft3D rk
    f RightV		= g renderRight3D rk
    g 			:: (Rubik -> String) -> Rubik -> IO Rubik
    g fu rk		= (putStrLn . fu) ~| rk

renderInternal		:: Rubik -> String
renderInternal rk	= f $ n rk where
    f 2			= projectD dTemp2x2 dProj2x2 rk
    f 3			= projectD dTemp3x3 dProj3x3 rk
    f 4			= projectD dTemp4x4 dProj4x4 rk
    f 5			= projectD dTemp5x5 dProj5x5 rk
    f _			= "size not supported"

renderLeft3D		:: Rubik -> String
renderLeft3D rk		= f $ n rk where
    f 2			= project3D lTemp2x2 lProj2x2 rk
    f 3			= project3D lTemp3x3 lProj3x3 rk
    f 4			= project3D lTemp4x4 lProj4x4 rk
    f 5			= project3D lTemp5x5 lProj5x5 rk
    f _			= "size not supported"

renderRight3D		:: Rubik -> String
renderRight3D rk	= f $ n rk where
    f 2			= project3D rTemp2x2 rProj2x2 rk
    f 3			= project3D rTemp3x3 rProj3x3 rk
    f 4			= project3D rTemp4x4 rProj4x4 rk
    f 5			= project3D rTemp5x5 rProj5x5 rk
    f _			= "size not supported"

project3D		:: Format -> Projection -> Rubik -> String
project3D fm pj rk	= f (map (getFaceColor rk) pj) fm where
    f vars		= g . map unpack . splitOn (pack "%") . replace (pack "b") (pack "\\") . pack where
        g fm		= join fm vars

join				:: [String] -> [String] -> String
join				= f [] where
    f acc (hd1:tl1) (hd2:tl2)	= f (acc ++ hd1 ++ hd2) tl1 tl2
    f acc (hd1:tl1) []		= f (acc ++ hd1) tl1 []
    f acc [] (hd2:tl2)		= f (acc ++ hd2) [] tl2
    f acc [] []			= acc

projectD		:: Format -> [ViewAssociation] -> Rubik -> String
projectD fm va rk	= f (viewToString rk va) fm where
    f vars		= g . map unpack . splitOn (pack "%") . pack where
        g fm		= join fm vars

viewToString			:: Rubik -> [ViewAssociation] -> [String]
viewToString rk			= map f where
    f (Sur pr)			= getFaceColor rk pr
    f (Ide id)			= g . cid $ getCubeFromPos rk id 
    f (Ori or)			= [eid . ori $ getCubeFromPos rk or]
    g nm			= pad $ show nm


cbLayout		:: Side -> [Int] -> [ViewAssociation]
cbLayout sd		= map f where
    f nm		= Sur (nm,sd)	

cbInternal		:: Int -> Int -> [ViewAssociation]
cbInternal bg ed	= (map f [bg .. ed]) ++ (map g [bg .. ed]) where
    f nm		= Ori nm
    g nm		= Ide nm 


lProj2x2	:: Projection
lProj2x2	= [ (1,UpS),		(2,UpS),		(2,LeftS),
		    (3,UpS),		(4,UpS),		(4,LeftS),
		    (6,LeftS),		(3,FrontS),		(4,FrontS),
		    (8,LeftS),		(7,FrontS),		(8,FrontS) ]  

rProj2x2	:: Projection
rProj2x2	= [ (1,UpS),		(2,UpS),		(1,RightS),
		    (3,UpS),		(4,UpS),		(5,RightS),
		    (3,RightS),		(3,FrontS),		(4,FrontS),
		    (7,RightS),		(7,FrontS),		(8,FrontS) ]

lProj3x3	:: Projection
lProj3x3	= [ (1,UpS), 		(2,UpS), 		(3,UpS),
		    (3,LeftS),		(4,UpS), 		(5,UpS),
		    (6,UpS), 		(6,LeftS),		(12,LeftS),
	  	    (7,UpS), 		(8,UpS), 		(9,UpS),
		    (9,LeftS),	 	(15,LeftS), 		(21,LeftS),
		    (7,FrontS), 	(8,FrontS), 		(9,FrontS),
		    (18,LeftS),		(24,LeftS),		(16,FrontS),
		    (17,FrontS), 	(18,FrontS),		(27,LeftS),
		    (25,FrontS), 	(26,FrontS), 		(27,FrontS) ] 

rProj3x3	:: Projection
rProj3x3	= [ (1,UpS),		(2,UpS),		(3,UpS),
		    (1,RightS),		(4,UpS),		(5,UpS),
		    (6,UpS),		(10,RightS),		(4,RightS),
		    (7,UpS),		(8,UpS),		(9,UpS),
		    (19,RightS),	(13,RightS),		(7,RightS),
		    (7,FrontS),		(8,FrontS),		(9,FrontS),
		    (22,RightS),	(16,RightS),		(16,FrontS),
		    (17,FrontS),	(18,FrontS),		(25,RightS),
		    (25,FrontS),	(26,FrontS),		(27,FrontS) ]

lProj4x4	:: Projection
lProj4x4	= [ (1,UpS), (2,UpS), (3,UpS), (4,UpS), (4,LeftS),
		    (5,UpS), (6,UpS), (7,UpS), (8,UpS), (8,LeftS),
		    (9,UpS), (10,UpS), (11,UpS), (12,UpS), (12,LeftS), (24,LeftS), (36,LeftS),
		    (13,UpS), (14,UpS), (15,UpS), (16,UpS), (16,LeftS), (28,LeftS), (40,LeftS), (52,LeftS),
		    (13,FrontS), (14,FrontS), (15,FrontS),(16,FrontS), (32,LeftS), (44,LeftS), (56,LeftS),
                    (29,FrontS), (30,FrontS), (31,FrontS), (32,FrontS), (48,LeftS), (60,LeftS),
                    (45,FrontS), (46,FrontS), (47,FrontS), (48,FrontS), (64,LeftS),
		    (61,FrontS), (62,FrontS), (63,FrontS), (64,FrontS) ]

rProj4x4	:: Projection
rProj4x4	= [ (1,UpS), (2,UpS), (3,UpS), (4,UpS), (1,RightS),
		    (5,UpS), (6,UpS), (7,UpS), (8,UpS), (17,RightS), (5,RightS),
		    (9,UpS), (10,UpS), (11,UpS), (12,UpS), (33,RightS), (21,RightS), (9,RightS),
		    (13,UpS), (14,UpS), (15,UpS), (16,UpS), (49,RightS), (37,RightS), (25,RightS), (13,RightS),
                    (13,FrontS), (14,FrontS), (15,FrontS), (16,FrontS), (53,RightS), (41,RightS), (29,RightS),
                    (29,FrontS), (30,FrontS), (31,FrontS), (32,FrontS), (57,RightS), (45,RightS),
                    (45,FrontS), (46,FrontS), (47,FrontS), (48,FrontS), (61,RightS),
		    (61,FrontS), (62,FrontS), (63,FrontS), (64,FrontS) ]		    

lProj5x5	:: Projection
lProj5x5	= [ (1,UpS), (2,UpS), (3,UpS), (4,UpS), (5,UpS), (5,LeftS),
		    (6,UpS), (7,UpS), (8,UpS), (9,UpS), (10,UpS), (10,LeftS), (30,LeftS),
		    (11,UpS), (12,UpS), (13,UpS), (14,UpS), (15,UpS), (15,LeftS), (35,LeftS), (55,LeftS),
		    (16,UpS), (17,UpS), (18,UpS), (19,UpS), (20,UpS), (20,LeftS), (40,LeftS), (60,LeftS), (80,LeftS),
		    (21,UpS), (22,UpS), (23,UpS), (24,UpS), (25,UpS), (25,LeftS), (45,LeftS), (65,LeftS), (85,LeftS), (105,LeftS),
		    (21,FrontS), (22,FrontS), (23,FrontS), (24,FrontS), (25,FrontS), (50,LeftS), (70,LeftS), (90,LeftS), (110,LeftS),
		    (46,FrontS), (47,FrontS), (48,FrontS), (49,FrontS), (50,FrontS), (75,LeftS), (95,LeftS), (115,LeftS),
		    (71,FrontS), (72,FrontS), (73,FrontS), (74,FrontS), (75,FrontS), (100,LeftS), (120,LeftS),
		    (96,FrontS), (97,FrontS), (98,FrontS), (99,FrontS), (100,FrontS), (125,LeftS) ] 

rProj5x5	:: Projection
rProj5x5	= [ (1,UpS), (2,UpS), (3,UpS), (4,UpS), (5,UpS), (1,RightS),
		    (6,UpS), (7,UpS), (8,UpS), (9,UpS), (10,UpS), (26,RightS), (6,RightS),
		    (11,UpS), (12,UpS), (13,UpS), (14,UpS), (15,UpS), (51,RightS), (31,RightS), (11,RightS),
                    (16,UpS), (17,UpS), (18,UpS), (19,UpS), (20,UpS), (76,RightS), (56,RightS), (36,RightS), (16,RightS),
		    (21,UpS), (22,UpS), (23,UpS), (24,UpS), (25,UpS), (101,RightS), (81,RightS), (61,RightS), (41,RightS), (21,RightS),
		    (21,FrontS), (22,FrontS), (23,FrontS), (24,FrontS), (25,FrontS), (106,RightS), (86,RightS), (66,RightS), (46,RightS), (46,FrontS), (47,FrontS), (48,FrontS), (49,FrontS), (50,FrontS), (111,RightS), (91,RightS), (71,RightS),
		    (71,FrontS), (72,FrontS), (73,FrontS), (74,FrontS), (75,FrontS), (116,RightS), (96,RightS),
		    (96,FrontS), (97,FrontS), (98,FrontS), (99,FrontS), (100,FrontS), (121,RightS),
		    (121,FrontS), (121,FrontS), (122,FrontS), (123,FrontS), (124,FrontS), (125,FrontS) ]

dProj2x2	:: [ViewAssociation]
dProj2x2	= concat [
 cbLayout BackS [5,6,1,2],
 cbLayout RightS [5,1], cbLayout UpS [1,2], cbLayout LeftS [2,6], cbInternal 1 2,
 cbLayout RightS [7,3], cbLayout UpS [3,4], cbLayout LeftS [4,8], cbInternal 3 4,
 cbLayout FrontS [3,4,7,8], cbInternal 5 6,
 cbLayout RightS [3,7], cbLayout DownS [7,8], cbLayout LeftS [8,4], cbInternal 7 8,
 cbLayout RightS [1,5], cbLayout DownS [5,6], cbLayout LeftS [6,2], cbLayout BackS [5,6,1,2] ]
	
dProj3x3	:: [ViewAssociation]
dProj3x3	= concat [
 cbLayout BackS [19,20,21], cbLayout BackS [10,11,12],
 cbLayout BackS [1,2,3], cbInternal 1 3,
 cbLayout RightS [19,10,1], cbLayout UpS [1,2,3], cbLayout LeftS [3,12,21], cbInternal 4 6,
 cbLayout RightS [22,13,4], cbLayout UpS [4,5,6], 
 cbLayout LeftS [6,15,24], cbInternal 7 9,
 cbLayout RightS [25,16,7], cbLayout UpS [7,8,9], cbLayout LeftS [9,18,27], 
 cbLayout FrontS [7,8,9], cbInternal 10 12,
 cbLayout FrontS [16,17,18], cbInternal 13 15,
 cbLayout FrontS [25,26,27], cbInternal 16 18,
 cbLayout RightS [7,16,25], cbLayout DownS [25,26,27], cbLayout LeftS [27,18,9],
 cbLayout RightS [4,13,22], cbLayout DownS [22,23,24], cbLayout LeftS [24,15,6], cbInternal 19 21,
 cbLayout RightS [1,10,19], cbLayout DownS [19,20,21],
 cbLayout LeftS [21,12,3], cbInternal 22 24,
 cbLayout BackS [19,20,21], cbInternal 25 27,
 cbLayout BackS [10,11,12], cbLayout BackS [1,2,3]]

dProj4x4	:: [ViewAssociation]
dProj4x4	= concat [
 cbLayout BackS [49,50,51,52], 
 cbLayout BackS [33,34,35,36], cbInternal 1 4,
 cbLayout BackS [17,18,19,20], cbInternal 5 8,
 cbLayout BackS [1,2,3,4], cbInternal 9 12,

 cbLayout RightS [49,33,17,1], cbLayout UpS [1,2,3,4], cbLayout LeftS [4,20,36,52], cbInternal 13 16,
 cbLayout RightS [53,37,21,5], cbLayout UpS [5,6,7,8], cbLayout LeftS [8,24,40,56],
 cbLayout RightS [57,41,25,9], cbLayout UpS [9,10,11,12], cbLayout LeftS [12,28,44,60], cbInternal 17 20,
 cbLayout RightS [61,45,29,13], cbLayout UpS [13,14,15,16], cbLayout LeftS [16,32,48,64], cbInternal 21 24,

 cbLayout FrontS [13,14,15,16], cbInternal 25 28,
 cbLayout FrontS [29,30,31,32], cbInternal 29 32,
 cbLayout FrontS [45,46,47,48], 
 cbLayout FrontS [61,62,63,64], cbInternal 33 36,

 cbLayout RightS [1,17,33,49], cbLayout DownS [61,62,63,64], cbLayout LeftS [52,36,20,4], cbInternal 37 40,
 cbLayout RightS [5,21,37,53], cbLayout DownS [57,58,59,60], cbLayout LeftS [56,40,24,8], cbInternal 41 44,
 cbLayout RightS [9,25,41,57], cbLayout DownS [53,54,55,56], cbLayout LeftS [60,44,28,12], cbInternal 45 48,
 cbLayout RightS [13,29,45,61], cbLayout DownS [49,50,51,52], cbLayout LeftS [64,48,32,16],
 
 cbLayout BackS [49,50,51,52], cbInternal 49 52,
 cbLayout BackS [33,34,35,36], cbInternal 53 56,
 cbLayout BackS [17,18,19,20], cbInternal 57 60,
 cbLayout BackS [1,2,3,4], cbInternal 61 64] 

dProj5x5	:: [ViewAssociation]
dProj5x5	= concat [
 cbInternal 1 5,
 cbInternal 6 10,
 cbLayout BackS [101,102,103,104,105], cbInternal 11 15,
 cbLayout BackS [76,77,78,79,80], cbInternal 16 20, 
 cbLayout BackS [51,52,53,54,55], cbInternal 21 25,
 cbLayout BackS [26,27,28,29,30],
 cbLayout BackS [1,2,3,4,5], cbInternal 26 30,

 cbLayout RightS [101,76,51,26,1], cbLayout UpS [1,2,3,4,5], cbLayout LeftS [5,30,55,80,105], cbInternal 31 35,
 cbLayout RightS [106,81,56,31,6], cbLayout UpS [6,7,8,9,10], cbLayout LeftS [10,35,60,85,110], cbInternal 36 40,
 cbLayout RightS [111,86,61,36,11], cbLayout UpS [11,12,13,14,15], cbLayout LeftS [15,40,65,90,115], cbInternal 41 45,
 cbLayout RightS [116,91,66,41,16], cbLayout UpS [16,17,18,19,20], cbLayout LeftS [20,45,70,95,120], cbInternal 46 50,
 cbLayout LeftS [121,96,71,46,21], cbLayout UpS [21,22,23,24,25], cbLayout LeftS [25,50,75,100,125],

 cbLayout FrontS [21,22,23,24,25], cbInternal 51 55,
 cbLayout FrontS [46,47,48,49,50], cbInternal 56 60,
 cbLayout FrontS [71,72,73,74,75], cbInternal 61 65,
 cbLayout FrontS [96,97,98,99,100], cbInternal 66 70,
 cbLayout FrontS [121,122,123,124,125], cbInternal 71 75,

 cbLayout RightS [121,96,71,46,21], cbLayout DownS [121,122,123,124,125], cbLayout LeftS [125,100,75,50,25],
 cbLayout RightS [116,91,66,41,16], cbLayout DownS [116,117,118,119,120], cbLayout LeftS [120,95,70,45,20], cbInternal 76 80,
 cbLayout RightS [111,86,61,36,11], cbLayout DownS [111,112,113,114,115], cbLayout LeftS [115,90,65,40,15], cbInternal 81 85,
 cbLayout RightS [106,81,56,31,6], cbLayout DownS [106,107,108,109,110], cbLayout LeftS [110,85,60,35,10], cbInternal 86 90,
 cbLayout RightS [101,76,51,26,1], cbLayout DownS [101,102,103,104,105], cbLayout LeftS [105,80,55,30,5], cbInternal 91 95,

 cbLayout BackS [101,102,103,104,105], cbInternal 96 100,
 cbLayout BackS [76,77,78,79,80],
 cbLayout BackS [51,52,53,54,55], cbInternal 101 105,
 cbLayout BackS [26,27,28,29,30], cbInternal 106 110,
 cbLayout BackS [1,2,3,4,5], cbInternal 111 115,
 cbInternal 116 120,
 cbInternal 121 125]
 
lTemp2x2	:: String
lTemp2x2	= unlines [
	"     _____  ______",
	"   /  %   /  %   / b",
	"  /______/______/ % b",
	" /  %   /   %  / b  /b",
	"/______/______/ % b/ %b/",
	"b   %  b    % b   /b  /",
	" b______b _____b / %b/",
	"  b  %   b   %  b   /",
	"   b______b______b /"]

rTemp2x2	= unlines [
	"    ______ ______ ",
	"   /b  %   b  %   b",
	"  /% b______b______b",
	" /b  /b  %   b  %   b",
	"/% b/% b______b______b",
	"b  /b  /  %   /  %   /",    
	" b/% b/______/______/",
	"  b  /   %  /   %  /",
	"   b/______/______/"]

	
lTemp3x3	:: String
lTemp3x3	= unlines [
	"       _____  ______ _____",
	"     / %    / %    / %    / b",
	"    /_____ /_____ /______/ % b",
	"   /  %   /  %   /  %   / b  /b",
	"  /______/______/______/ % b/ %b",
	" /  %   /   %  /   %  / b  /b  /b",
	"/______/______/______/ % b/ %b/ %b",
	"b   %  b    % b    % b   /b  /b  /",
	" b______b _____b______b / %b/ %b/",
	"  b  %   b   %  b   %  b   /b  /",
	"   b______b______b______b / %b/",
	"    b  %   b  %   b  %   b   /",
	"     b______b______b______b /"]

rTemp3x3	:: String
rTemp3x3	= unlines [
	"         ______ ______ ______",
	"        /b   %  b  %   b   %  b",
	"       /% b______b______b______b",
	"      /b  /b  %   b  %   b  %   b",
	"     /% b/% b______b______b______b",
	"    /b  /b  /b  %   b  %   b  %   b",
	"   /% b/% b/% b______b______b______b",
	"   b  /b  /b  /  %   /  %   /  %   /",    
	"    b/% b/% b/______/______/______/",
	"     b  /b  /   %  /   %  /   %  /",
	"      b/% b/______/______/______/",
	"       b  /    % /    % /    % /",
	"        b/______/______/______/"]

lTemp4x4	:: String
lTemp4x4	= unlines [
	"        ___________________________",
	"       / %    / %    / %    / %    / b",
	"      /_____ /______/______/______/ % b",
	"     / %    / %    / %    / %    / b  /b",
	"    /_____ /_____ /_____ /______/ % b/ %b",
	"   /  %   /  %   /  %   /  %   / b  /b  /b",
	"  /______/______/______/______/ % b/ %b/ %b",
	" /  %   /   %  /   %  /   %  / b  /b  /b  /b",
	"/______/______/______/______/ % b/ %b/ %b/ %b",
	"b   %  b    % b    % b   %  b   /b  /b  /b  /",
	" b______b _____b______b______b / %b/ %b/ %b/",
	"  b  %   b   %  b   %  b   %  b   /b  /b  /",
	"   b______b______b______b______b / %b/ %b/",
	"    b  %   b  %   b  %   b  %   b   /b  /",
	"     b______b______b______b______b / %b/",
	"      b  %   b  %   b  %   b  %   b   /",
	"       b______b______b______b______b /"]

rTemp4x4	:: String
rTemp4x4	= unlines [
	"         ___________________________",
	"       /b  %   b   %  b    % b    % b",
	"      /% b______b______b______b______b",
	"     /b  /b   %  b  %   b   %  b   %  b",
	"    /% b/% b______b______b______b______b",
	"   /b  /b  /b  %   b  %   b  %   b   %  b",
	"  /% b/% b/% b______b______b______b______b",
	" /b  /b  /b  /b  %   b  %   b  %   b   %  b",
	"/% b/% b/% b/% b______b______b______b______b",
	"b  /b  /b  /b  /  %   /  %   /  %   /  %   /",    
	" b/% b/% b/% b/______/______/______/______/",
	"  b  /b  /b  /   %  /   %  /   %  /  %   /",
	"   b/% b/% b/______/______/______/______/",
	"    b  /b  /   %  /   %  /  %   /  %   /",
	"     b/% b/______/______/______/______/",
	"      b  /   %  /   %  /   %  /  %   /",
	"       b/_____ /______/______/______/"]

lTemp5x5	:: String
lTemp5x5	= unlines [
	"          ___________________________________",
	"         /  %   /  %   /  %   /  %   /  %   / b",
	"        /_____ /______/______/______/______/ % b",
	"       /   %  /  %   /   %  /   %  /   %  / b  /b",
	"      /_____ /_____ /_____ /______/______/ % b/ %b",
	"     /   %  /  %   /  %   /  %   /  %   / b  /b  /b",
        "    /_____ /_____ /_____ /______/______/ % b/ %b/ %b",
        "   /  %   /  %   /  %   /  %   /  %   / b  /b  /b  /b",
	"  /______/______/______/______/______/ % b/ %b/ %b/ %b",
	" /  %   /  %   /  %   /  %   /  %   / b  /b  /b  /b  /b",
	"/______/______/______/______/______/ % b/ %b/ %b/ %b/ %b",
	"b   %  b  %   b  %   b  %   b  %   b   /b  /b  /b  /b  /",
	" b______b _____b______b______b______b / %b/ %b/ %b/ %b/ ",
	"  b  %   b  %   b  %   b  %   b  %   b   /b  /b  /b  /",
	"   b______b______b______b______b______b / %b/ %b/ %b/",
	"    b  %   b  %   b  %   b  %   b  %   b   /b  /b  /",
        "     b______b______b______b______b______b / %b/ %b/",
	"      b  %   b  %   b  %   b  %   b  %   b   /b  /",
	"       b______b______b______b______b______b / %b/",
	"        b  %   b  %   b  %   b  %   b  %   b   /",
	"         b______b______b______b______b______b /"]

rTemp5x5	:: String
rTemp5x5	= unlines [
	"          ___________________________________",
	"         /b  %   b   %  b  %   b   %  b  %   b",
	"        /% b______b______b______b______b______b",
	"       /b  /b   %  b  %   b  %   b   %  b  %   b",
	"      /% b/% b______b______b______b______b______b",
	"     /b  /b  /b  %   b  %   b  %   b  %   b  %   b",
	"    /% b/% b/% b______b______b______b______b______b",
	"   /b  /b  /b  /b  %   b  %   b  %   b  %   b  %   b",
	"  /% b/% b/% b/% b______b______b______b______b______b",
	" /b  /b  /b  /b  /b  %   b  %   b  %   b  %   b  %   b",
	"/% b/% b/% b/% b/% b______b______b______b______b______b",
	"b  /b  /b  /b  /b  /  %   /  %   /  %   /  %   /  %   /",    
	" b/% b/% b/% b/% b/______/______/______/______/______/",
	"  b  /b  /b  /b  /   %  /   %  /  %   /   %  /  %   /",
	"   b/% b/% b/% b/______/______/______/______/______/",
	"    b  /b  /b  /   %  /   %  /  %   /  %   /  %   /",
	"     b/% b/% b/______/______/______/______/______/",
	"      b  /b  /   %  /   %  /  %   /  %   /  %   /",
	"       b/% b/______/______/______/______/______/",
	"        b  /   %  /   %  /  %   /   %  /  %   /",
	"         b/_____ /______/______/______/______/"]


dTemp2x2	:: String
dTemp2x2	= unlines [
	"      %  %",
	"      %  %",
	"%  %  %  %  %  %     %  %     %  %    1 2",
	"%  %  %  %  %  %     %  %     %  %    3 4",
	"      %  %",
	"      %  %           %  %     %  %    5 6",
	"%  %  %  %  %  %     %  %     %  %    7 8",
	"%  %  %  %  %  %",
	"      %  %",
	"      %  %"] 

dTemp3x3	:: String
dTemp3x3	= unlines [
	"         %  %  %",
	"         %  %  %",
	"         %  %  %             %  %  %    %  %  %      1  2  3",
	"%  %  %  %  %  %  %  %  %    %  %  %    %  %  %      4  5  6",
	"%  %  %  %  %  %  %  %  %    %  %  %    %  %  %      7  8  9",
	"%  %  %  %  %  %  %  %  %",
	"         %  %  %             %  %  %    %  %  %     10 11 12",
	"         %  %  %             %  %  %    %  %  %     13 14 15",
	"         %  %  %             %  %  %    %  %  %     16 17 18",
	"%  %  %  %  %  %  %  %  %",
	"%  %  %  %  %  %  %  %  %    %  %  %    %  %  %     19 20 21",
	"%  %  %  %  %  %  %  %  %    %  %  %    %  %  %     22 23 24",
	"         %  %  %             %  %  %    %  %  %     25 26 27",
	"         %  %  %",
	"         %  %  %"] 

dTemp4x4	:: String
dTemp4x4	= unlines [
	"            %  %  %  %",
	"            %  %  %  %                 %  %  %  %     %  %  %  %     1  2  3  4",           
	"            %  %  %  %                 %  %  %  %     %  %  %  %     5  6  7  8",
	"            %  %  %  %                 %  %  %  %     %  %  %  %     9 10 11 12",
	"%  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %     %  %  %  %    13 14 15 16",
	"%  %  %  %  %  %  %  %  %  %  %  %",
	"%  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %     %  %  %  %    17 18 19 20",
	"%  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %     %  %  %  %    21 22 23 24",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    25 26 27 28",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    29 30 31 32",
	"            %  %  %  %",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    33 34 35 36",
	"%  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %     %  %  %  %    37 38 39 40",
	"%  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %     %  %  %  %    41 42 43 44",
	"%  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %     %  %  %  %    45 46 47 48",
	"%  %  %  %  %  %  %  %  %  %  %  %",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    49 50 51 52",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    53 54 55 56",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    57 58 59 60",
	"            %  %  %  %                 %  %  %  %     %  %  %  %    61 62 63 64"] 


dTemp5x5	:: String
dTemp5x5	= unlines [
 "                                                %  %  %  %  %    %  %  %  %  %    1   2   3   4   5",
 "                                                %  %  %  %  %    %  %  %  %  %    6   7   8   9   10",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    11  12  13  14  15",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    16  17  18  19  20",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    21  22  23  24  25",
 "               %  %  %  %  %",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    26  27  28  29  30",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    31  32  33  34  35",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    36  37  38  39  40",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    41  42  43  44  45",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    46  47  48  49  50",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    51  52  53  54  55",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    56  57  58  59  60",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    61  62  63  64  65",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    66  67  68  69  70",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    71  72  73  74  75",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    76  77  78  79  80",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    81  82  83  84  85",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    86  87  88  89  90",
 "%  %  %  %  %  %  %  %  %  %  %  %  %  %  %     %  %  %  %  %    %  %  %  %  %    91  92  93  94  95",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %    96  97  98  99 100",
 "               %  %  %  %  %",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %   101 102 103 104 105",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %   106 107 108 109 110",
 "               %  %  %  %  %                    %  %  %  %  %    %  %  %  %  %   111 112 113 114 115",
 "                                                %  %  %  %  %    %  %  %  %  %   116 117 118 119 120", 
 "                                                %  %  %  %  %    %  %  %  %  %   121 122 123 124 125"]  

pad				:: String -> String
pad (ch:[])			= "  " ++  [ch]
pad (ch1:ch2:[])		= ' ' : [ch1,ch2]
pad chs				= chs