| Copyright | (c) Sebastian Galkin 2018 | 
|---|---|
| License | GPL-3 | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
HBF.Compiler
Contents
Description
Synopsis
- type ProgramParser a = ParsecT [Op] () Identity a
- data CompilerOptions = CompilerOptions {}
- data OffsetState = OffSt {}
- newtype FusedProgram = Fused {}
- newtype CompilationSummary = CompilationSummary {}
- saveCompilerOutput :: Program Optimized -> FilePath -> IO ()
- inMemoryCompile :: CompilerOptions -> Text -> Either ParseError (Program Optimized, CompilationSummary)
- summarizeCompilation :: Program Optimized -> CompilationSummary
- compile :: CompilerOptions -> IO (Either ParseError CompilationSummary)
- optimize :: CompilerOptions -> Program Unoptimized -> Program Optimized
- toIR :: Program Unoptimized -> Program Optimized
- fusionOpt :: Program Optimized -> Program Optimized
- liftLoop :: ([Op] -> Maybe [Op]) -> Program o -> Program o
- clearOpt :: Program Optimized -> Program Optimized
- mulOpt :: Program Optimized -> Program Optimized
- scanOpt :: Program Optimized -> Program Optimized
- emptyState :: OffsetState
- offsetInstructionOpt :: Program Optimized -> Program Optimized
- load :: ByteString -> Program Optimized
- loadFile :: FilePath -> IO (Program Optimized)
- optionsP :: Parser CompilerOptions
- options :: ParserInfo CompilerOptions
- defaultCompilerOptions :: CompilerOptions
- noOptimizationCompilerOptions :: CompilerOptions
- parsePure :: [String] -> ParserResult CompilerOptions
- unsafeParse :: [String] -> IO CompilerOptions
- parse :: IO CompilerOptions
- satisfy' :: Show t => (t -> Bool) -> ParsecT [t] () Identity t
- mrightP :: ProgramParser MemOffset
- mleftP :: ProgramParser MemOffset
- plusP :: ProgramParser Int
- minusP :: ProgramParser Int
- summedP :: Num n => ProgramParser n -> ProgramParser n
- mulP :: ProgramParser [(MulFactor, MemOffset)]
- isRight :: Op -> Bool
- isLeft :: Op -> Bool
- isPlus :: Op -> Bool
- isMinus :: Op -> Bool
- data ParseError
Documentation
type ProgramParser a = ParsecT [Op] () Identity a Source #
This parser is used to implement the mul optimization. See mulOpt.
data CompilerOptions Source #
Command line flags to the Brainfuck compiler
Constructors
| CompilerOptions | |
| Fields 
 | |
Instances
| Show CompilerOptions Source # | |
| Defined in HBF.Compiler Methods showsPrec :: Int -> CompilerOptions -> ShowS # show :: CompilerOptions -> String # showList :: [CompilerOptions] -> ShowS # | |
data OffsetState Source #
Helper datastructure to implement a stateful transformation in offsetInstructionOpt.
Constructors
| OffSt | |
Instances
| Show OffsetState Source # | |
| Defined in HBF.Compiler Methods showsPrec :: Int -> OffsetState -> ShowS # show :: OffsetState -> String # showList :: [OffsetState] -> ShowS # | |
newtype FusedProgram Source #
Helper type to apply the Fuse optimization using a Monoid.
Instances
| Show FusedProgram Source # | |
| Defined in HBF.Compiler Methods showsPrec :: Int -> FusedProgram -> ShowS # show :: FusedProgram -> String # showList :: [FusedProgram] -> ShowS # | |
| Semigroup FusedProgram Source # | This  Examples of fusable operations: 
 | 
| Defined in HBF.Compiler Methods (<>) :: FusedProgram -> FusedProgram -> FusedProgram # sconcat :: NonEmpty FusedProgram -> FusedProgram # stimes :: Integral b => b -> FusedProgram -> FusedProgram # | |
| Monoid FusedProgram Source # | |
| Defined in HBF.Compiler Methods mempty :: FusedProgram # mappend :: FusedProgram -> FusedProgram -> FusedProgram # mconcat :: [FusedProgram] -> FusedProgram # | |
newtype CompilationSummary Source #
Compilation summary for the user. It contains overview information and statistics about the compilation result.
Constructors
| CompilationSummary | |
| Fields | |
Instances
| Show CompilationSummary Source # | |
| Defined in HBF.Compiler Methods showsPrec :: Int -> CompilationSummary -> ShowS # show :: CompilationSummary -> String # showList :: [CompilationSummary] -> ShowS # | |
saveCompilerOutput :: Program Optimized -> FilePath -> IO () Source #
Encode the compiled file into the given path.
inMemoryCompile :: CompilerOptions -> Text -> Either ParseError (Program Optimized, CompilationSummary) Source #
Use the given CompilerOptions to parse, compile and optimize the text representation of a
 Brainfuck program into the IR. cOptsSource and cOptsOut in the compiler options are ignored.
summarizeCompilation :: Program Optimized -> CompilationSummary Source #
Summarize a compiled program creating the CompilationSummary
compile :: CompilerOptions -> IO (Either ParseError CompilationSummary) Source #
Use CompilerOptions to read, compile, optimize, and save a program from/to the filesystem.
 Input and output files are provided by cOptsSource and cOptsOut.
optimize :: CompilerOptions -> Program Unoptimized -> Program Optimized Source #
Apply optimizations to the Unoptimized program turning. The optimizations that
 will be available are the ones specified by the CompilerOptions given.
toIR :: Program Unoptimized -> Program Optimized Source #
Given a parsed program, turn it into an optimized one, but with the null optimization. Effectively this is only a type change.
fusionOpt :: Program Optimized -> Program Optimized Source #
Apply the fusion optimization using the FusedProgram Monoid instance.
The fusion optimization consist of turning multiple instructions into one. For example
 if the original Brainfuck code contains ++++, this would be parsed as
Program[Inc1 0,Inc1 0,Inc1 0,Inc1 0]
but it would be fused to a single IR instruction: Inc 4 0.
>>>fusionOpt $ Program [Inc 1 0, Inc 1 0, Inc 1 0, Inc 1 0][Inc 4 0]
Similarly, other instructions,
 like Move, In, Out, Clear and Scan can be fused as long as the offset at which they
 must be applied is the same.
Non fusable operation remain unchanged:
>>>fusionOpt $ Program [Inc 1 0, Inc 1 1][Inc 1 0,Inc 1 1]
clearOpt :: Program Optimized -> Program Optimized Source #
Basic optimization that turns the loop [-] into a single instruction Clear.
 Useful because clearing a memory position is a pretty common operation in Brainfuck and
 very expensive if treated as a loop.
>>>:set -XOverloadedStrings>>>Right (res, _) = inMemoryCompile defaultCompilerOptions "[-]">>>res[Clear 0]
mulOpt :: Program Optimized -> Program Optimized Source #
Copy and multiply optimization. A very common usage of loops is to copy the value of a memory
 position to a different: [->>+<<] this will move the contents of the current memory position
 to places to the right, also clearing the original position to zero. If we change the number of +
 operations we get multiplication, if we have several groups of ++.. operations we get multiple copies.
 In the general case, for example:
>>>:set -XOverloadedStrings>>>Right (res, _) = inMemoryCompile defaultCompilerOptions "[->+>++>++++<<<]">>>res[Mul 1 0 1,Mul 2 0 2,Mul 4 0 3,Clear 0]
The original Brainfuck copies the current position one place to the right, doubles the current position two places to the right, and quadruples the current position three places to the right; finally zeroing the current position. With the mul optimization in this function, all that loop would be replaced by 4 instructions.
scanOpt :: Program Optimized -> Program Optimized Source #
Implement the scan optimization. Another common operation in Brainfuck is to search for the first zero
 in the neighboring memory, either to the right or to the left [>] or [<]. These loops can be replaced
 for a more optimal search, represented as a single Scan UpScan Down
>>>scanOpt $ Program [Loop [Move 1]][Scan Up 0]
emptyState :: OffsetState Source #
Start state for offsetInstructionOpt.
offsetInstructionOpt :: Program Optimized -> Program Optimized Source #
Implement the offset instruction optimization. This is probably the most complex optimization implemented in the library.
In streams of instructions between loops, there is no need to keep updating the current position if we can keep track of where the different operations should be applied. This is a trade-off of time (not updating the pointer) by space (keeping track of the offset in every operation). For example the following unoptimized code
>>>offsetInstructionOpt $ Program [Loop [], Move 1, Inc 1 0, Move 2, Clear 0, Mul 2 0 1, Loop []][Loop [],Inc 1 1,Clear 3,Mul 2 3 1,Move 3,Loop []]
And the optimization eliminated one Move instruction. In general, for larger programs the gain
 will be more noticeable.
An important detail to take into account is that Scan operations break the stream of operations
 that can be optimized together, and turn the accumulated offset back to zero:
>>>offsetInstructionOpt $ Program [Loop [], Move 1, Inc 1 0, Scan Up 0, Inc 0 2, Loop []][Loop [],Inc 1 1,Scan Up 1,Inc 0 2,Loop []]
load :: ByteString -> Program Optimized Source #
Load a compiled program from saveCompilerOutput output.
loadFile :: FilePath -> IO (Program Optimized) Source #
Load a compiled program saved with saveCompilerOutput.
defaultCompilerOptions :: CompilerOptions Source #
Default compiler options: all optimizations, not verbose, no input or output files.
noOptimizationCompilerOptions :: CompilerOptions Source #
Compiler options: all optimizations off.
parsePure :: [String] -> ParserResult CompilerOptions Source #
Parse a list of command line arguments
unsafeParse :: [String] -> IO CompilerOptions Source #
Parse a list of command line arguments printing errors to the stderr
parse :: IO CompilerOptions Source #
Parse command line arguments printing errors to the stderr
satisfy' :: Show t => (t -> Bool) -> ParsecT [t] () Identity t Source #
Parse successfully if the token satisfies the predicate.
mrightP :: ProgramParser MemOffset Source #
Parse movement to the right (>), returning the offset value.
>>>Parsec.parse mrightP "" [Move 3]Right 3
>>>Data.Either.isLeft $ Parsec.parse mrightP "" [Move (-1)]True
mleftP :: ProgramParser MemOffset Source #
Parsemovement to the left (<), returning the offset value.
>>>Parsec.parse mleftP "" [Move (-3)]Right 3
>>>Data.Either.isLeft $ Parsec.parse mleftP "" [Move 1]True
plusP :: ProgramParser Int Source #
Parse increment, returning total increment.
>>>Parsec.parse plusP "" [Inc 3 0]Right 3
>>>Data.Either.isLeft $ Parsec.parse plusP "" [Inc (-2) 0]True
minusP :: ProgramParser Int Source #
Parse decrement, returning total decrement.
>>>Parsec.parse minusP "" [Inc (-3) 0]Right 3
>>>Data.Either.isLeft $ Parsec.parse minusP "" [Inc 2 0]True
summedP :: Num n => ProgramParser n -> ProgramParser n Source #
Sum the result of a parser applied repeatedly
>>>Parsec.parse (summedP plusP) "" [Inc 3 0, Inc 1 0, Inc (-4) 0]Right 4
mulP :: ProgramParser [(MulFactor, MemOffset)] Source #
Full multiple copy/multiply operation parser. Returns the set of factors and relative, incremental offsets.
>>>Parsec.parse mulP "" [Inc (-1) 0, Move 1, Inc 2 0, Move 3, Inc 1 0, Move (-4)]Right [(2,1),(1,3)]
Reexport from BFP.Parser
data ParseError #
The abstract data type ParseError represents parse errors. It
 provides the source position (SourcePos) of the error
 and a list of error messages (Message). A ParseError
 can be returned by the function parse. ParseError is an
 instance of the Show and Eq classes.
Instances
| Eq ParseError | |
| Defined in Text.Parsec.Error | |
| Show ParseError | |
| Defined in Text.Parsec.Error Methods showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |