module Michelson.Preprocess
( transformStrings
, transformBytes
) where
import Data.Default (def)
import Michelson.Text (MText)
import Michelson.Typed
transformStrings :: Bool -> (MText -> MText) -> Instr inp out -> Instr inp out
transformStrings :: Bool -> (MText -> MText) -> Instr inp out -> Instr inp out
transformStrings goToValues :: Bool
goToValues f :: MText -> MText
f = Bool
-> (forall (t :: T). Value t -> Value t)
-> Instr inp out
-> Instr inp out
forall (inp :: [T]) (out :: [T]).
Bool
-> (forall (t :: T). Value t -> Value t)
-> Instr inp out
-> Instr inp out
transformConstants Bool
goToValues forall (t :: T). Value t -> Value t
mapStr
where
mapStr :: Value t -> Value t
mapStr :: Value t -> Value t
mapStr = \case
VString str :: MText
str -> MText -> Value t
forall (instr :: [T] -> [T] -> *). MText -> Value' instr 'TString
VString (MText -> Value t) -> MText -> Value t
forall a b. (a -> b) -> a -> b
$ MText -> MText
f MText
str
v :: Value t
v -> Value t
v
transformBytes :: Bool -> (ByteString -> ByteString) -> Instr inp out -> Instr inp out
transformBytes :: Bool
-> (ByteString -> ByteString) -> Instr inp out -> Instr inp out
transformBytes goToValues :: Bool
goToValues f :: ByteString -> ByteString
f = Bool
-> (forall (t :: T). Value t -> Value t)
-> Instr inp out
-> Instr inp out
forall (inp :: [T]) (out :: [T]).
Bool
-> (forall (t :: T). Value t -> Value t)
-> Instr inp out
-> Instr inp out
transformConstants Bool
goToValues forall (t :: T). Value t -> Value t
mapBytes
where
mapBytes :: Value t -> Value t
mapBytes :: Value t -> Value t
mapBytes = \case
VBytes bytes :: ByteString
bytes -> ByteString -> Value t
forall (instr :: [T] -> [T] -> *).
ByteString -> Value' instr 'TBytes
VBytes (ByteString -> Value t) -> ByteString -> Value t
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
f ByteString
bytes
v :: Value t
v -> Value t
v
transformConstants ::
forall inp out.
Bool
-> (forall t. Value t -> Value t)
-> Instr inp out
-> Instr inp out
transformConstants :: Bool
-> (forall (t :: T). Value t -> Value t)
-> Instr inp out
-> Instr inp out
transformConstants dsGoToValues :: Bool
dsGoToValues f :: forall (t :: T). Value t -> Value t
f = (Instr inp out, ()) -> Instr inp out
forall a b. (a, b) -> a
fst ((Instr inp out, ()) -> Instr inp out)
-> (Instr inp out -> (Instr inp out, ()))
-> Instr inp out
-> Instr inp out
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DfsSettings ()
-> (forall (i :: [T]) (o :: [T]). Instr i o -> (Instr i o, ()))
-> Instr inp out
-> (Instr inp out, ())
forall x (inp :: [T]) (out :: [T]).
Semigroup x =>
DfsSettings x
-> (forall (i :: [T]) (o :: [T]). Instr i o -> (Instr i o, x))
-> Instr inp out
-> (Instr inp out, x)
dfsInstr DfsSettings ()
forall a. Default a => a
def{ Bool
dsGoToValues :: Bool
dsGoToValues :: Bool
dsGoToValues } forall (i :: [T]) (o :: [T]). Instr i o -> (Instr i o, ())
step
where
step :: forall i o. Instr i o -> (Instr i o, ())
step :: Instr i o -> (Instr i o, ())
step = (,()) (Instr i o -> (Instr i o, ()))
-> (Instr i o -> Instr i o) -> Instr i o -> (Instr i o, ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
PUSH v :: Value' Instr t
v -> Value' Instr t -> Instr i (t : i)
forall (t :: T) (s :: [T]).
ConstantScope t =>
Value' Instr t -> Instr s (t : s)
PUSH ((forall (t :: T). Value t -> Value t)
-> Value' Instr t -> Value' Instr t
forall (t :: T).
(forall (t :: T). Value t -> Value t) -> Value t -> Value t
dfsModifyValue forall (t :: T). Value t -> Value t
f Value' Instr t
v)
i :: Instr i o
i -> Instr i o
i