LoginSignup
5
5

More than 5 years have passed since last update.

HaskellでBrainfuck

Last updated at Posted at 2014-12-23

背景

まったく興味のない内容の会合で3時間ほど暇を持て余していたので、BrainfuckについてのWikipediaの記事を見ながら書いた。他人の(きっと大量にあるに違いない)コードとか見てもないし、しかもVectorではなくMapを使うというクソみたいな実装なので、実用性は色々な意味で皆無だし、そもそもこういう書き方でいいのかすらまったくわかっていない。

追記:IOVectorを使って書きなおしてみた。あと、連続するインクリメント・デクリメントの個数を数えて引き渡すようにしてみた。双方向リストを使って最後尾にappendしていくのではなく、おとなしく普通のリストを使って途中でreverseすることにした。このあたり、どうするのがいいんだろうか。

(ハノイの塔) http://esoteric.sange.fi/brainfuck/bf-source/prog/hanoi.bf

を実行してみると両者の速度差が歴然とする(それでも遅いけど)。

再追記:機械状態をアドレス値からセルへの写像ではなく、おとなしくヘッダと双方向の無限長テープで表現するヴァージョンを作ってみた。これが一番簡単。そしてリスト使ってるのに一番早いのでなんか凄い悔しい。

再々追記:C言語へのトランスレータを作ってみた。Hanoi.bfから生成されたコードでも、gcc -O だと実行が速すぎて塔の状態遷移がまったくわからなくてつまらない(最適化しなければ大丈夫)。

会議中の暇つぶしの産物である最初のクソコード

Brainfuck.hs
module Main where
import Data.Foldable (foldlM)
import Data.Sequence (Seq, empty, (|>))
import qualified Data.Map.Strict as M

import System.Environment (getArgs)
import System.IO (stdin, putChar)

import Data.Word (Word8)
import Data.ByteString.Internal (w2c, c2w)


type Pointer = Int
type Cell = Word8
type Memory = M.Map Pointer Cell
type Machine = (Pointer, Memory)

data Instruction =  PIncr
                   |PDecr
                   |CIncr
                   |CDecr
                   |Print
                   |Read
                   |Loop (Seq Instruction)
                   deriving (Eq, Show)

-- parse and compile a Brainfuck code to instructions.
compile :: String -> Seq Instruction  
compile str = fst $ compile' (empty, str)
  where
    compile' :: (Seq Instruction, String) -> (Seq Instruction, String)
    compile' (acc, "") = (acc, "")
    compile' (acc,'>':xs) = compile' (acc |> PIncr, xs)
    compile' (acc,'<':xs) = compile' (acc |> PDecr, xs)
    compile' (acc,'+':xs) = compile' (acc |> CIncr, xs)
    compile' (acc,'-':xs) = compile' (acc |> CDecr, xs)
    compile' (acc,'.':xs) = compile' (acc |> Print, xs)
    compile' (acc,',':xs) = compile' (acc |> Read, xs)
    compile' (acc,'[':xs) = compile' (acc |> Loop subinstructs, xss)
      where (subinstructs, xss) = compile' (empty, xs)
    compile' (acc,']':xs) = (acc, xs)
    compile' (acc, _:xs) = compile' (acc, xs) -- ignore any other character.

-- execute an instruction on a machine with a given state. 
execute :: Machine -> Instruction -> IO Machine
execute machine@(pointer, memory) instruct = case instruct of
  PIncr -> return (pointer+1, memory)
  PDecr -> return (pointer-1, memory)
  CIncr -> return (pointer, incr pointer memory)
    where incr ptr mem = M.insert ptr (M.findWithDefault 0 ptr mem +1) mem
  CDecr -> return (pointer, decr pointer memory)
    where decr ptr mem = M.insert ptr (M.findWithDefault 0 ptr mem -1) mem
  Print -> do
            putChar $ w2c $ M.findWithDefault 0 pointer memory
            return machine
  Read -> do
            chr <- getChar
            return (pointer, M.insert pointer (c2w chr) memory)
  Loop subinstructs -> do {loop machine subinstructs;}
              where loop m@(ptr, mem) i = do
                      if (i==empty) || (M.findWithDefault 0 ptr mem) == 0
                        then return m
                        else do {m' <- run m i; loop m' i;}

-- execute a sequence of instructions.
run :: Machine -> Seq Instruction -> IO Machine 
run machine = foldlM execute machine

-- read the first argument as a code, compile and execute it
-- on a machine with an initial state.
main :: IO () 
main = do
         fmap (!!0) getArgs >>= run (0, M.empty) . compile
         return ()

main' = do -- or read the first argument as a filename of a source code.
          filename <- fmap (!!0) getArgs
          readFile filename >>= run (0, M.empty) . compile
          return ()

使ったこともないIOVectorで書きなおしたウンコード

Brainfuck2.hs
module Main where

import Data.Word (Word8)
import Data.ByteString.Internal (w2c, c2w)
import qualified Data.Vector.Unboxed.Mutable as M
import System.Environment (getArgs)

type Memory = M.IOVector Word8
type Machine = (Int, Memory)

data Instruction =  PIncr Int
                   |PDecr Int
                   |CIncr Word8
                   |CDecr Word8
                   |Print
                   |Read
                   |Loop [Instruction]
                   deriving (Eq, Show)

-- parse and compile a Brainfuck code to instructions.
compile :: String -> [Instruction]
compile str = fst $ compile' ([], str)
  where
    compile' :: ([Instruction], String) -> ([Instruction], String)
    compile' (acc, "") = (reverse acc, "")
    compile' (PIncr n:acc, '>':xs) = compile' (PIncr (n+1):acc, xs)
    compile' (PDecr n:acc, '<':xs) = compile' (PDecr (n+1):acc, xs)
    compile' (CIncr n:acc, '+':xs) = compile' (CIncr (n+1):acc, xs)
    compile' (CDecr n:acc, '-':xs) = compile' (CDecr (n+1):acc, xs)
    compile' (acc,'>':xs) = compile' (PIncr 1:acc, xs)
    compile' (acc,'<':xs) = compile' (PDecr 1:acc, xs)
    compile' (acc,'+':xs) = compile' (CIncr 1:acc, xs)
    compile' (acc,'-':xs) = compile' (CDecr 1:acc, xs)
    compile' (acc,'.':xs) = compile' (Print:acc, xs)
    compile' (acc,',':xs) = compile' (Read:acc, xs)
    compile' (acc,'[':xs) = compile' (Loop subinstructs:acc, xss)
      where (subinstructs, xss) = compile' ([], xs)
    compile' (acc,']':xs) = (reverse acc, xs)
    compile' (acc, _:xs) = compile' (acc, xs) -- ignore any other character.

-- execute instructions on a machine with an initial state.
run :: [Instruction] -> IO ()
run instructions = do
  initial <- M.replicate 30000 0
  run' instructions (0, initial)
  return ()
    where
      run' [] m = return m
      run' i@(x:xs) m@(ptr, mem) = case x of
        PIncr n -> run' xs (ptr+n, mem)
        PDecr n -> run' xs (ptr-n, mem)
        CIncr n -> do
          c <- M.read mem ptr
          M.write mem ptr (c+n)
          run' xs m
        CDecr n -> do
          c <- M.read mem ptr
          M.write mem ptr (c-n)
          run' xs m
        Print -> M.read mem ptr >>= putChar.w2c >> run' xs m
        Read -> getChar >>= (M.write mem ptr).c2w >> run' xs m
        Loop sub -> do
                      c <- M.read mem ptr
                      if (c==0) || null sub
                        then run' xs m
                        else run' sub m >>= run' i

-- read the first argument as a name of a source file.
main :: IO ()
main = do
         filename <- fmap (!!0) getArgs
         readFile filename >>= run.compile

おとなしくチューリングマシンそのものにしとくのが一番

Brainfuck3.hs
module Main where
import Data.Word (Word8)
import Data.ByteString.Internal (w2c, c2w)
import Control.Monad (void)
import System.Environment (getArgs)

type Machine = ([Word8], Word8, [Word8])
data Op =  PIncr|PDecr|CIncr|CDecr|Print|Read|Loop [Op] deriving (Eq, Show)

compile :: String -> [Op]
compile str = fst $ compile' ([], str)
  where
    compile' :: ([Op], String) -> ([Op], String)
    compile' (ops, "") = (reverse ops, "")
    compile' (ops,'>':xs) = compile' (PIncr:ops, xs)
    compile' (ops,'<':xs) = compile' (PDecr:ops, xs)
    compile' (ops,'+':xs) = compile' (CIncr:ops, xs)
    compile' (ops,'-':xs) = compile' (CDecr:ops, xs)
    compile' (ops,'.':xs) = compile' (Print:ops, xs)
    compile' (ops,',':xs) = compile' (Read:ops, xs)
    compile' (ops,'[':xs) = compile' (Loop subops:ops, xss)
      where (subops, xss) = compile' ([], xs)
    compile' (ops,']':xs) = (reverse ops, xs)
    compile' (ops, _:xs) = compile' (ops, xs) -- ignore any other character.

run :: [Op] -> IO Machine
run ops = run' ops (repeat 0, 0, repeat 0)
  where
    run' :: [Op] -> Machine -> IO Machine
    run' [] m = return m
    run' (Loop [CDecr]:xs) (ls, c, rs) = run' xs (ls, 0, rs) -- a BF idiom.
    run' (PIncr:xs) (ls, c, r:rs) = run' xs (c:ls, r, rs)
    run' (PDecr:xs) (l:ls, c, rs) = run' xs (ls, l, c:rs)
    run' (CIncr:xs) (ls, c, rs) = run' xs (ls, c+1, rs)
    run' (CDecr:xs) (ls, c, rs) = run' xs (ls, c-1, rs)
    run' (Print:xs) (ls, c, rs) = (putChar.w2c) c >> run' xs (ls, c, rs)
    run' (Read:xs) (ls, c, rs) = getChar >>= \chr -> run' xs (ls, c2w chr, rs)
    run' (Loop sub:xs) (ls, 0, rs) = run' xs (ls, 0, rs)
    run' (Loop sub:xs) (ls, c, rs) = run' sub (ls, c, rs) >>= run' (Loop sub:xs)

main = do
         filename <- fmap (!!0) getArgs
         readFile filename >>= void . run . compile

C言語へのトランスレータ(これが一番早い)

Bf2c.hs
module Main where

import Data.Word (Word8)
import System.Environment (getArgs)

data Instruction =  PIncr Int
                   |PDecr Int
                   |CIncr Word8
                   |CDecr Word8
                   |Print
                   |Read
                   |Loop [Instruction]
                   deriving (Eq, Show)

-- parse and compile a Brainfuck code to instructions.
compile :: String -> [Instruction]
compile str = fst $ compile' ([], str)
  where
    compile' :: ([Instruction], String) -> ([Instruction], String)
    compile' (acc, "") = (reverse acc, "")
    compile' (PIncr n:acc, '>':xs) = compile' (PIncr (n+1):acc, xs)
    compile' (PDecr n:acc, '<':xs) = compile' (PDecr (n+1):acc, xs)
    compile' (CIncr n:acc, '+':xs) = compile' (CIncr (n+1):acc, xs)
    compile' (CDecr n:acc, '-':xs) = compile' (CDecr (n+1):acc, xs)
    compile' (acc,'>':xs) = compile' (PIncr 1:acc, xs)
    compile' (acc,'<':xs) = compile' (PDecr 1:acc, xs)
    compile' (acc,'+':xs) = compile' (CIncr 1:acc, xs)
    compile' (acc,'-':xs) = compile' (CDecr 1:acc, xs)
    compile' (acc,'.':xs) = compile' (Print:acc, xs)
    compile' (acc,',':xs) = compile' (Read:acc, xs)
    compile' (acc,'[':xs) = compile' (Loop subinstructs:acc, xss)
      where (subinstructs, xss) = compile' ([], xs)
    compile' (acc,']':xs) = (reverse acc, xs)
    compile' (acc, _:xs) = compile' (acc, xs) -- ignore any other character.

translate :: [Instruction] -> String
translate [] = ""
-- very simple optimisation.
translate (Loop [CDecr 1]:xs) = "*p=0;" ++ translate xs
translate (PIncr 1:xs) = "p++;" ++ translate xs
translate (PDecr 1:xs) = "p--;" ++ translate xs
translate (CIncr 1:xs) = "(*p)++;" ++ translate xs
translate (CDecr 1:xs) = "(*p)--;" ++ translate xs
--
translate (PIncr n:xs) = "p=p+" ++ show n ++ ";" ++ translate xs
translate (PDecr n:xs) = "p=p-" ++ show n ++ ";" ++ translate xs
translate (CIncr n:xs) = "*p=*p+" ++ show n ++ ";" ++ translate xs
translate (CDecr n:xs) = "*p=*p-" ++ show n ++ ";" ++ translate xs
translate (Print:xs) = "putchar(*p);" ++ translate xs
translate (Read:xs) = "getchar(*p);" ++ translate xs
translate (Loop sub:xs) = "while(*p){" ++ translate sub ++ "}" ++ translate xs

translate' str = header ++ (translate$compile$str) ++ footer
  where
    header = "#include <stdio.h>\n\
             \int main(){\
             \int m[30000]={};\
             \int *p=m;"
    footer = "}\n"

-- read the first argument as a name of a source file.
main :: IO ()
main = do
         filename <- fmap (!!0) getArgs
         readFile filename >>= putStr.translate'

ベンチマーク用Brainfuckコード(ハノイの塔)

Hanoi.bf
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>[-]>[-]+++++++++++++++++++++++++++.++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++.-------------------.-------
--------------------------------------.+++++++++++++++++++++++++++++++++++++
+++++++++++++++++++++++++++.-----------------------------------------.++++++
++++++++++++++++++.[-]+++++++++++++++++++++++++++.++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++.-------------------------------------
----.+++++++++.---------.+++++.+++++++++++++++++.++++++++++++.++++++++++++++
+++++++++++++.++++++++.------------------.+++++++++++++.+.------------------
-----------------------------------------------------------------.++++++++++
+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++.------
---.----------------------------------------------------------------------.+
+++++++++++++++++++++++++++++++++++++++.+++++++++++++++++++++++++.++++++++++
+++.+.------.---------------------------------------------------------------
----------.+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++.+++++.-------------------------------------------------------------
-----------------.++++++++++++++++++++++++++++++++++.+++++++++++++++++++++++
+++++++++++++++++++++++++.-----------------.++++++++.+++++.--------.--------
----------------------------------------------------.+++++++++++++++++++++++
++++++++++++++++++++++++++++++++++.++++++++.[-]+++++++++++++++++++++++++++.+
+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++.------------
----------------------------.++++++++.----------.++++.+++++++++++++++++++.++
+++++++++++++.+++++++++++++++++++++++++++.---------.+++++++++++..-----------
----.+++++++++.-------------------------------------------------------------
-----------------.++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++.+++++++++++++++++++++++.-------------------------------------------
----------------------------------------------.+++++++++++++++++++++++++++++
++++++.+++++++++++++++++++++++++++++++++++++++++.---.---..+++++++++.+++.----
----------.-----------------------------------------------------------------
---.+++++++++++++++++++++++++++++++++++++++++++++++++++++++.++++++++++++++++
++++++++.---.------.--------------------------------------------------------
--------------.++++++++++++++++++++++++++++.++++++++++++++++++++++++++++++++
++++++++++++.++++++++++++..----.--------------------------------------------
----------.-----------..++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++...-----------------------------------------------------
--------------------.+++++++++++++++++++++++++++++++++++++++++++++++++++++.+
++++++++.---.---..+++++++++.+++.--------------.-----------------------------
-------------------------.++++++++++++++++++++++++++++++++++++++++++++++++++
+.+++++++++++++++++++.------------------------------------------------------
---------------.+++++++++++++++++++++++++++++++++++++++++++++++++++.++++.---
.+++++++++++++.+++++.-------------------------------------------------------
---------------.+++++++++++++++.[-]>[-]+++++++++>[-]+++>>[-]>[-]<<<<<[->>>>>
+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<[-]>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<
<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]
>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-
<<+>>]<<<[-]+>>>][-]<[->+<]>[[-<+>]<<<[-]+>>>]<<<[>[-]++++++++++++++++++++++
+++++++++++++++++++++++>[-]<<<<<[->>>>>+<<<<<]>>>>>[[-<<<<<+>>>>>]<+++++++++
++++++++++++++++++++++++++++++++++>]<<<[>>>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<<
->>>][-]++++++++++++++++>[-]++++++++++++++>>>>[-]>[-]<<<<<<<<<[->>>>>>>>>+<<
<<<<<<<]>>>>>>>>>[-<+<<<<<<<<+>>>>>>>>>][-]<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[
[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+
<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>
>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-]<<<<+++++>>>>]>[-]>[-
]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<+<<<<<<<<+>>>>>>>>>][-]+<<[-]+>>
>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<
]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<
[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<
[[-]<<<++++++++++>>>][-]>[-]<<<<<<<<[->>>>>>>>+<<<<<<<<]>>>>>>>>[-<+<<<<<<<+
>>>>>>>>][-]+++++++++++++++++++++++++<<<[-]>>[>>[-]<[->+<]>[-<+<<<+>>>>]<<-]
[-]<<[->>+<<]>>[-<<+<<+>>>>][-]<<<<<<<<[->>>>>>>>+<<<<<<<<]>>>>>>>>[-<<<<<<<
<+>>>>->>>>][-]<<<<<<<<[->>>>>>>>+<<<<<<<<]>>>>>>>>[-<<<<<<<<+>>>>->>>>]>[-]
>[-]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<+<<<<<<<<+>>>>>>>>>][-]++<<[-
]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+
>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>
>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>
]<<<[[-]<<<<----->>>>][-]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<<<<<<<<<
+>>>>>>->>>][-]+++++++++++++++++++++++++++.+++++++++++++++++++++++++++++++++
+++++++++++++++++++++++++++++++.>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>
>>]>>>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[
-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->
>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<
+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<<[-]>>>>>>[-]<[->+<]
>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<<+>>>>>>>]<<[-<<<<<->>>>>]>]<<<[-]>[-]<
<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-]<<[->>
+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>
>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[
-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>
]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]+
+++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-
<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->
>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<
[-]>>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<+>>>>>>]<<[-<<<<->>>>
]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>
>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]
<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[
[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>
[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<
<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>
>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->
[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]
+>>]<]<]<<<]<[-]>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<+>>>>>]<<[
-<<<->>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<
<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>
>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<
<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[-
>>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]<[->+<]>>[-]+<[[-<+>]<+++
+++++++++++++++++++++++++++++++++++++++++++++.<+++++++++++++++++++++++++++++
+++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++++.>>>>-<
]>[[-]>[-]<<<<[->>>>+<<<<]>>>>>[-]+<[[-<<<<+>>>>]<<<<+++++++++++++++++++++++
+++++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++++.
>>>>>>-<]>[[-]<<<<<<++++++++++++++++++++++++++++++++++++++++++++++++.>>>>>>]
<<]<<<<<<--------------------------------.>[-]>[-]<<<<<<[->>>>>>+<<<<<<]>>>>
>>[-<+<<<<<+>>>>>>]>>>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]+++++
+++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<
+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+
<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<<[-]
>>>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<<+>>>>>>>]<<[-<<<<<->>>
>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>
>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[
-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>
>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]
>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<
+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->
>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>
->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[
-]+>>]<]<]<<<]<<[-]>>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<+>>>>
>>]<<[-<<<<->>>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]+++++
+++++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[
[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[
->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+
>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+
<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>]
[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]
+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>
[[-<<<+>>>]<<[-]+>>]<]<]<<<]<[-]>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-
<<<+<<+>>>>>]<<[-<<<->>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>]
[-]++++++++++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<
<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>
[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]
<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]<[->+<]>>
[-]+<[[-<+>]<++++++++++++++++++++++++++++++++++++++++++++++++.<+++++++++++++
+++++++++++++++++++++++++++++++++++.<+++++++++++++++++++++++++++++++++++++++
+++++++++.>>>>-<]>[[-]>[-]<<<<[->>>>+<<<<]>>>>>[-]+<[[-<<<<+>>>>]<<<<+++++++
+++++++++++++++++++++++++++++++++++++++++.<+++++++++++++++++++++++++++++++++
+++++++++++++++.>>>>>>-<]>[[-]<<<<<<++++++++++++++++++++++++++++++++++++++++
++++++++.>>>>>>]<<]<<<<<<+++++++++++++.>[-]>[-]<<<<<<<[->>>>>>>+<<<<<<<]>>>>
>>>[-<+<<<<<<+>>>>>>>][-]+++++++++++++++++++++++++++++++++++++++++++++++++++
+++++++++++++++++++++++++++++++++++++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+
>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>
>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<
+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<[-]+<[[-]>>[-]++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++.<-<]>[[-]<<<<<<.>>>>>>]<[-]<<<<<<<<[->>>>>>>>+<<<
<<<<<]>>>>>>[-]>>[-<<<<<<<<+>>>>>>+>>][-]<<[->>+<<]>>[[-<<+>>]<<->>]<<[<<<..
>>>-]<<<.>>>>>[-]<<<<<<<<[->>>>>>>>+<<<<<<<<]>>>>>>[-]>>[-<<<<<<<<+>>>>>>+>>
][-]<<[->>+<<]>>[[-<<+>>]<<->>]<<[<<<..>>>-]>>>[-]>[-]<<<<<<<[->>>>>>>+<<<<<
<<]>>>>>>>[-<+<<<<<<+>>>>>>>][-]++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>
[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>
+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]
>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<[-]+<[[-]>>[-]+++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
+++++++++++++++++++++++++++++++++.<-<]>[[-]<<<<<<.>>>>>>]<<<<<<<<]>>>[-]<<<<
<[->>>>>+<<<<<]>>>>>[[-<<<<<+>>>>>]<<<<<<<[-]<[-]<[-]>>>>>>>>>>[-]<<<<<[->>>
>>+<<<<<]>>>>>[-<<<<<+<<<+>>>>>>>>][-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>+>>>>>>>>>]<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>>[<<<<+>>>>-]<-
[<<<<+>>>>-]<<<<]<<[-]>>>[<<<+>>>-]<<[>>>>]><<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<<<<<[->>>>>+<<<<
<]>>>>>[[-<<<<<+>>>>>]<<<<<->>>>>]<]<<<<<+>>[-]+>>[-]>[-]<<<<<[->>>>>+<<<<<]
>>>>>[-<+<<<<+>>>>>][-]++++++++++<<[-]>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>
[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<
<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<
<<[-]+>>>][-]<[->+<]>[[-<+>]<<<[-]+>>>]<<<]<<<[-]>[-]+>[-]++>[-]++++++++>[-]
+>[-]+[>>>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++<<[-]>>>[-]>[
-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<-
>->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>
]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]+>>>][-]<[->+<]>[[-<+>]<<<[-]+>>>]<<<[>[-
]<<<<<[->>>>>+<<<<<]>>>>>[[-<<<<<+>>>>>]>[-]>[-]>[-]>>[-]>[-]<<<<<<<<<<[->>>
>>>>>>>+<<<<<<<<<<]>>>>>>>>>>[-<+<<<<<<<<<+>>>>>>>>>>][-]+<<[-]+>>>[-]>[-]<<
<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[
-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<
][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-]<<<[-]
+>[-]+>>]>[-]>[-]<<<<<<<<<<[->>>>>>>>>>+<<<<<<<<<<]>>>>>>>>>>[-<+<<<<<<<<<+>
>>>>>>>>>][-]+++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]
>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[-
>>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->
+<]>[[-<+>]<<<[-]>>>]<<<[[-]<<<[-]+>>[-]+>][-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-
]>>[-]<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>[-]>[-<
<<<<<<<<<<<<<<+>>>>>>>>>>>>>>+>]<[<+>-]>[-]<<<<<<<<<<<<<<[->>>>>>>>>>>>>>+<<
<<<<<<<<<<<<]>>>>>>>>>>>>>[-]>[-<<<<<<<<<<<<<<+>>>>>>>>>>>>>+>]<[<+++>-]>[-]
<<<<<<<<<<<<<[->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>>>>>>>>>>>[-]>[-<<<<<<<<<<<<<+>
>>>>>>>>>>>+>]<[<+++++++++>-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<[-]<[-]<[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>[-]<<[->>+<<]>>[-<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>][-]<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>+<<<<<<<<<
<<<<<<<]>>>>>>>>>>>>>>>>[-<<<<<<<<<<<<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<[<<<[-]<[-]<[-]+>>>>>>[<<<<+>>>>-]<-[<<<<+>>>>-]<<<<]<<[-]>>>[<<<+>>
>-]<<[>>>>]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-]<[-]>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>[-]<<<<<<<<<<<<[->>>>>>>>>>>>+<<<<<<<<<<<<]>>>>>>>>>>>>[-<
<<<<<<<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>][-]<<<<<<<<<<<<<<<
<[->>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>[-<<<<<<<<<<<<<<<<+<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]
<[-]<[-]+>>>>>>[<<<<+>>>>-]<-[<<<<+>>>>-]<<<<]<<[-]>>>[<<<+>>>-]<<[>>>>]>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-]<[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<<<<<<<<<<<[->>>>>>>>>>>+<<<<<<<<<
<<]>>>>>>>>>>>[-<<<<<<<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>][-]<<
<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>[-<<<<<<<<
<<<<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>>[<<<<+>>>>-]<-[<
<<<+>>>>-]<<<<]<<[-]>>>[<<<+>>>-]<<[>>>>]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>+>>>>>>>>>>>>>][-]<<[->>+<<]>>[[-<<+>>]>[-]<<<<<<<<<<<<[->>>>
>>>>>>>>+<<<<<<<<<<<<]>>>>>[-]>>>>>>>[-<<<<<<<<<<<<+>>>>>+>>>>>>>][-]<<<<<<<
<<<<[->>>>>>>>>>>+<<<<<<<<<<<]<[-]>>>>>>>>>>>>[-<<<<<<<<<<<+<+>>>>>>>>>>>>][
-]<<<<<<<[->>>>>>>+<<<<<<<]<<<<[-]>>>>>>>>>>>[-<<<<<<<+<<<<+>>>>>>>>>>>]<<<<
<<<<<<->[-]>+>>>>>>>][-]<[->+<]>[[-<+>]>[-]<<<<<<<<<<<<[->>>>>>>>>>>>+<<<<<<
<<<<<<]>>>>>[-]>>>>>>>[-<<<<<<<<<<<<+>>>>>+>>>>>>>][-]<<<<<<<<<<<<<[->>>>>>>
>>>>>>+<<<<<<<<<<<<<]>[-]>>>>>>>>>>>>[-<<<<<<<<<<<<<+>+>>>>>>>>>>>>][-]<<<<<
<<[->>>>>>>+<<<<<<<]<<<<<<[-]>>>>>>>>>>>>>[-<<<<<<<+<<<<<<+>>>>>>>>>>>>>]<<<
<<<<<<<->[-]>+>>>>>>>]<<<<]>[-]>[-]<<<<<<[->>>>>>+<<<<<<]>>>>>>[-<+<<<<<+>>>
>>>][-]++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<
<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<
]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-
<+>]<<<[-]>>>]<<<[[-]>>>>[-]++>>[-]>[-]<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>+<<<<
<<<<<<<<<<<]>>>>>>>>>>>>>>>[-<+<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>][-]<<[-]+>>>[-
]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[
<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]
+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-
]>[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>[-]>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>]<]>[-]>[-]<<<<<<<<<<<<<<<[-
>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>[-<+<<<<<<<<<<<<<<+>>>>>>>>>>
>>>>>][-]+<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-
<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<
<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[
-<+>]<<<[-]>>>]<<<[[-]>[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>>[-<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>+>>>>]<]>[-]>[-]<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>+<<<
<<<<<<<<<<<<]>>>>>>>>>>>>>>>[-<+<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>][-]++<<[-]+>>
>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<
]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<
[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<
[[-]>[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>[-]>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>]<]>[-]
>[-]<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>[-<+<<<<
<<<<<<<<<<+>>>>>>>>>>>>>>>][-]<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-
]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<
+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<
[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-]<[-]>>>
>>>>>>>>>>[-]>>>>>[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<
<<<[<<<[-]<[-]<[-]+>>>>>-[<<<<+>>>>-]<<<<]<<[->>+>+<<<]>>[-<<+>>]<[>>[->>>>+
<<<<]<<>>>>]>>[->>>>>>>>>>>+<<<<<<<<<<<]>>>>>>>>>>>>>>>]>[-]>[-]<<<<<<<<<<<<
<<<[->>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>[-<+<<<<<<<<<<<<<<+>>>>>
>>>>>>>>>>][-]+<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>
>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->
>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+
<]>[[-<+>]<<<[-]>>>]<<<[[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-]<[-]>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>[-]>>>>>[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>-[<<<<+>>>>-]
<<<<]<<[->>+>+<<<]>>[-<<+>>]<[>>[->>>>+<<<<]<<>>>>]>>[->>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]>[-]>[-]<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>
>+<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>[-<+<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>][-]++<<[
-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]
+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>
>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>
>]<<<[[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-
]<[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>>>[-]<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>-[<<<<+>>>>-]<<<<]<<
[->>+>+<<<]>>[-<<+>>]<[>>[->>>>+<<<<]<<>>>>]>>[->>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]>[-]>[-]<<<<<<<<<
<<<<[->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>>>>>>>>>>>>[-<+<<<<<<<<<<<<+>>>>>>>>>>>>
>][-]<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>
>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>
[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]
<<<[-]>>>]<<<[[-]<<<<<<<<<<<<<<<[-]<[-]<[-]>>>>>>>>>>>>>>>>>>[-]<<<<<[->>>>>
+<<<<<]>>>>>[-<<<<<+<<<<<<<<<<<+>>>>>>>>>>>>>>>>][-]<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>
>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>>[<<<<+>>>>-]<-[<<<<+
>>>>-]<<<<]<<[-]>>>[<<<+>>>-]<<[>>>>]><<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]>[-]>[-]<<<<<<<<<<
<<<[->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>>>>>>>>>>>>[-<+<<<<<<<<<<<<+>>>>>>>>>>>>>
][-]+<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>
>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>
[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]
<<<[-]>>>]<<<[[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[-]<[-]<[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]
<<<<<[->>>>>+<<<<<]>>>>>[-<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>][-]
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>>[<<<<+>>>>-]<-[<<<<+>>>>-]<<<<
]<<[-]>>>[<<<+>>>-]<<[>>>>]><<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]>[-]>[-]<<<<<<<<<<<<<[
->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>>>>>>>>>>>>[-<+<<<<<<<<<<<<+>>>>>>>>>>>>>][-]
++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]
<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-
<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<
[-]>>>]<<<[[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[-]<[-
]<[-]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<<<<<[->>
>>>+<<<<<]>>>>>[-<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>][-]<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>>[<<<<+>>>>-]<-[<<<<+>>>>-]<<
<<]<<[-]>>>[<<<+>>>-]<<[>>>>]><<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>]>[-]>[-]<<<<<<<<<<<<<[->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>>>>>>>>>
>>>[-<+<<<<<<<<<<<<+>>>>>>>>>>>>>][-]<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+
>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>
>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<
+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-]>[-]<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<]>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>[-<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>+>>>]<]>[-]>[-]<<<<<<<<<<<<<[->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>
>>>>>>>>>>>[-<+<<<<<<<<<<<<+>>>>>>>>>>>>>][-]+<<[-]+>>>[-]>[-]<<<[->>>+<<<]>
>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->
>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<
<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-]>[-]<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>[-]>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+>>>]<]>[-]>[-]
<<<<<<<<<<<<<[->>>>>>>>>>>>>+<<<<<<<<<<<<<]>>>>>>>>>>>>>[-<+<<<<<<<<<<<<+>>>
>>>>>>>>>>][-]++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]
>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[-
>>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->
+<]>[[-<+>]<<<[-]>>>]<<<[[-]>[-]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>[-<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>+>>>]<]<[->>>>[-]<<<<[->>>>+<<<<]>>>>>[-]+<[[-<<<<+>>>>]>>[-]<<
<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>[-]>>>>
>[-<<<<<<<<<<<<<<<<<<+>>>>>>>>>>>>>+>>>>>][-]<<<<<<<<[->>>>>>>>+<<<<<<<<]>>>
>[-]>>>>[-<<<<<<<<+>>>>+>>>>]<<<[-]++++++++++++++++++++++++++++++++>>-<]>[[-
]>[-]<<<<<<<<<<<<<<<<[->>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<]>>>>>>>>>>>[-]>>>>>
[-<<<<<<<<<<<<<<<<+>>>>>>>>>>>+>>>>>][-]<<<<<<<[->>>>>>>+<<<<<<<]>>>[-]>>>>[
-<<<<<<<+>>>+>>>>]<<<[-]++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++>>]<[-]++++++++++++++++>[-]+++++++++++++
+>>>>[-]>[-]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<+<<<<<<<<+>>>>>>>>>][
-]<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]
<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-
<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<
[-]>>>]<<<[[-]<<<<+++++>>>>]>[-]>[-]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>
[-<+<<<<<<<<+>>>>>>>>>][-]+<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<
<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>
>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]
>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[[-]<<<++++++++++>>>][-]>[-]<<<<<<<<[->>>
>>>>>+<<<<<<<<]>>>>>>>>[-<+<<<<<<<+>>>>>>>>][-]+++++++++++++++++++++++++<<<[
-]>>[>>[-]<[->+<]>[-<+<<<+>>>>]<<-][-]<<[->>+<<]>>[-<<+<<+>>>>][-]<<<<<<<<<<
<[->>>>>>>>>>>+<<<<<<<<<<<]>>>>>>>>>>>[-<<<<<<<<<<<+>>>>>>>->>>>][-]<<<<<<<<
<<<[->>>>>>>>>>>+<<<<<<<<<<<]>>>>>>>>>>>[-<<<<<<<<<<<+>>>>>>>->>>>]>[-]>[-]<
<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<+<<<<<<<<+>>>>>>>>>][-]++<<[-]+>>>
[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]
<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[
-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<<[
[-]<<<<----->>>>][-]<<<<<<[->>>>>>+<<<<<<]>>>>>>[-<<<<<<+>>>->>>][-]++++++++
+++++++++++++++++++.++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++.>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>]>>>[-]>[-]<<<<<[->>>
>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>
+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<
[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]
>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<<[-]>>>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<
<]>>>[-<<<+<<<<+>>>>>>>]<<[-<<<<<->>>>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>
[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[
-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<
]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<
<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<
<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<
<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+
<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>
>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<[-]>>>>>[-]<[->+<]>[[-<
+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<+>>>>>>]<<[-<<<<->>>>]>]<<<[-]>[-]<<<<<[->>>
>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>
[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+
>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>
>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<
<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++
>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>
]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]
>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<[-]>>>>[-]
<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<+>>>>>]<<[-<<<->>>]>]<<<[-]>[-]<<
<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-]<<[->>+
<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>
>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-
]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]
<[[-]<<<<<<<+>>>>>>>]<<<][-]<[->+<]>>[-]+<[[-<+>]<++++++++++++++++++++++++++
++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++++.<++
++++++++++++++++++++++++++++++++++++++++++++++.>>>>-<]>[[-]>[-]<<<<[->>>>+<<
<<]>>>>>[-]+<[[-<<<<+>>>>]<<<<++++++++++++++++++++++++++++++++++++++++++++++
++.<++++++++++++++++++++++++++++++++++++++++++++++++.>>>>>>-<]>[[-]<<<<<<+++
+++++++++++++++++++++++++++++++++++++++++++++.>>>>>>]<<]<<<<<<--------------
------------------.>[-]>[-]<<<<<<[->>>>>>+<<<<<<]>>>>>>[-<+<<<<<+>>>>>>]>>>[
-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->
>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]
>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>
[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<<[-]>>>>>>[-]<[->+<]>[[-<+>
]>[-]<<<[->>>+<<<]>>>[-<<<+<<<<+>>>>>>>]<<[-<<<<<->>>>>]>]<<<[-]>[-]<<<<<[->
>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-
]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<
<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[-
>>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<
<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++
++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>
>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<
<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<[-]>>>>
>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<+>>>>>>]<<[-<<<<->>>>]>]<<<[
-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-
]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>
>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+
>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>
>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>
>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]
>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]
<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<
]<<<]<[-]>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<+>>>>>]<<[-<<<->>
>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>
>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-
]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>
[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>
>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]<[->+<]>>[-]+<[[-<+>]<++++++++++
++++++++++++++++++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++
++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++++.>>>>-<]>[[-]>
[-]<<<<[->>>>+<<<<]>>>>>[-]+<[[-<<<<+>>>>]<<<<++++++++++++++++++++++++++++++
++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++++.>>>>>>-
<]>[[-]<<<<<<++++++++++++++++++++++++++++++++++++++++++++++++.>>>>>>]<<]<<<<
<<+++++++++++++.>[-]>[-]<<<<<<<[->>>>>>>+<<<<<<<]>>>>>>>[-<+<<<<<<+>>>>>>>][
-]++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++<<[-]+>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>
>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>
>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<
]>[[-<+>]<<<[-]>>>]<<[-]+<[[-]>>[-]+++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
+++.<-<]>[[-]<<<<<<.>>>>>>]<[-]<<<<<<<<<<<[->>>>>>>>>>>+<<<<<<<<<<<]>>>>>>>>
>[-]>>[-<<<<<<<<<<<+>>>>>>>>>+>>][-]<<[->>+<<]>>[[-<<+>>]<<->>]<<[<<<..>>>-]
<<<.>>>>>[-]<<<<<<<<<<<[->>>>>>>>>>>+<<<<<<<<<<<]>>>>>>>>>[-]>>[-<<<<<<<<<<<
+>>>>>>>>>+>>][-]<<[->>+<<]>>[[-<<+>>]<<->>]<<[<<<..>>>-]>>>[-]>[-]<<<<<<<[-
>>>>>>>+<<<<<<<]>>>>>>>[-<+<<<<<<+>>>>>>>][-]+++++++++++++++++++++++++++++++
+++++++++++++++++++++++++++++++++++++++++++++++++++++++++<<[-]+>>>[-]>[-]<<<
[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-
]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]
[-]<<[->>+<<]>>[[-<<+>>]<<<[-]>>>][-]<[->+<]>[[-<+>]<<<[-]>>>]<<[-]+<[[-]>>[
-]++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++.<-<]>[[-]<<<<<<.>>>>>>]<<<<<<
<<<]>[-]++++++++++.[-]+>[-]+>[-]+++++++++++++++++++++++++++.++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++.>[-]>[-]<<<[->>>+<<<]>>>[-<
+<<+>>>]>>>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<
[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<
<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[
-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<<[-]>>>>>>[-]<[
->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<<+>>>>>>>]<<[-<<<<<->>>>>]>]<<<[-]
>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>[-]<
<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+
<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>
>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<+>>]
<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>
][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>
>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<
<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<
<<]<<[-]>>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<+>>>>>>]<<[-<<<<
->>>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[
-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>
]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]
>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+
<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>
[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<
[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<
->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]
<<[-]+>>]<]<]<<<]<[-]>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<+>>>>
>]<<[-<<<->>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++
++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<
<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>
>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-
]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]<[->+<]>>[-]+<[[-<+>
]<++++++++++++++++++++++++++++++++++++++++++++++++.<++++++++++++++++++++++++
++++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++++.>
>>>-<]>[[-]>[-]<<<<[->>>>+<<<<]>>>>>[-]+<[[-<<<<+>>>>]<<<<++++++++++++++++++
++++++++++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++
++++.>>>>>>-<]>[[-]<<<<<<++++++++++++++++++++++++++++++++++++++++++++++++.>>
>>>>]<<]<<<<<<--------------------------------.>[-]>[-]<<<<[->>>>+<<<<]>>>>[
-<+<<<+>>>>]>>>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++>[
-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>
[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>
>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<]<<<]<<<[-]>>>>>>[
-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<<+>>>>>>>]<<[-<<<<<->>>>>]>]<<
<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<<<<[-]>>>>[>>>
[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[-
>>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<
<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[->>+<<]>>[[-<<
+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>
>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<
<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[
-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<
]<]<<<]<<[-]>>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<<+>>>>>>]<<[-
<<<<->>>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++++++++<<
<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+
>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<[->>>>+<
<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]+>[-]<<[
->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]>[-]<<<<<[->>>>>+<<<<<]>
>>>>[-<+<<<<+>>>>>][-]++++++++++>[-]<<[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]
<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<
[<<<->>->[-]>[-]<<<<[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+
>>>]<<[-]+>>]<]<]<<<]<[-]>>>>[-]<[->+<]>[[-<+>]>[-]<<<[->>>+<<<]>>>[-<<<+<<+
>>>>>]<<[-<<<->>>]>]<<<[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<<<+>>>>>][-]++++
++++++<<<<<[-]>>>>[>>>[-]<<[->>+<<]>[-]>[-<<+>+>][-]>[-]<<<<[->>>>+<<<<]>>>>
[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<<->>->[-]>[-]<<<<
[->>>>+<<<<]>>>>[[-<<<<+>>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]
+>[-]<<[->>+<<]>>[[-<<+>>]<[-]>]<[[-]<<<<<<<+>>>>>>>]<<<][-]<[->+<]>>[-]+<[[
-<+>]<++++++++++++++++++++++++++++++++++++++++++++++++.<++++++++++++++++++++
++++++++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++++++++
++.>>>>-<]>[[-]>[-]<<<<[->>>>+<<<<]>>>>>[-]+<[[-<<<<+>>>>]<<<<++++++++++++++
++++++++++++++++++++++++++++++++++.<++++++++++++++++++++++++++++++++++++++++
++++++++.>>>>>>-<]>[[-]<<<<<<+++++++++++++++++++++++++++++++++++++++++++++++
+.>>>>>>]<<]<<<<<<+++++++++++++.<<[-]+++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
+++++++++[>[-]++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++[>[-]+++++++++
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
+++++++++++++++[-]<-]<-]<<<<<]<<<<+>>>>[-]>[-]<<<<<[->>>>>+<<<<<]>>>>>[-<+<<
<<+>>>>>][-]++++<<[-]>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>
>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->
>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<<[->>+<<]>>[[-<<+>>]<<<[-]+>>>][-]<[->
+<]>[[-<+>]<<<[-]+>>>]<<<]<<->>[-]<<[->>+<<]>>[[-<<+>>]<<<<<<<<-<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[-]<[-]<[-]>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>>>>>>[-]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>
>>>>>>>>[-<<<<<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<+>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>-[<<<<+>
>>>-]<<<<]<<[->>+>+<<<]>>[-<<+>>]<[>>[->>>>+<<<<]<<>>>>]>>[->>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-]<[-]>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>[-]>>>>>[-]<<<<<<<<<[->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<<<<<<<<<+<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>>>
-[<<<<+>>>>-]<<<<]<<[->>+>+<<<]>>[-<<+>>]<[>>[->>>>+<<<<]<<>>>>]>>[->>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]<[-]<[-
]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>[-]>>>>[-]<<<<<<<<<[
->>>>>>>>>+<<<<<<<<<]>>>>>>>>>[-<<<<<<<<<+<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<+>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>]<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<[<<<[-]<[-]<[-]+>>>
>>-[<<<<+>>>>-]<<<<]<<[->>+>+<<<]>>[-<<+>>]<[>>[->>>>+<<<<]<<>>>>]>>[->>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>+<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
<<<<<<<<<<<<<<<<<<<<<<<<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[-]>[-]>>>>>>>[-]++++++++>[-]>[-]<<<<<<<<<<<[->>>>>>>>>>>+<<<<<<<<<<<]>>>>>>
>>>>>[-<+<<<<<<<<<<+>>>>>>>>>>>]<<<[-]>>>[-]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]>
[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<<<]>>>[[-<
<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<[->+<]>[[-<+>]<<<[-]+
>>>]<<<[<<<<<<<<--------->>+>>>>>>>[-]++++++++>[-]>[-]<<<<<<<<<<<[->>>>>>>>>
>>+<<<<<<<<<<<]>>>>>>>>>>>[-<+<<<<<<<<<<+>>>>>>>>>>>]<<<[-]>>>[-]>[-]<<<[->>
>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-
]<<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<
[->+<]>[[-<+>]<<<[-]+>>>]<<<]>[-]++>[-]>[-]<<<<<<<<<<<[->>>>>>>>>>>+<<<<<<<<
<<<]>>>>>>>>>>>[-<+<<<<<<<<<<+>>>>>>>>>>>]<<<[-]>>>[-]>[-]<<<[->>>+<<<]>>>[[
-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<<<[->>>+<
<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<[->+<]>[[-<
+>]<<<[-]+>>>]<<<[<<<<<<<<--->+>>>>>>>>[-]++>[-]>[-]<<<<<<<<<<<[->>>>>>>>>>>
+<<<<<<<<<<<]>>>>>>>>>>>[-<+<<<<<<<<<<+>>>>>>>>>>>]<<<[-]>>>[-]>[-]<<<[->>>+
<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<[<<->->[-]>[-]<
<<[->>>+<<<]>>>[[-<<<+>>>]>[-]<<<[->>>+<<<]>>>[[-<<<+>>>]<<[-]+>>]<]<][-]<[-
>+<]>[[-<+>]<<<[-]+>>>]<<<]<<<<+>>>]<<]>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>

実行

prompt> ./Brainfuck3 Hanoi.bf

prompt> ./Bf2c Hanoi.bf > Hanoi.c
prompt> gcc -o Hanoi Hanoi.c
prompt> ./Hanoi
5
5
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
5
5