factory-lang/Main.hs

111 lines
3.7 KiB
Haskell

module Main where
import Data.List
import System.Environment
import System.Exit
import Element
import Types
import Dirty
main :: IO ()
main = do
args <- getArgs
if null args
then die "No filename provided."
else run $ head args
run :: String -> IO ()
run inputFile = do
input <- readFile inputFile
let internalFactory = stringsToFactory $ lines input
let el = entryPointLocation internalFactory
interpretLoop internalFactory [Element 0 (fst el) (snd el) True]
interpretLoop :: Factory -> [Element] -> IO ()
interpretLoop f es =
let getDeadElement (e:es)
| state e == False = e
| otherwise = getDeadElement es
in do
let elements = stepInterpret f es
if any (\e -> state e == False) es
then exitWith (ExitFailure $ fromInteger $ value $ getDeadElement es)
else printFactory f elements
a <- getChar
case a of
'q' -> return ()
_ -> interpretLoop f elements
stringsToFactory :: [[Char]] -> [[Tile]]
stringsToFactory [] = []
stringsToFactory s = map (map charToTile) s
tupAdd :: (Num a, Num b) => (a, b) -> (a, b) -> (a, b)
tupAdd (a, b) (c, d) = (a + c, b + d)
entryPointLocation :: Factory -> (Int, Int)
entryPointLocation [] = error "Couldn't find an entrypoint (E)."
entryPointLocation (l:ls) = case index of
Nothing -> tupAdd (0, 1) (entryPointLocation ls)
Just x -> (x, 0)
where index = elemIndex Entrypoint l
oobCheck :: Factory -> Element -> Bool
oobCheck f e = yPos e >= length f
|| xPos e >= length (f !! yPos e)
singleton :: a -> [a]
singleton a = [a]
-- custom hashmap thingy, but uses lists so it's slow on large things (luckily this is small)
tileActionMap :: Tile -> [(Tile, Element -> [Element])] -> (Element -> [Element])
tileActionMap _ [] = singleton
tileActionMap tile (pair:rest)
| tile == fst pair = snd pair
| otherwise = tileActionMap tile rest
-- TODO: make this safe, aka boundary check
spitOut :: Direction -> Factory -> Element -> Element
spitOut dir f elem = case dir of
East -> spitOutEast f elem
South -> spitOutSouth f elem
West -> spitOutWest f elem
North -> spitOutNorth f elem
spitOutNth :: Int -> Direction -> Factory -> Element -> Element
spitOutNth 0 dir f elem = spitOut dir f elem
spitOutNth n dir f elem = spitOutNth decremented (succ dir) f elem
where decremented
| (getTile dir f elem) == (Just $ Track dir) = n - 1
| otherwise = n
duplicate :: Element -> [Element]
duplicate e = [e, e]
update :: Factory -> Element -> [Element]
update f e = if oobCheck f e then error "Element out of bounds check failed!"
else tileActionMap t tileActions e
where t = (f !! yPos e) !! xPos e
tileActions = [ (Track East, singleton . incXPos)
, (Track West, singleton . decXPos)
, (Track South, singleton . incYPos)
, (Track North, singleton . decYPos)
, (Modifier Increment, singleton . incVal . spitOut East f)
, (Modifier Decrement, singleton . decVal . spitOut East f)
, (Special Duplicate, dupFunc)
, (Special Conditional, singleton . zeroBranch)
, (Entrypoint, singleton . spitOut East f)
, (Exitpoint, singleton . kill)
]
dupFunc :: Element -> [Element]
dupFunc elem = [ spitOutNth 0 East f elem
, spitOutNth 1 East f elem
]
zeroBranch elem = if value elem == 0
then spitOutNth 0 East f elem
else spitOutNth 1 East f elem
stepInterpret :: Factory -> [Element] -> [Element]
stepInterpret f = concatMap (update f)