Navigation Menu

Skip to content

Instantly share code, notes, and snippets.

@crabmusket
Last active December 16, 2015 04:19
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save crabmusket/5376653 to your computer and use it in GitHub Desktop.
Save crabmusket/5376653 to your computer and use it in GitHub Desktop.
Reads the G commands from a CNC file and outputs the physical state of the machine after each command.
module Main where
import Data.Maybe
import Text.Printf
import Text.Regex.Posix
-- The main function defines what the program does when we compile it.
main = do
-- Read all data from standard input (until the end of the file).
file <- getContents
-- Get a list of all the go commands from the file.
let commands = goCommandsOf file
-- Apply commands to default machine.
let states = defaultMachine `afterRunning` commands
-- Convert command states to physical positions.
let positions = map (getMachineState) states
-- Print out each state.
mapM (print) positions
-- Declare a data type representing the command state of a CNC machine. That is,
-- where it expects to be putting holes! Each named value is of type Float.
data Machine = Machine {
conN :: Int,
conX :: Float,
conY :: Float,
conZ :: Float
}
-- A constant Machine we can use as a starting state.
defaultMachine = Machine 0 0 0 0
-- Define the Command data type. It's very similar to the Machine data type, but
-- instead of Floats, the values are Maybe Floats. Maybe Float means the value may
-- either be Nothing or Just x, where x is a Float. This allows us to omit some
-- values (i.e., not change them).
data Command = Command {
number :: Int,
comX :: Maybe Float,
comY :: Maybe Float,
comZ :: Maybe Float
}
defaultCommand = Command 0 Nothing Nothing Nothing
-- A new data type that represents the physical positions the machine can be in.
data MachineState = MachineState {
command :: Int,
posX :: Float,
posD :: Float,
posZ :: Float
}
defaultMachineState = MachineState 0 0 0 0
-- Define the type of a function goCommandsOf. It takes a single big String and
-- returns a list of Commands.
goCommandsOf :: String -> [Command]
-- The goCommandsOf function is a composition of three other functions. Don't
-- worry too much about the syntax, but it will convert a big block of text to
-- a list of lines, then attempt to produce a Command from each one using the
-- readGoCommand function. If the function can't find a go command (i.e., it
-- returns Nothing) the line will be ignored. All the successful Commands will
-- be returned in a new list.
goCommandsOf s = mapMaybe (readGoCommand) (lines s)
-- Again, we'll declare the type of the readGocommand function. These type
-- declarations are optional, but they're good for explanations. This function
-- returns a Maybe Command because it may fail to find a go command.
readGoCommand :: String -> Maybe Command
-- The readGoCommand basically checks if the input string s contains
-- the "G0X" pattern. If it does, it returns a Command with the appropriate
-- parameters.
readGoCommand s = if isGoCommand
then Just Command {
number = readNumber s,
comX = readParam 'X' s,
comY = readParam 'Y' s,
comZ = readParam 'Z' s
}
else Nothing
-- The if block has ended - now we define the variable isGoCommand and
-- the function readParam that we used in it.
where
-- Use a regular expression to check whether the line contains the
-- G0X pattern. The :: Bool tells the function we expect a Boolean
-- result - i.e., true or false.
isGoCommand = s =~ "G0[123]" :: Bool
-- readParam takes a parameter character and the line, and returns
-- the parameter value. For example, given 'X' and "X3.5", it should
-- return (Just 3.5). If the string was "Y3.5", it would return
-- Nothing.
readParam param str = fmap
(\x -> read (tail x) :: Float)
(str =~~ (param : "-?[0-9.]+") :: Maybe String)
-- This needs to return a definite Int (not a Maybe Int). For lines
-- without numbers we'll just return a dodgy 0.
readNumber str = case n of
"" -> 0
otherwise -> read $ tail n :: Int
where n = str =~ "N[0-9]+" :: String
-- afterRunning is a convenience function that provides a nice interface to the
-- recursive runCommands' function below. It applies a list of commands to a
-- machine, returning a list of states the machine is in after each command.
afterRunning :: Machine -> [Command] -> [Machine]
afterRunning m [] = [m]
afterRunning m cs = reverse (runCommands' cs [m])
-- Recursively apply each command to the most recent state. As this function runs,
-- the list of commands shrinks while the returned list of Machine states
-- grows.
runCommands' :: [Command] -> [Machine] -> [Machine]
runCommands' [] ms = ms
runCommands' (c:cs) (m:ms) = runCommands' cs (state:m:ms) where
state = applySingleCommand m c
-- Apply a command to a control state. This involves checking lots of Maybe values
-- in the command, and if they're not Nothing, overwriting the command state. For this
-- we use fromMaybe. fromMaybe x y returns x if y is Nothing - otherwise it returns the
-- Just value.
applySingleCommand :: Machine -> Command -> Machine
applySingleCommand control command = control {
conN = number command,
conX = fromMaybe (conX control) (comX command),
conY = fromMaybe (conY control) (comY command),
conZ = fromMaybe (conZ control) (comZ command)
}
-- Determines the physical parameters of the machine in order for it to assume
-- the given commanded position. Edit this function to change the way the machine
-- responds to position commands.
getMachineState :: Machine -> MachineState
getMachineState c = defaultMachineState {
command = conN c,
posZ = conZ c,
posX = conX c,
posD = conY c
}
-- Lets us control the way a MachineState is printed to the console.
instance Show MachineState where
show s = "N" ++ show (command s) ++ " " ++
"x" ++ show (posX s) ++ " " ++
"d" ++ show (posD s) ++ " " ++
"z" ++ show (posZ s)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment