{-# LANGUAGE CPP #-} {- | @moto@ is a library for describing and running /migrations/. A /migration/ is any code that changes the environment somehow. The stereotypical example of a migration is code that modifies the schema of a database, but really anything that changes the environment somehow can be seen as a migration. For example, moving a file to a different directory or host, installing a package, deploying infrastructure, etc. Essentially, a migration is a glorified bash script to which we hold dear because of how devastating it can be for our project if we get it wrong. @moto@ understands this, so it is very careful about how, when, where and why it runs these migrations, paying special attention to what happens when something goes wrong. Of course, this being Haskell, we are encouraged to use domain specific tools that can prevent us from accidentally writing the wrong migration code (e.g., deleting a database rather than modifying it). In @moto@ we can specify migrations in such a way that any data that is going modified or deleted by a migration can be backed up for us in one or more storages of our choice. If anything goes wrong, or if we latter decide to undo these changes, then this backup will be automatically made available to us. @moto@ is excellent for teams, where multiple collaborators can add new migrations to the project at the same time, establishing dependencies between them by saying “this migration needs to run before that other one” as a graph. At compile time, @moto@ will ensure whether there is at least one way to execute these migrations graph sequentially, or fail to compile otherwise. And at runtime, it will execute this graph in any way that's compatible with the environment where the migrations are being run. We don't need to worry about serializing the release and deployment of migrations anymore, nor about making sure that everybody runs migrations in the same order. We can delegate that responsibility to @moto@. Also, @moto@ is an excellent interface to interacting with our migrations and environment. The final product we obtain as a user of @moto@ is a ready-made /command line interface/ program that we can deploy and use to run all or some migrations, undo them, render the dependency graph, compare it with the current registry of migrations that have been run so far, obtain an execution plan as well as very detailed logs in human and computer readable formats, etc. @moto@ relies on a /registry/ of migrations to understand what has been run so far and what hasn't. We can decide whether to keep this state locally or in a remote database. Last, but not least, @moto@ encourages us to remove old migrations after some time, once these migrations are so old that maintaining them in the project is an unnecessary burden to us. To this end, @moto@ offers us enough vocabulary to mark said migrations as /gone/. This module is inteded to be imported qualified: @ import qualified "Moto" @ -} module Moto ( -- * Example -- -- $example -- * Frequently Asked Questions -- -- $faq -- * Running IC.run , IC.Opts , IC.getOpts -- * Describing individual migrations , I.Mig(..) , I.Store(..) , I.mapStore , I.Backup(..) , I.Change(..) , I.Direction(..) , I.direction , I.Mode(..) , I.MigId(..) -- * Describing migrations graph , I.Migs , I.migs , (I.*) , I.DAG -- * Command line help -- -- $cli_help ) where import qualified Moto.Internal as I import qualified Moto.Internal.Cli as IC {- $example The main interface to running migrations is the command line. As a user of @moto@, we are expected to create an executable that calls 'I.cli'. This executable can then be deployed and used to run migrations. Usually, the code in this executable will look like this: @ \{\-\# LANGUAGE DataKinds \#\-\} \{\-\# LANGUAGE PartialTypeSignatures \#\-\} -- Our project will be an executable, so we name our module Main as it is -- customary. module Main (main) where -- "Moto" is designed to be imported qualified, as well as "Di", a module that -- provides the logging support required by "Moto". import qualified "Di" import qualified "Moto" -- Moreover, in this example we will use a migrations registry from the -- "Moto.File" module as an example. import qualified "Moto.File" -- Here are some migrations, each of them with a identifier and a set of -- identifiers for other migrations expected to be executed before them when -- going 'Moto.Forwards'. -- -- Optional: It is actually recommended to put each migration in its own module. -- It is not necessary, but GHC takes a longer time and more resources to -- compile big modules. And considering the list of migrations in our project -- will always be growing, it's better to organize things that way from the -- start, as this can quickly become a source of slow compilation times. For -- example, instead of Main.mig_black and Main.mig_blue, we can have -- MyProject.Migs.Black.mig and MyProject.Migs.Blue.mig that we import as -- necessary. mig_red :: Moto.Mig "red" '["blue"] mig_red = Moto.Mig ... -- Please see the documentation for 'Moto.Mig'. mig_yellow :: Moto.Mig "yellow" '["black","red"] mig_yellow = Moto.Mig ... -- Please see the documentation for 'Moto.Mig'. mig_green :: Moto.Mig "green" '["red"] mig_green = Moto.Mig ... -- Please see the documentation for 'Moto.Mig'. mig_black :: Moto.Mig "black" '["blue"] mig_black = Moto.Mig ... -- Please see the documentation for 'Moto.Mig'. mig_blue :: Moto.Mig "blue" '[] mig_blue = Moto.Mig ... -- Please see the documentation for 'Moto.Mig'. -- All of the 'Mig's that we might want to run need to be put in directed -- acyclic graph where each migration is a node and each edge is a dependency -- between migrations. In "Moto", we use 'Moto.migs' and the infix 'Moto.*' -- function to safely construct the graph of migrations. The way we define our -- 'Moto.Migs' is a bit strange. Let's understand why. -- -- The Moto.* infix function says that the migrations that appear syntactically -- to its right can only mention as their dependencies migrations that appear -- to its syntactic left. This prevents us from mentioning our migrations in -- any order, but on the other hand it ensures at construction that there are no -- cycles nor dangling references in our dependency graph. If we get the order -- wrong, we will get a type-checker error. Moreover, migration identifiers are -- forced to be unique within this graph. The Moto.migs value itself is a dummy -- starting point we use as the leftmost argument to our chain of Moto.* calls. -- -- Observation: Note we avoid giving an explicit type to myMigs. Instead, we -- used the PartialTypeSignatures GHC extension to put an underscore there and -- allow GHC to use the inferred type. This is a desirable thing to do so as to -- prevent type-inference from accidentally inferring an undesired identifier -- for our migrations. This approach forces all of our Moto.Mig values to have -- their identifiers and dependencies fully specified at their definition site. -- We could have accomplished the same by not giving an type signature to our -- top level myMigs, or by simply inlining our definition of myMigs at its use -- site later on. myMigs :: Moto.Migs _ myMigs = Moto.migs Moto.* mig_blue Moto.* mig_red Moto.* mig_black Moto.* mig_green Moto.* mig_yellow -- Finally, we have our main entry point. This program can be run from the -- command line and allows us to run and inspect migrations. main :: IO () main = do -- Using 'Moto.getOpts' we parse the command-line arguments and obtain the -- instructions necessary to call 'Moto.run' afterwards. We specify as -- arguments a 'Moto.Cli.RegistryConf' that describes the migrations -- registry where we keep track of the migrations that have run so far, as -- well as any extra command-line parsing needs we may have. In our case, we -- use a file in the filesystem as our registry, and we don't do any extra -- command-line argument parsing. Please see the documentation of -- 'Moto.getOpts' for more details. (myOpts, ()) <- Moto.getOpts Moto.File.registryConf (pure ()) -- @moto@ uses "Di" for its own logging, so we first -- need to obtain a @'Di.Di' 'Df1.Level' 'Df1.Path' 'Df1.Message'@ value (also -- known by its 'Di.Df1' synonym). We can do this using 'Di.new'. Di.new $ \\di -> do -- Finally, we 'Moto.run' @moto@ as instructed by @myOpts@, passing in the -- 'Di.Df1' we just obtained, as well as the migrations graph Moto.run di myMigs myOpts @ -} {- $faq Here are some answers to questions you'll frequently ask yourselves when using @moto@. [Where should we maintain the migrations code for our project?] Ideally, if you keep your whole project in a single code repository, you should keep the migrations in that same repository, so that they are always in sync with the code they cater for. You should create a standalone executable program for running your migrations. [Should my migrations program depend on the code I am migrating?] Definitely not. That code will change or disappear over time, and it will affect your migrations code whenever it changes. Your migrations code should stand alone and have a holistic view of the history of the many environments where your project runs, without depending on it. [Can I use @moto@ to migrate projects not written in Haskell?] Yes, @moto@ doesn't care about the language your project is written in. However, the migrations code itself will have to be written Haskell. [How do I deploy this?] The same way you deploy other executables. We recommend packaging the program as a Nix derivation containing a statically linked executable. Moreover, you can package the migrations execution as a NixOS module that runs automatically whenever a new version is deployed. Future versions of @moto@ will provide a web interface for making migration execution a bit more interactive. [How do I make sure my migrations work before deploying them?] Generally speaking, as much as possible, you should use domain-specific type-safe DSLs to describe your changes. But still, eventually, try the real thing locally. Don't try to “mock” scenarios, that doesn't help. @moto@ makes it quite easy to run migrations backwards afterwards. Moreover, in order to try recovery scenarios, you try and throw exceptions from the different parts of your migrations and see what happens. [I don't see anything about SQL nor versioned data-types here] Whether you are modifying an SQL database or moving any other kind of bits around, @moto@ doesn't care about those details. You can write all the SQL you want inside your migration, using the SQL-supporting library of your choice, or version your datatypes as well. [Is this ready for production?] Migrations are a tricky business, and this is a very early release of @moto@, so use at your own risk. [Is the API stable?] No, and it will never be. We will always break the API as necessary if it allows us offer better safety and experience. However, we understand the subtle nature of the projects relying on @moto@ an we will take the necessary steps to ensure a positive and maintainable experience over time. Please see the [changelog](https://hackage.haskell.org/package/moto/changelog) to understand differences between versions and learn about any necessary changes you'll need to make. In a @moto@ version @x.y.z@, we will always increase one of @x@ or @y@ whenever a new version introduces backwards incompatible changes. [I have more questions!] We have more answers. Just [ask](https://gitlab.com/k0001/moto/issues). -} #include "cli_help.docs"