remove toSimpleProp
It didn't do what I thought it did with a RevertableProperty; it always returned Nothing because even if the input properties to <!> are NoInfo, it casts them to HasInfo. Even if it had worked, it lost type safety. Better to export the Property NoInfo that is used in a RevertableProperty, so it can be used directly.
This commit is contained in:
parent
334abae312
commit
e9d5d9aff1
|
@ -0,0 +1,18 @@
|
|||
Currently, a RevertableProperty's Properties always both HasInfo. This
|
||||
means that if a Property NoInfo is updated to be a RevertableProperty, and
|
||||
someplace called ensureProperty on it, that will refuse to compile.
|
||||
|
||||
The workaround is generally to export the original NoInfo property under
|
||||
a different name, so it can still be used with ensureProperty.
|
||||
|
||||
This could be fixed:
|
||||
|
||||
data RevertableProperty i1 i2 where
|
||||
RProp :: Property i1 -> Property i2 -> RevertableProperty i1 i2
|
||||
|
||||
However, needing to write "RevertableProperty HasInfo NoInfo" is quite
|
||||
a mouthful!
|
||||
|
||||
Since only 2 places in the propellor source code currently need to deal
|
||||
with this, it doesn't currently seem worth making the change, unless a less
|
||||
intrusive way can be found.
|
|
@ -266,17 +266,24 @@ data AptKey = AptKey
|
|||
}
|
||||
|
||||
trustsKey :: AptKey -> RevertableProperty
|
||||
trustsKey k = trust <!> untrust
|
||||
where
|
||||
desc = "apt trusts key " ++ keyname k
|
||||
f = "/etc/apt/trusted.gpg.d" </> keyname k ++ ".gpg"
|
||||
untrust = File.notPresent f
|
||||
trust = check (not <$> doesFileExist f) $ property desc $ makeChange $ do
|
||||
trustsKey k = trustsKey' k <!> untrustKey k
|
||||
|
||||
trustsKey' :: AptKey -> Property NoInfo
|
||||
trustsKey' k = check (not <$> doesFileExist f) $ property desc $ makeChange $ do
|
||||
withHandle StdinHandle createProcessSuccess
|
||||
(proc "gpg" ["--no-default-keyring", "--keyring", f, "--import", "-"]) $ \h -> do
|
||||
hPutStr h (pubkey k)
|
||||
hClose h
|
||||
nukeFile $ f ++ "~" -- gpg dropping
|
||||
where
|
||||
desc = "apt trusts key " ++ keyname k
|
||||
f = aptKeyFile k
|
||||
|
||||
untrustKey :: AptKey -> Property NoInfo
|
||||
untrustKey = File.notPresent . aptKeyFile
|
||||
|
||||
aptKeyFile :: AptKey -> FilePath
|
||||
aptKeyFile k = "/etc/apt/trusted.gpg.d" </> keyname k ++ ".gpg"
|
||||
|
||||
-- | Cleans apt's cache of downloaded packages to avoid using up disk
|
||||
-- space.
|
||||
|
|
|
@ -1,3 +1,5 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
||||
module Propellor.Property.Debootstrap (
|
||||
Url,
|
||||
DebootstrapConfig(..),
|
||||
|
@ -56,18 +58,18 @@ toParams (c1 :+ c2) = toParams c1 <> toParams c2
|
|||
-- Note that reverting this property does not stop any processes
|
||||
-- currently running in the chroot.
|
||||
built :: FilePath -> System -> DebootstrapConfig -> RevertableProperty
|
||||
built = built' (toProp installed)
|
||||
|
||||
built' :: Property HasInfo -> FilePath -> System -> DebootstrapConfig -> RevertableProperty
|
||||
built' installprop target system@(System _ arch) config = setup <!> teardown
|
||||
built target system config = built' (toProp installed) target system config <!> teardown
|
||||
where
|
||||
setup = check (unpopulated target <||> ispartial) setupprop
|
||||
`requires` installprop
|
||||
|
||||
teardown = check (not <$> unpopulated target) teardownprop
|
||||
|
||||
unpopulated d = null <$> catchDefaultIO [] (dirContents d)
|
||||
teardownprop = property ("removed debootstrapped " ++ target) $
|
||||
makeChange (removetarget target)
|
||||
|
||||
built' :: (Combines (Property NoInfo) (Property i)) => Property i -> FilePath -> System -> DebootstrapConfig -> Property (CInfo NoInfo i)
|
||||
built' installprop target system@(System _ arch) config =
|
||||
check (unpopulated target <||> ispartial) setupprop
|
||||
`requires` installprop
|
||||
where
|
||||
setupprop = property ("debootstrapped " ++ target) $ liftIO $ do
|
||||
createDirectoryIfMissing True target
|
||||
-- Don't allow non-root users to see inside the chroot,
|
||||
|
@ -92,25 +94,26 @@ built' installprop target system@(System _ arch) config = setup <!> teardown
|
|||
, return FailedChange
|
||||
)
|
||||
|
||||
teardownprop = property ("removed debootstrapped " ++ target) $
|
||||
makeChange removetarget
|
||||
-- A failed debootstrap run will leave a debootstrap directory;
|
||||
-- recover by deleting it and trying again.
|
||||
ispartial = ifM (doesDirectoryExist (target </> "debootstrap"))
|
||||
( do
|
||||
removetarget target
|
||||
return True
|
||||
, return False
|
||||
)
|
||||
|
||||
removetarget = do
|
||||
unpopulated :: FilePath -> IO Bool
|
||||
unpopulated d = null <$> catchDefaultIO [] (dirContents d)
|
||||
|
||||
removetarget :: FilePath -> IO ()
|
||||
removetarget target = do
|
||||
submnts <- filter (\p -> simplifyPath p /= simplifyPath target)
|
||||
. filter (dirContains target)
|
||||
<$> mountPoints
|
||||
forM_ submnts umountLazy
|
||||
removeDirectoryRecursive target
|
||||
|
||||
-- A failed debootstrap run will leave a debootstrap directory;
|
||||
-- recover by deleting it and trying again.
|
||||
ispartial = ifM (doesDirectoryExist (target </> "debootstrap"))
|
||||
( do
|
||||
removetarget
|
||||
return True
|
||||
, return False
|
||||
)
|
||||
|
||||
extractSuite :: System -> Maybe String
|
||||
extractSuite (System (Debian s) _) = Just $ Apt.showSuite s
|
||||
extractSuite (System (Ubuntu r) _) = Just r
|
||||
|
|
|
@ -89,10 +89,10 @@ cleanInstallOnce confirmation = check (not <$> doesFileExist flagfile) $
|
|||
(Just u@(System (Ubuntu _) _)) -> debootstrap u
|
||||
_ -> error "os is not declared to be Debian or Ubuntu"
|
||||
|
||||
debootstrap targetos = ensureProperty $ fromJust $ toSimpleProp $
|
||||
debootstrap targetos = ensureProperty $
|
||||
-- Ignore the os setting, and install debootstrap from
|
||||
-- source, since we don't know what OS we're running in yet.
|
||||
Debootstrap.built' (toProp Debootstrap.sourceInstall)
|
||||
Debootstrap.built' Debootstrap.sourceInstall
|
||||
newOSDir targetos Debootstrap.DefaultConfig
|
||||
-- debootstrap, I wish it was faster..
|
||||
-- TODO eatmydata to speed it up
|
||||
|
|
|
@ -118,7 +118,7 @@ latestVersion :: Property NoInfo
|
|||
latestVersion = withOS "obnam latest version" $ \o -> case o of
|
||||
(Just (System (Debian suite) _)) | isStable suite -> ensureProperty $
|
||||
Apt.setSourcesListD (stablesources suite) "obnam"
|
||||
`requires` (fromJust (toSimpleProp (Apt.trustsKey key)))
|
||||
`requires` Apt.trustsKey' key
|
||||
_ -> noChange
|
||||
where
|
||||
stablesources suite =
|
||||
|
|
|
@ -179,7 +179,6 @@ class IsProp p where
|
|||
-- | Sets description.
|
||||
describe :: p -> Desc -> p
|
||||
toProp :: p -> Property HasInfo
|
||||
toSimpleProp :: p -> Maybe (Property NoInfo)
|
||||
getDesc :: p -> Desc
|
||||
-- | Gets the info of the property, combined with all info
|
||||
-- of all children properties.
|
||||
|
@ -188,7 +187,6 @@ class IsProp p where
|
|||
instance IsProp (Property HasInfo) where
|
||||
describe (IProperty _ a i cs) d = IProperty d a i cs
|
||||
toProp = id
|
||||
toSimpleProp _ = Nothing
|
||||
getDesc = propertyDesc
|
||||
getInfoRecursive (IProperty _ _ i cs) =
|
||||
i <> mconcat (map getInfoRecursive cs)
|
||||
|
@ -196,7 +194,6 @@ instance IsProp (Property NoInfo) where
|
|||
describe (SProperty _ a cs) d = SProperty d a cs
|
||||
toProp = toIProperty
|
||||
getDesc = propertyDesc
|
||||
toSimpleProp = Just
|
||||
getInfoRecursive _ = mempty
|
||||
|
||||
instance IsProp RevertableProperty where
|
||||
|
@ -205,7 +202,6 @@ instance IsProp RevertableProperty where
|
|||
RevertableProperty (describe p1 d) (describe p2 ("not " ++ d))
|
||||
getDesc (RevertableProperty p1 _) = getDesc p1
|
||||
toProp (RevertableProperty p1 _) = p1
|
||||
toSimpleProp = toSimpleProp . toProp
|
||||
-- | Return the Info of the currently active side.
|
||||
getInfoRecursive (RevertableProperty p1 _p2) = getInfoRecursive p1
|
||||
|
||||
|
|
Loading…
Reference in New Issue