\begin{comment}
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE RankNTypes #-}
module LiveCoding.Migrate where
import Control.Arrow ((&&&))
import Control.Monad (guard)
import Data.Data
import Data.Function ((&))
import Data.Functor ((<&>))
import Data.Maybe
import Prelude hiding (GT)
import Control.Monad.Trans.Class
import Control.Monad.Trans.State
import Data.Generics.Aliases
import Data.Generics.Twins
import LiveCoding.Migrate.Debugger
import LiveCoding.Migrate.Cell
import LiveCoding.Migrate.Monad.Trans
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
<> migrationCell
<> newtypeMigration
<> migrationState
treeMigration :: Migration -> Migration
treeMigration specific
= specific
<> sameConstructorMigration specific
<> constructorMigration specific
matchingAlgebraicDataTypes :: (Data a, Data b) => a -> b -> Bool
matchingAlgebraicDataTypes a b
= isAlgType typeA
&& isAlgType typeB
&& dataTypeName typeA == dataTypeName typeB
where
typeA = dataTypeOf a
typeB = dataTypeOf b
sameConstructorMigration :: Migration -> Migration
sameConstructorMigration specific = Migration $ \a b -> do
guard $ matchingAlgebraicDataTypes a b
let
constrA = toConstr a
constrB = toConstr b
guard $ showConstr constrA == showConstr constrB
let
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
return migrateSameConstr
constructorMigration :: Migration -> Migration
constructorMigration specific = Migration $ \a b -> do
let
constrB = toConstr b
constrFieldsB = constrFields constrB
guard $ matchingAlgebraicDataTypes a b
matchingConstructor <- dataTypeOf a
& dataTypeConstrs
& map (show &&& id)
& lookup (showConstr constrB)
let matchingConstructorFields = constrFields matchingConstructor
fieldSetters <- if null constrFieldsB || null matchingConstructorFields
then
return $ getChildrenMaybe b
else
getChildrenMaybe b
& zip constrFieldsB
& flip lookup
& flip map matchingConstructorFields
& sequence
flip evalStateT fieldSetters $ fromConstrM tryOneField matchingConstructor
tryOneField :: Data a => StateT [GenericR' Maybe] Maybe a
tryOneField = do
(field : fields) <- get
put fields
lift $ unGR field
getChildrenSetters :: Data a => Migration -> a -> [GenericT']
getChildrenSetters specific = gmapQ $ \child -> GT $ flip (runSafeMigration $ treeMigration specific) child
newtype GenericR' m = GR { unGR :: GenericR m }
getChildrenMaybe :: Data a => a -> [GenericR' Maybe]
getChildrenMaybe = gmapQ $ \child -> GR $ cast 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}