-- | Tests for preprocessing. module Test.Preprocess ( unit_Sample_preprocess ) where import Prelude hiding (EQ) import Test.HUnit (Assertion, (@?=)) import Michelson.Preprocess import Michelson.Text import qualified Michelson.Typed as T import Michelson.Typed.Instr unit_Sample_preprocess :: Assertion unit_Sample_preprocess = do transformStrings False (f (mkMTextUnsafe . toText)) (sample (T.VString . mkMTextUnsafe)) @?= (expected (T.VString . mkMTextUnsafe)) transformBytes False (f fromString) (sample T.VBytes) @?= (expected T.VBytes) where f :: (Eq a) => (String -> a) -> a -> a f fn s | s == (fn str1) = (fn str5) | s == (fn str2) = (fn str4) | s == (fn str4) = (fn str2) | s == (fn str5) = (fn str1) | otherwise = s sample :: (IsString i, T.ConstantScope o, Typeable o) => (i -> T.Value o) -> T.ContractCode o o sample fn = CAR `Seq` PUSH (fn str1) `Seq` DIP (PUSH (fn str2)) `Seq` LEFT @('T.TKey) `Seq` IF_LEFT Nop (PUSH (fn str4) `Seq` FAILWITH) `Seq` DIP (DIP (PUSH (fn str5))) `Seq` PUSH (fn str3) `Seq` DROP `Seq` DROP `Seq` DROP `Seq` DROP `Seq` NIL `Seq` PAIR expected :: (IsString i, T.ConstantScope o, Typeable o) => (i -> T.Value o) -> T.ContractCode o o expected fn = CAR `Seq` PUSH (fn str5) `Seq` DIP (PUSH (fn str4)) `Seq` LEFT @('T.TKey) `Seq` IF_LEFT Nop (PUSH (fn str2) `Seq` FAILWITH) `Seq` DIP (DIP (PUSH (fn str1))) `Seq` PUSH (fn str3) `Seq` DROP `Seq` DROP `Seq` DROP `Seq` DROP `Seq` NIL `Seq` PAIR str1, str2, str3, str4, str5 :: (IsString a) => a str1 = "aa" str2 = "ls" str3 = "gulya" str4 = "naiks" str5 = "eek"