initials generation added
[mc1516pa.git] / code / SokobanCoord.icl
index c23e282..db780cc 100644 (file)
@@ -1,26 +1,51 @@
-module SokobanCoord
+module SocobanCoord
 
 import StdList, StdInt, StdChar, StdMisc, StdClass, StdString, StdFile, StdArray, StdTuple, Data.Maybe, Data.Map, Control.Monad, Data.Tuple, Data.Void
+import Sokoban
 
-:: SokobanPuzzle :== [[SokobanTile]]
-:: SokobanTile = Wall | Free | Box | Target | Agent
+inputfile  :== "screen.1"
+outputfile :== "solver.smv"
 
 puzzle :: SokobanPuzzle
-puzzle = [[Wall, Wall, Wall, Wall, Wall,   Wall],
-          [Wall, Free, Free, Free, Free,   Wall],
-          [Wall, Agent,Free, Box,  Free,   Wall],
-          [Wall, Free, Free, Free, Target, Wall],
-          [Wall, Wall, Wall, Wall, Wall,   Wall]]
-
-size :: (Int, Int)
-size = (4,5)
+puzzle = Sokoban [[Wall, Wall, Wall, Wall, Wall,   Wall], 
+                  [Wall, Free, Free, Free, Free,   Wall],
+                  [Wall, Agent,Free, Box,  Free,   Wall],
+                  [Wall, Free, Free, Free, Target, Wall],
+                  [Wall, Wall, Wall, Wall, Wall,   Wall]]
+
+fromTile :: SokobanTile -> String
+fromTile Wall = "Wall"          
+fromTile Free = "Free"
+fromTile Box = "Box"
+fromTile Target = "Target"
+fromTile Agent = "Agent" 
+fromTile TargetAgent = "AgentOnTarget"
+fromTile TargetBox = "BoxOnTarget"
 
 checkX :: Int -> Int
-checkX x = if (x > length (hd puzzle)) (-1) x
+checkX x = let (Sokoban p) = puzzle in if (x > length (hd p)) (-1) x
 
 checkY :: Int -> Int
-checkY y = if (y > length puzzle) (-1) y
-
+checkY y = let (Sokoban p) = puzzle in if (y > length p) (-1) y
+
+genField :: SokobanPuzzle -> [String]
+genField p = let (Sokoban pzl) = p in genField` pzl 0 0 []
+where
+  genField` :: [[SokobanTile]] Int Int [String] -> [String]
+  genField` p i j rs
+    | i+1 == length (hd p) = rs
+    | j == (length p) = genField` p (i+1) 0 ["    init(x" +++ toString i +++ "_" +++ toString j +++ ") := " +++ fromTile ((p !! i) !! j) +++ ";\n": rs] 
+    | otherwise = genField` p i (j+1) ["    init(x" +++ toString i +++ "_" +++ toString j +++ ") := " +++ fromTile ((p !! i) !! j) +++ ";\n": rs] 
+
+genVars :: Int Int -> [String]
+genVars x y = genVars` x y 0 0 []
+where
+  genVars` :: Int Int Int Int [String] -> [String]
+  genVars` a b x y res
+    | (a+1) == x = res
+    | b == y = genVars` a b (x+1) 0 ["    x" +++ toString x +++ "_" +++ toString y +++ " : {Wall, Free, Box, BoxOnTarget, Target, Agent, AgentOnTarget};\n":res]
+    | otherwise = genVars` a b x (y+1) ["    x" +++ toString x +++ "_" +++ toString y +++ " : {Wall, Free, Box, BoxOnTarget, Target, Agent, AgentOnTarget};\n":res]
+          
 genCoord :: Int Int -> [String]
 genCoord x y = ["  next(x" +++ toString x +++ "_" +++ toString y +++ ") := case\n",
                 "    x" +++ toString x +++ "_" +++ toString y +++ " = Wall: Wall;\n",
@@ -60,11 +85,19 @@ genCoord x y = ["  next(x" +++ toString x +++ "_" +++ toString y +++ ") := case\
                 "  esac;\n"
                 ]
 
-/*
-genAll :: SokobanPuzzle -> [[String]]
-genAll p = [\\]
-genAll [x:xs] = []
-*/
+genAll :: [String]
+genAll = let (Sokoban p) = puzzle in
+         [
+          "MODULE main\n",
+          "VAR\n"
+          ] 
+      ++ genVars ((length p) - 1) ((length (hd p)) - 1)
+      ++ [
+          "  ASSIGN\n",
+          "    init(move) := {Up, Down, Left, Right};\n"
+         ]
+      ++ genField puzzle
+      ++ flatten [filter (\x -> not (contains '-' x)) (genCoord x y) \\ x <- [0..4], y <- [0..5]]
 
 contains :: Char String -> Bool
 contains char str = not (isEmpty [c\\c<-:str | char == c])
@@ -74,28 +107,26 @@ readLines file
   | sfend file = []
   # (line, file) = sfreadline file
   | otherwise = [line: readLines file]
-
+  
 writeLines :: [String] *File -> *File
 writeLines [] file = file
 writeLines [l:ls] file = writeLines ls (file <<< l)
-
-openInpFile :: *World String -> (File, *World)
+  
+openInpFile :: *World String -> (File, *World) 
 openInpFile world path
   # (ok, file, world) = sfopen path 0 world
   | not ok = abort "Error reading the file."
   = (file, world)
-
+  
 openOutFile :: *World String -> (*File, *World)
 openOutFile world path
   # (ok, file, world) = fopen path 1 world
   | not ok = abort "Can not write to a file."
   = (file, world)
-
+  
 closeFile :: *World *File -> (Bool, *World)
 closeFile world file
   # world = fclose file world
   = world
-
-
-
-Start = flatten [filter (\x -> not (contains '-' x)) (genCoord x y) \\ x <- [0..4], y <- [0..5]]
+  
+Start = genAll 
\ No newline at end of file