{-# LANGUAGE RecordWildCards #-}
module LiveCoding.Migrate.Cell where
import Data.Data
import Data.Generics.Aliases
import LiveCoding.Cell
import LiveCoding.Exceptions
import LiveCoding.Migrate.Migration
maybeMigrateToComposition1
:: (Typeable state1', Typeable state1)
=> Composition state1 state2
-> state1'
-> Maybe (Composition state1 state2)
maybeMigrateToComposition1 (Composition (_, state2)) state1' = do
state1 <- cast state1'
return $ Composition (state1, state2)
migrationToComposition1 :: Migration
migrationToComposition1 = migrationTo2 maybeMigrateToComposition1
maybeMigrateFromComposition1
:: (Typeable state1', Typeable state1)
=> Composition state1 state2
-> Maybe state1'
maybeMigrateFromComposition1 (Composition (state1, _)) = cast state1
migrationFromComposition1 :: Migration
migrationFromComposition1 = constMigrationFrom2 maybeMigrateFromComposition1
maybeMigrateToComposition2
:: (Typeable state2', Typeable state2)
=> Composition state1 state2
-> state2'
-> Maybe (Composition state1 state2)
maybeMigrateToComposition2 (Composition (state1, _)) state2' = do
state2 <- cast state2'
return $ Composition (state1, state2)
migrationToComposition2 :: Migration
migrationToComposition2 = migrationTo2 maybeMigrateToComposition2
maybeMigrateFromComposition2
:: (Typeable state2', Typeable state2)
=> Composition state1 state2
-> Maybe state2'
maybeMigrateFromComposition2 (Composition (_, state2)) = cast state2
migrationFromComposition2 :: Migration
migrationFromComposition2 = constMigrationFrom2 maybeMigrateFromComposition2
migrationComposition :: Migration
migrationComposition
= migrationToComposition1
<> migrationFromComposition1
<> migrationToComposition2
<> migrationFromComposition2
maybeMigrateToParallel1
:: (Typeable state1', Typeable state1)
=> Parallel state1 state2
-> state1'
-> Maybe (Parallel state1 state2)
maybeMigrateToParallel1 (Parallel (_, state2)) state1' = do
state1 <- cast state1'
return $ Parallel (state1, state2)
migrationToParallel1 :: Migration
migrationToParallel1 = migrationTo2 maybeMigrateToParallel1
maybeMigrateFromParallel1
:: (Typeable state1', Typeable state1)
=> Parallel state1 state2
-> Maybe state1'
maybeMigrateFromParallel1 (Parallel (state1, _)) = cast state1
migrationFromParallel1 :: Migration
migrationFromParallel1 = constMigrationFrom2 maybeMigrateFromParallel1
maybeMigrateToParallel2
:: (Typeable state2', Typeable state2)
=> Parallel state1 state2
-> state2'
-> Maybe (Parallel state1 state2)
maybeMigrateToParallel2 (Parallel (state1, _)) state2' = do
state2 <- cast state2'
return $ Parallel (state1, state2)
migrationToParallel2 :: Migration
migrationToParallel2 = migrationTo2 maybeMigrateToParallel2
maybeMigrateFromParallel2
:: (Typeable state2', Typeable state2)
=> Parallel state1 state2
-> Maybe state2'
maybeMigrateFromParallel2 (Parallel (_, state2)) = cast state2
migrationFromParallel2 :: Migration
migrationFromParallel2 = constMigrationFrom2 maybeMigrateFromParallel2
migrationParallel :: Migration
migrationParallel
= migrationToParallel1
<> migrationFromParallel1
<> migrationToParallel2
<> migrationFromParallel2
maybeMigrateToChoice1
:: (Typeable stateLeft', Typeable stateLeft)
=> Choice stateLeft stateRight
-> stateLeft'
-> Maybe (Choice stateLeft stateRight)
maybeMigrateToChoice1 Choice { .. } choiceLeft' = do
choiceLeft <- cast choiceLeft'
return Choice { .. }
migrationToChoice1 :: Migration
migrationToChoice1 = migrationTo2 maybeMigrateToChoice1
maybeMigrateFromChoice1
:: (Typeable stateLeft', Typeable stateLeft)
=> Choice stateLeft stateRight
-> Maybe stateLeft'
maybeMigrateFromChoice1 Choice { .. } = cast choiceLeft
migrationFromChoice1 :: Migration
migrationFromChoice1 = constMigrationFrom2 maybeMigrateFromChoice1
maybeMigrateToChoice2
:: (Typeable stateRight', Typeable stateRight)
=> Choice stateLeft stateRight
-> stateRight'
-> Maybe (Choice stateLeft stateRight)
maybeMigrateToChoice2 Choice { .. } choiceRight' = do
choiceRight <- cast choiceRight'
return Choice { .. }
migrationToChoice2 :: Migration
migrationToChoice2 = migrationTo2 maybeMigrateToChoice2
maybeMigrateFromChoice2
:: (Typeable stateRight', Typeable stateRight)
=> Choice stateLeft stateRight
-> Maybe stateRight'
maybeMigrateFromChoice2 Choice { .. } = cast choiceRight
migrationFromChoice2 :: Migration
migrationFromChoice2 = constMigrationFrom2 maybeMigrateFromChoice2
migrationChoice :: Migration
migrationChoice
= migrationToChoice1
<> migrationFromChoice1
<> migrationToChoice2
<> migrationFromChoice2
maybeMigrateToExceptState
:: (Typeable state, Typeable state')
=> ExceptState state e
-> state'
-> Maybe (ExceptState state e)
maybeMigrateToExceptState (NotThrown _) state = NotThrown <$> cast state
maybeMigrateToExceptState (Exception e) _ = Just $ Exception e
migrationToExceptState :: Migration
migrationToExceptState = migrationTo2 maybeMigrateToExceptState
maybeMigrateFromExceptState
:: (Typeable state, Typeable state')
=> ExceptState state e
-> Maybe state'
maybeMigrateFromExceptState (NotThrown state) = cast state
maybeMigrateFromExceptState (Exception e) = Nothing
migrationFromExceptState :: Migration
migrationFromExceptState = constMigrationFrom2 maybeMigrateFromExceptState
migrationExceptState :: Migration
migrationExceptState = migrationToExceptState <> migrationFromExceptState
migrationCell :: Migration
migrationCell
= migrationComposition
<> migrationParallel
<> migrationChoice
<> migrationExceptState