Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Cloudy.Db
Synopsis
- createLocalDatabase :: Connection -> IO ()
- withCloudyDb :: (Connection -> IO a) -> IO a
- withSqliteConn :: FilePath -> (Connection -> IO a) -> IO a
- data QuerySingleErr = QuerySingleErr Query String
- querySingleErr_ :: FromRow r => Connection -> Query -> IO r
- data OnlyOne r
- = OnlyOne r
- | MultipleExist
- | NoneExist
- querySingle_ :: FromRow r => Connection -> Query -> IO (OnlyOne r)
- queryUnique :: (ToRow a, FromRow r) => Connection -> Query -> a -> IO (Maybe r)
- newtype CloudyInstanceId = CloudyInstanceId {}
- data CloudyInstance = CloudyInstance {}
- newtype DbInstanceSetup = DbInstanceSetup {}
- data ScalewayInstance = ScalewayInstance {}
- data InstanceInfo
- cloudyInstanceFromInstanceInfo :: InstanceInfo -> CloudyInstance
- newCloudyInstance :: Connection -> IO (CloudyInstanceId, Text)
- findCloudyInstanceByNameWithDeleted :: Connection -> Text -> IO (Maybe CloudyInstance)
- findCloudyInstanceIdByName :: Connection -> Text -> IO (Maybe CloudyInstanceId)
- findCloudyInstanceById :: Connection -> CloudyInstanceId -> IO (Maybe CloudyInstance)
- findAllCloudyInstances :: Connection -> IO [CloudyInstance]
- setCloudyInstanceDeleted :: Connection -> CloudyInstanceId -> IO ()
- newScalewayInstance :: Connection -> UTCTime -> CloudyInstanceId -> Maybe InstanceSetup -> Text -> Text -> Text -> Text -> IO ()
- findScalewayInstanceByCloudyInstanceId :: Connection -> CloudyInstanceId -> IO (Maybe ScalewayInstance)
- findAllScalewayInstances :: Connection -> IO [ScalewayInstance]
- findOnlyOneInstanceId :: Connection -> IO (OnlyOne CloudyInstanceId)
- utcTimeToSqliteInt :: UTCTime -> Int64
- utcTimeFromSqliteInt :: Int64 -> UTCTime
- instanceInfoForId :: Connection -> CloudyInstanceId -> IO (Maybe InstanceInfo)
- findAllInstanceInfos :: Connection -> IO [InstanceInfo]
- data DbInvariantErr
- assertDbInvariants :: Connection -> IO ()
- invariantEveryCloudyInstHasExactlyOneProviderInst :: Connection -> IO [DbInvariantErr]
- invariantCloudyInstCorectDates :: Connection -> IO [DbInvariantErr]
Documentation
createLocalDatabase :: Connection -> IO () Source #
withCloudyDb :: (Connection -> IO a) -> IO a Source #
withSqliteConn :: FilePath -> (Connection -> IO a) -> IO a Source #
data QuerySingleErr Source #
Constructors
QuerySingleErr Query String |
Instances
Exception QuerySingleErr Source # | |
Defined in Cloudy.Db Methods toException :: QuerySingleErr -> SomeException # | |
Show QuerySingleErr Source # | |
Defined in Cloudy.Db Methods showsPrec :: Int -> QuerySingleErr -> ShowS # show :: QuerySingleErr -> String # showList :: [QuerySingleErr] -> ShowS # | |
Eq QuerySingleErr Source # | |
Defined in Cloudy.Db Methods (==) :: QuerySingleErr -> QuerySingleErr -> Bool # (/=) :: QuerySingleErr -> QuerySingleErr -> Bool # |
querySingleErr_ :: FromRow r => Connection -> Query -> IO r Source #
Constructors
OnlyOne r | |
MultipleExist | |
NoneExist |
querySingle_ :: FromRow r => Connection -> Query -> IO (OnlyOne r) Source #
queryUnique :: (ToRow a, FromRow r) => Connection -> Query -> a -> IO (Maybe r) Source #
Query on a column with a UNIQUE constraint. Throws an exception if multiple values are returned.
newtype CloudyInstanceId Source #
Constructors
CloudyInstanceId | |
Fields |
Instances
Show CloudyInstanceId Source # | |
Defined in Cloudy.Db Methods showsPrec :: Int -> CloudyInstanceId -> ShowS # show :: CloudyInstanceId -> String # showList :: [CloudyInstanceId] -> ShowS # | |
Eq CloudyInstanceId Source # | |
Defined in Cloudy.Db Methods (==) :: CloudyInstanceId -> CloudyInstanceId -> Bool # (/=) :: CloudyInstanceId -> CloudyInstanceId -> Bool # | |
Ord CloudyInstanceId Source # | |
Defined in Cloudy.Db Methods compare :: CloudyInstanceId -> CloudyInstanceId -> Ordering # (<) :: CloudyInstanceId -> CloudyInstanceId -> Bool # (<=) :: CloudyInstanceId -> CloudyInstanceId -> Bool # (>) :: CloudyInstanceId -> CloudyInstanceId -> Bool # (>=) :: CloudyInstanceId -> CloudyInstanceId -> Bool # max :: CloudyInstanceId -> CloudyInstanceId -> CloudyInstanceId # min :: CloudyInstanceId -> CloudyInstanceId -> CloudyInstanceId # | |
FromField CloudyInstanceId Source # | |
Defined in Cloudy.Db Methods | |
ToField CloudyInstanceId Source # | |
Defined in Cloudy.Db Methods toField :: CloudyInstanceId -> SQLData # |
data CloudyInstance Source #
Constructors
CloudyInstance | |
Fields
|
Instances
Show CloudyInstance Source # | |
Defined in Cloudy.Db Methods showsPrec :: Int -> CloudyInstance -> ShowS # show :: CloudyInstance -> String # showList :: [CloudyInstance] -> ShowS # | |
Eq CloudyInstance Source # | |
Defined in Cloudy.Db Methods (==) :: CloudyInstance -> CloudyInstance -> Bool # (/=) :: CloudyInstance -> CloudyInstance -> Bool # | |
FromRow CloudyInstance Source # | |
Defined in Cloudy.Db Methods |
newtype DbInstanceSetup Source #
newtype to hold the FromField
instance for InstanceSetup
, for use in
the FromRow
instance for CloudyInstance
.
The instance_setup
column in the cloudy_instance
table holds a
JSON-encoded InstanceSetup
value.
Constructors
DbInstanceSetup | |
Fields |
Instances
FromField DbInstanceSetup Source # | |
Defined in Cloudy.Db Methods | |
ToField DbInstanceSetup Source # | |
Defined in Cloudy.Db Methods toField :: DbInstanceSetup -> SQLData # |
data ScalewayInstance Source #
Constructors
ScalewayInstance | |
Fields |
Instances
Show ScalewayInstance Source # | |
Defined in Cloudy.Db Methods showsPrec :: Int -> ScalewayInstance -> ShowS # show :: ScalewayInstance -> String # showList :: [ScalewayInstance] -> ShowS # | |
Eq ScalewayInstance Source # | |
Defined in Cloudy.Db Methods (==) :: ScalewayInstance -> ScalewayInstance -> Bool # (/=) :: ScalewayInstance -> ScalewayInstance -> Bool # | |
FromRow ScalewayInstance Source # | |
Defined in Cloudy.Db Methods | |
ToRow ScalewayInstance Source # | |
Defined in Cloudy.Db Methods toRow :: ScalewayInstance -> [SQLData] # |
data InstanceInfo Source #
Constructors
CloudyScalewayInstance CloudyInstance ScalewayInstance | |
CloudyAwsInstance CloudyInstance Void |
Instances
Show InstanceInfo Source # | |
Defined in Cloudy.Db Methods showsPrec :: Int -> InstanceInfo -> ShowS # show :: InstanceInfo -> String # showList :: [InstanceInfo] -> ShowS # |
newCloudyInstance :: Connection -> IO (CloudyInstanceId, Text) Source #
findCloudyInstanceByNameWithDeleted :: Connection -> Text -> IO (Maybe CloudyInstance) Source #
Return a cloudy instance matching the given name. This will return an instance even if it has already been deleted.
findCloudyInstanceIdByName :: Connection -> Text -> IO (Maybe CloudyInstanceId) Source #
setCloudyInstanceDeleted :: Connection -> CloudyInstanceId -> IO () Source #
Arguments
:: Connection | |
-> UTCTime | |
-> CloudyInstanceId | |
-> Maybe InstanceSetup | |
-> Text | Scaleway Zone |
-> Text | Scaleway Instance Id |
-> Text | Scaleway IP Id |
-> Text | Scaleway IP Address |
-> IO () |
findScalewayInstanceByCloudyInstanceId :: Connection -> CloudyInstanceId -> IO (Maybe ScalewayInstance) Source #
findOnlyOneInstanceId :: Connection -> IO (OnlyOne CloudyInstanceId) Source #
Return a single CloudyInstanceId if there is exactly one in the database that is not already deleted.
utcTimeToSqliteInt :: UTCTime -> Int64 Source #
utcTimeFromSqliteInt :: Int64 -> UTCTime Source #
instanceInfoForId :: Connection -> CloudyInstanceId -> IO (Maybe InstanceInfo) Source #
findAllInstanceInfos :: Connection -> IO [InstanceInfo] Source #
data DbInvariantErr Source #
Constructors
CloudyInstanceHasNoProviderInstance CloudyInstanceId | |
CloudyInstanceHasMultipleProviderInstances CloudyInstanceId | |
CloudyInstanceHasNullCreatedAt CloudyInstanceId |
Instances
Show DbInvariantErr Source # | |
Defined in Cloudy.Db Methods showsPrec :: Int -> DbInvariantErr -> ShowS # show :: DbInvariantErr -> String # showList :: [DbInvariantErr] -> ShowS # |
assertDbInvariants :: Connection -> IO () Source #
invariantEveryCloudyInstHasExactlyOneProviderInst :: Connection -> IO [DbInvariantErr] Source #
There needs to be EXACTLY ONE corresponding cloud provider instance for each cloudy instance.
invariantCloudyInstCorectDates :: Connection -> IO [DbInvariantErr] Source #
Cloudy instances should always have a created_at
value that is non-null.
The only time a Cloudy instance can have a created_at
value that is null
is within the Create CLI command. Although this invariant should hold both
before and after the Create CLI command.