\begin{comment}
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE RankNTypes #-}
module LiveCoding.Migrate where
import Data.Data
import Data.Functor ((<&>))
import Data.Maybe
import Prelude hiding (GT)
import Data.Generics.Aliases
import Data.Generics.Twins
import LiveCoding.Migrate.Debugger
import LiveCoding.Migrate.Migration
\end{code}
\end{comment}
\begin{code}
migrate :: (Data a, Data b) => a -> b -> a
migrate = migrateWith standardMigration
migrateWith :: (Data a, Data b) => Migration -> a -> b -> a
migrateWith specific = runSafeMigration $ treeMigration specific
standardMigration :: Migration
standardMigration = castMigration <> migrationDebugging <> newtypeMigration
treeMigration :: Migration -> Migration
treeMigration migration = Migration $ treeMigrateWith migration
treeMigrateWith
:: (Data a, Data b)
=> Migration
-> a -> b -> Maybe a
treeMigrateWith specific a b
| Just a' <- runMigration specific a b
= Just a'
treeMigrateWith specific a b
| isAlgType typeA && isAlgType typeB
&& show typeA == show typeB
&& showConstr constrA == showConstr constrB
= Just migrateSameConstr
where
typeA = dataTypeOf a
typeB = dataTypeOf b
constrA = toConstr a
constrB = toConstr b
constrFieldsA = constrFields constrA
constrFieldsB = constrFields constrB
migrateSameConstr
| (not $ null constrFieldsA)
&& (not $ null constrFieldsB)
= setChildren getFieldSetters a
| otherwise = setChildren (getChildrenSetters specific b) a
settersB = zip constrFieldsB $ getChildrenSetters specific b
getFieldSetters = constrFieldsA <&>
\field -> fromMaybe (GT id)
$ lookup field settersB
treeMigrateWith _ _ _ = Nothing
getChildrenSetters :: Data a => Migration -> a -> [GenericT']
getChildrenSetters specific = gmapQ $ \child -> GT $ flip (runSafeMigration $ treeMigration specific) child
setChildren :: Data a => [GenericT'] -> a -> a
setChildren updates a = snd $ gmapAccumT f updates a
where
f [] e = ([], e)
f (update : updates) e = (updates, unGT update $ e)
\end{code}