I am trying to use the safecopy haskell library, but when I try to migrate a string to a bytestring, the last 4 characters are lost and 4 '\NULL' characters get prepended to the string:
{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, TypeFamilies #-}
import Data.SafeCopy
import Data.Acid
import Data.Typeable
import Control.Monad.State.Class
import Control.Monad.Reader.Class
data T = T { str :: String }
deriving (Show, Typeable)
getT :: Query T String
getT = fmap str ask
setT :: String -> Update T ()
setT str = put $ T str
deriveSafeCopy 0 'base ''T
makeAcidic ''T ['setT, 'getT]
main :: IO ()
main = do
state <- openLocalState (T "string set with default")
update state (SetT "string set with SetT")
str <- query state GetT
putStrLn str
This outputs: string set with SetT
, but when you run the following modificated version after that:
{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, TypeFamilies #-}
import Data.SafeCopy
import Data.Acid
import Data.Typeable
import Control.Monad.State.Class
import Control.Monad.Reader.Class
import Data.ByteString.Char8 as B
data T_v0 = T_v0 String
deriving (Show, Typeable)
deriveSafeCopy 0 'base ''T_v0
data T = T { str :: B.ByteString }
deriving (Show, Typeable)
deriveSafeCopy 1 'extension ''T
instance Migrate T where
type MigrateFrom T = T_v0
migrate (T_v0 str) = T $ B.pack str
getT :: Query T B.ByteString
getT = fmap str ask
setT :: B.ByteString -> Update T ()
setT str = put $ T str
makeAcidic ''T ['setT, 'getT]
main :: IO ()
main = do
state <- openLocalState (T $ B.pack "bytestring set with default")
str <- query state GetT
print str
it outputs: "\NUL\NUL\NUL\NULstring set with "
. I have no idea why this is happening. Am I doing something wrong in the migration step? I have tried to stay as close as possible to the example code. Does anyone know why this is happening?
P.S: Sorry for the big amount of code, but I couldn't think of any better way to convey the problem.
It's because of acid-state
. You've changed the types of getT
and setT
between the implementations which messes up the transaction log. You essentially cannot change any functions you've tagged with makeAcidic
without first clearing the transaction log with createCheckpoint
(using the older version of the codebase).