Skip to content
This repository has been archived by the owner on Jan 30, 2024. It is now read-only.

Rewrite Migration parser using conventional FromJSON #43

Merged
merged 6 commits into from
Jan 11, 2023
Merged
Show file tree
Hide file tree
Changes from 5 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion dbmigrations.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ Library
configurator >= 0.2,
split >= 0.2.2,
HUnit >= 1.2,
aeson < 2,
aeson,
unordered-containers

Hs-Source-Dirs: src
Expand Down
169 changes: 81 additions & 88 deletions src/Database/Schema/Migrations/Filesystem.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables, OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, LambdaCase, ScopedTypeVariables, OverloadedStrings #-}
-- |This module provides a type for interacting with a
-- filesystem-backed 'MigrationStore'.
module Database.Schema.Migrations.Filesystem
Expand All @@ -20,26 +20,21 @@ import Data.String.Conversions ( cs, (<>) )

import Data.Typeable ( Typeable )
import Data.Time.Clock ( UTCTime )
import Data.Time () -- for UTCTime Show instance
import Data.Time ( defaultTimeLocale, formatTime, parseTimeM )
import qualified Data.Map as Map

import Control.Applicative ( (<$>) )
import Control.Monad ( filterM )
import Control.Exception ( Exception(..), throw, catch )

import Data.Aeson as J (Object, Value(String, Null))
import Data.HashMap.Strict as M (toList)
import Data.Yaml
import Data.Aeson
import Data.Aeson.Types (typeMismatch)
import qualified Data.Yaml as Yaml
import GHC.Generics (Generic)

import Database.Schema.Migrations.Migration
( Migration(..)
, emptyMigration
)
import Database.Schema.Migrations.Migration (Migration(..))
import Database.Schema.Migrations.Filesystem.Serialize
import Database.Schema.Migrations.Store

type FieldProcessor = Text -> Migration -> Maybe Migration

data FilesystemStoreSettings = FSStore { storePath :: FilePath }

data FilesystemStoreError = FilesystemStoreError String
Expand Down Expand Up @@ -106,79 +101,77 @@ migrationFromPath path = do
readMigrationFile = do
ymlExists <- doesFileExist (addNewMigrationExtension path)
if ymlExists
then decodeFileThrow (addNewMigrationExtension path) `catch` (\(e::ParseException) -> throwFS $ show e)
else decodeFileThrow (addMigrationExtension path filenameExtensionTxt) `catch` (\(e::ParseException) -> throwFS $ show e)

process name = do
yaml <- readMigrationFile

-- Convert yaml structure into basic key/value map
let fields = getFields yaml
missing = missingFields fields

case length missing of
0 -> do
let newM = emptyMigration name
case migrationFromFields newM fields of
Nothing -> throwFS $ "Error in " ++ (show path) ++ ": unrecognized field found"
Just m -> return m
_ -> throwFS $ "Error in " ++ (show path) ++ ": missing required field(s): " ++ (show missing)

getFields :: J.Object -> [(Text, Text)]
getFields mp = map toPair $ M.toList mp
where
toPair :: (Text, Value) -> (Text, Text)
toPair (k, J.String v) = (cs k, cs v)
toPair (k, J.Null) = (cs k, cs ("" :: String))
toPair (k, v) = throwFS $ "Error in YAML input; expected string key and string value, got " ++ (show (k, v))
getFields _ = throwFS "Error in YAML input; expected mapping"

missingFields :: [(Text, Text)] -> [Text]
missingFields fs =
[ k | k <- requiredFields, not (k `elem` inputStrings) ]
where
inputStrings = map fst fs

-- |Given a migration and a list of parsed migration fields, update
-- the migration from the field values for recognized fields.
migrationFromFields :: Migration -> [(Text, Text)] -> Maybe Migration
migrationFromFields m [] = Just m
migrationFromFields m ((name, value):rest) = do
processor <- lookup name fieldProcessors
newM <- processor value m
migrationFromFields newM rest

requiredFields :: [Text]
requiredFields = [ "Apply"
, "Depends"
]

fieldProcessors :: [(Text, FieldProcessor)]
fieldProcessors = [ ("Created", setTimestamp )
, ("Description", setDescription )
, ("Apply", setApply )
, ("Revert", setRevert )
, ("Depends", setDepends )
]

setTimestamp :: FieldProcessor
setTimestamp value m = do
ts <- case readTimestamp value of
[(t, _)] -> return t
_ -> fail "expected one valid parse"
return $ m { mTimestamp = Just ts }

readTimestamp :: Text -> [(UTCTime, String)]
readTimestamp = reads . cs

setDescription :: FieldProcessor
setDescription desc m = Just $ m { mDesc = Just desc }

setApply :: FieldProcessor
setApply apply m = Just $ m { mApply = apply }

setRevert :: FieldProcessor
setRevert revert m = Just $ m { mRevert = Just revert }

setDepends :: FieldProcessor
setDepends depString m = Just $ m { mDeps = T.words depString }
then Yaml.decodeFileThrow (addNewMigrationExtension path) `catch` (\(e::Yaml.ParseException) -> throwFS $ show e)
else Yaml.decodeFileThrow (addMigrationExtension path filenameExtensionTxt) `catch` (\(e::Yaml.ParseException) -> throwFS $ show e)

process name = migrationYamlToMigration name <$> readMigrationFile

-- | TODO: re-use this for the generation side too
data MigrationYaml = MigrationYaml
{ myCreated :: Maybe UTCTimeYaml
, myDescription :: Maybe Text
, myApply :: Text
, myRevert :: Maybe Text
, myDepends :: DependsYaml
}
deriving Generic

instance FromJSON MigrationYaml where
parseJSON = genericParseJSON jsonOptions

instance ToJSON MigrationYaml where
toJSON = genericToJSON jsonOptions
toEncoding = genericToEncoding jsonOptions

jsonOptions :: Options
jsonOptions = defaultOptions
{ fieldLabelModifier = drop 2 -- remove "my" prefix
, omitNothingFields = True
, rejectUnknownFields = True
}

migrationYamlToMigration :: Text -> MigrationYaml -> Migration
migrationYamlToMigration theId my = Migration
{ mTimestamp = unUTCTimeYaml <$> myCreated my
, mId = theId
, mDesc = myDescription my
, mApply = myApply my
, mRevert = myRevert my
, mDeps = unDependsYaml $ myDepends my
}

newtype UTCTimeYaml = UTCTimeYaml
{ unUTCTimeYaml :: UTCTime
}

instance FromJSON UTCTimeYaml where
parseJSON = withText "UTCTime"
$ maybe (fail "Unable to parse UTCTime") (pure . UTCTimeYaml)
. parseTimeM True defaultTimeLocale utcTimeYamlFormat
. cs

instance ToJSON UTCTimeYaml where
toJSON = toJSON . formatTime defaultTimeLocale utcTimeYamlFormat . unUTCTimeYaml
toEncoding = toEncoding . formatTime defaultTimeLocale utcTimeYamlFormat . unUTCTimeYaml

-- Keeps things as the old Show/Read-based format, e.g "2009-04-15 10:02:06 UTC"
Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

👋 @jtdaugherty I just wanted to mention: I finally updated my own app to this version of this library and I found it failed because my migrations all had fractional seconds, such as

Created: 2009-04-15 10:02:06.23345 UTC

I'm not sure where that came from, or why the parse won't accept it, because I swear I tested things when I wrote this PR.

In any event, I ran the following to truncate them before my migrations would run with the new version:

sed -i 's/\.[0-9]\+ UTC$/ UTC/' db/migrations/**/*  

I'm not sure if we should make an update to make the parser more flexible?

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yikes! Sorry to hear about this. It seems to me that a relaxation to the parser ought to be okay. If you want to make that change, let me know - otherwise I'll see to it.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It seems to me that a relaxation to the parser ought to be okay

Yeah, agreed. If I'm reading the docs correctly, it seems like using ...%T%Q UTC could do it:

%Q

decimal point and fraction of second, up to 12 second decimals, without trailing zeros. For a whole number of seconds, %Q omits the decimal point unless padding is specified

(Emphasis mine)

I'm not quite sure my availability, so I'll comment again if I get a chance to work on it; otherwise, feel free.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think we need to do something, because new migrations still get created with fractional seconds, so the problem will keep coming back. @pbrisbin any chance you could create a PR with this fix, as you seem quite familiar with the problem and relevant code?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

because new migrations still get created with fractional seconds

I didn't realize this. You're saying this version creates fractional seconds files that it can't parse? That's much worse.

you seem quite familiar with the problem and relevant code?

I may have been at one time, but that was a long time ago. Still, it seems like a relatively straightforward thing. The decoder needs to accept with or without fractional seconds. Adding a unit test and using the format-string I mentioned above should do it.

utcTimeYamlFormat :: String
utcTimeYamlFormat = "%F %T UTC"

newtype DependsYaml = DependsYaml
{ unDependsYaml :: [Text]
}
pbrisbin marked this conversation as resolved.
Show resolved Hide resolved

instance FromJSON DependsYaml where
parseJSON = \case
Null -> pure $ DependsYaml []
String t -> pure $ DependsYaml $ T.words t
x -> typeMismatch "Null or whitespace-separated String" x

instance ToJSON DependsYaml where
toJSON (DependsYaml ts) = case ts of
[] -> toJSON Null
_ -> toJSON $ T.unwords ts
toEncoding (DependsYaml ts) = case ts of
[] -> toEncoding Null
_ -> toEncoding $ T.unwords ts