Skip to content

Commit

Permalink
Change all instances in code of Zelm to Zokka
Browse files Browse the repository at this point in the history
This finishes #6
  • Loading branch information
changlinli committed Dec 5, 2023
1 parent c06c023 commit 0b9fa76
Show file tree
Hide file tree
Showing 16 changed files with 183 additions and 183 deletions.
16 changes: 8 additions & 8 deletions builder/src/Deps/CustomRepositoryDataIO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,23 +10,23 @@ import qualified File
import qualified Json.Decode as D
import qualified Json.Encode as E
import Data.Bifunctor (first)
import Stuff (ZelmCustomRepositoryConfigFilePath (..))
import Stuff (ZokkaCustomRepositoryConfigFilePath (..))

data CustomRepositoriesError = CREJsonDecodeError (D.Error CustomRepositoryDataParseError)
deriving Show

-- FIXME: Boolean argument a hack for now
createCustomRepositoriesData :: ZelmCustomRepositoryConfigFilePath -> Bool -> IO (Either e CustomRepositoriesData)
createCustomRepositoriesData (ZelmCustomRepositoryConfigFilePath filePath) shouldIncludeZelmRepo =
createCustomRepositoriesData :: ZokkaCustomRepositoryConfigFilePath -> Bool -> IO (Either e CustomRepositoriesData)
createCustomRepositoriesData (ZokkaCustomRepositoryConfigFilePath filePath) shouldIncludeZokkaRepo =
let
defaultData = if shouldIncludeZelmRepo then defaultCustomRepositoriesData else defaultCustomRepositoriesDataElmPackageRepoOnly
defaultData = if shouldIncludeZokkaRepo then defaultCustomRepositoriesData else defaultCustomRepositoriesDataElmPackageRepoOnly
in
do
E.write filePath (customRepostoriesDataEncoder defaultData)
pure (Right defaultData)

loadCustomRepositoriesData :: ZelmCustomRepositoryConfigFilePath -> IO (Either CustomRepositoriesError CustomRepositoriesData)
loadCustomRepositoriesData z@(ZelmCustomRepositoryConfigFilePath filePath) = do
loadCustomRepositoriesData :: ZokkaCustomRepositoryConfigFilePath -> IO (Either CustomRepositoriesError CustomRepositoriesData)
loadCustomRepositoriesData z@(ZokkaCustomRepositoryConfigFilePath filePath) = do
customReposDataDoesExist <- File.exists filePath
if customReposDataDoesExist
then do
Expand All @@ -35,8 +35,8 @@ loadCustomRepositoriesData z@(ZelmCustomRepositoryConfigFilePath filePath) = do
else
createCustomRepositoriesData z True

loadCustomRepositoriesDataForReactorTH :: ZelmCustomRepositoryConfigFilePath -> IO (Either CustomRepositoriesError CustomRepositoriesData)
loadCustomRepositoriesDataForReactorTH z@(ZelmCustomRepositoryConfigFilePath filePath) = do
loadCustomRepositoriesDataForReactorTH :: ZokkaCustomRepositoryConfigFilePath -> IO (Either CustomRepositoriesError CustomRepositoriesData)
loadCustomRepositoriesDataForReactorTH z@(ZokkaCustomRepositoryConfigFilePath filePath) = do
customReposDataDoesExist <- File.exists filePath
if customReposDataDoesExist
then do
Expand Down
8 changes: 4 additions & 4 deletions builder/src/Deps/Diff.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ import qualified Http
import qualified Json.Decode as D
import qualified Reporting.Exit as Exit
import qualified Stuff
import Deps.Registry (ZelmRegistries)
import Deps.Registry (ZokkaRegistries)
import qualified Deps.Registry as Registry
import qualified Data.Utf8 as Utf8
import Logging.Logger (printLog)
Expand Down Expand Up @@ -359,8 +359,8 @@ changeMagnitude (Changes added changed removed) =
-- GET DOCS


getDocs :: Stuff.PackageCache -> ZelmRegistries -> Http.Manager -> Pkg.Name -> V.Version -> IO (Either Exit.DocsProblem Docs.Documentation)
getDocs cache zelmRegistry manager name version =
getDocs :: Stuff.PackageCache -> ZokkaRegistries -> Http.Manager -> Pkg.Name -> V.Version -> IO (Either Exit.DocsProblem Docs.Documentation)
getDocs cache zokkaRegistry manager name version =
do let home = Stuff.package cache name version
let path = home </> "docs.json"
exists <- File.exists path
Expand All @@ -375,7 +375,7 @@ getDocs cache zelmRegistry manager name version =
do File.remove path
return $ Left Exit.DP_Cache
else
do let registryKeyMaybe = Registry.lookupPackageRegistryKey zelmRegistry name version
do let registryKeyMaybe = Registry.lookupPackageRegistryKey zokkaRegistry name version
-- FIXME: Handle the non-repository URL case better
repositoryUrl <- case registryKeyMaybe of
Just (Registry.RepositoryUrlKey repositoryUrl) -> pure repositoryUrl
Expand Down
60 changes: 30 additions & 30 deletions builder/src/Deps/Registry.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
module Deps.Registry
( Registry(..)
, KnownVersions(..)
, ZelmRegistries(..)
, ZokkaRegistries(..)
, RegistryKey(..)
, read
, fetch
Expand Down Expand Up @@ -48,7 +48,7 @@ import Data.Map.Utils (exchangeKeys, invertMap)
-- because of how we perform updates of the registry. We need to know how many
-- packages came from a given repository to pass to the /all-packages/since
-- endpoint. So we can't start from the outset with all the registries merged.
data ZelmRegistries = ZelmRegistries
data ZokkaRegistries = ZokkaRegistries
{ _registries :: !(Map.Map RegistryKey Registry)
, _packagesToLocations :: !(Map.Map Pkg.Name (Map.Map V.Version RegistryKey))
}
Expand All @@ -60,8 +60,8 @@ knownVersionsToNEListOfVersions :: KnownVersions -> NE.List V.Version
knownVersionsToNEListOfVersions (KnownVersions newest rest) = NE.List newest rest


zelmRegistriesFromRegistriesMap :: Map.Map RegistryKey Registry -> ZelmRegistries
zelmRegistriesFromRegistriesMap registriesMap =
zokkaRegistriesFromRegistriesMap :: Map.Map RegistryKey Registry -> ZokkaRegistries
zokkaRegistriesFromRegistriesMap registriesMap =
let
--FIXME: Deal with what happens when we have multiple registries with the same
-- version of a package. Right now we just essentially randomly choose one
Expand All @@ -72,11 +72,11 @@ zelmRegistriesFromRegistriesMap registriesMap =
pkgNamesToAllVersionsAndRegistry = fmap invertMap pkgNamesToRegistryAndAllVersions
pkgNamesToSingleVersionAndRegistry = (fmap . fmap) NE.head pkgNamesToAllVersionsAndRegistry
in
ZelmRegistries{_registries=registriesMap, _packagesToLocations=pkgNamesToSingleVersionAndRegistry}
ZokkaRegistries{_registries=registriesMap, _packagesToLocations=pkgNamesToSingleVersionAndRegistry}


lookupPackageRegistryKey :: ZelmRegistries -> Pkg.Name -> V.Version -> Maybe RegistryKey
lookupPackageRegistryKey ZelmRegistries{_packagesToLocations=packagesToLocations} pkgName pkgVersion =
lookupPackageRegistryKey :: ZokkaRegistries -> Pkg.Name -> V.Version -> Maybe RegistryKey
lookupPackageRegistryKey ZokkaRegistries{_packagesToLocations=packagesToLocations} pkgName pkgVersion =
do
versions <- Map.lookup pkgName packagesToLocations
Map.lookup pkgVersion versions
Expand All @@ -102,8 +102,8 @@ emptyRegistry :: Registry
emptyRegistry = Registry 0 Map.empty


mergeRegistries :: ZelmRegistries -> Registry
mergeRegistries ZelmRegistries{_registries=registries} = Map.foldl combineRegistry emptyRegistry registries
mergeRegistries :: ZokkaRegistries -> Registry
mergeRegistries ZokkaRegistries{_registries=registries} = Map.foldl combineRegistry emptyRegistry registries


data Registry =
Expand All @@ -126,7 +126,7 @@ data KnownVersions =
-- READ


read :: HasCallStack => Stuff.ZelmSpecificCache -> IO (Maybe ZelmRegistries)
read :: HasCallStack => Stuff.ZokkaSpecificCache -> IO (Maybe ZokkaRegistries)
read cache =
File.readBinary (Stuff.registry cache)

Expand All @@ -136,7 +136,7 @@ read cache =



fetch :: Http.Manager -> Stuff.ZelmSpecificCache -> CustomRepositoriesData -> IO (Either Exit.RegistryProblem ZelmRegistries)
fetch :: Http.Manager -> Stuff.ZokkaSpecificCache -> CustomRepositoriesData -> IO (Either Exit.RegistryProblem ZokkaRegistries)
fetch manager cache (CustomRepositoriesData customFullRepositories singlePackageLocations) =
do
-- FIXME: this is pretty awful
Expand All @@ -149,8 +149,8 @@ fetch manager cache (CustomRepositoriesData customFullRepositories singlePackage
Right registries -> do
let path = Stuff.registry cache
let registry = Map.fromList registries
File.writeBinary path (zelmRegistriesFromRegistriesMap registry)
pure $ Right (zelmRegistriesFromRegistriesMap registry)
File.writeBinary path (zokkaRegistriesFromRegistriesMap registry)
pure $ Right (zokkaRegistriesFromRegistriesMap registry)


createRegistryFromSinglePackageLocation :: SinglePackageLocationData -> Registry
Expand Down Expand Up @@ -199,10 +199,10 @@ allPkgsDecoder =

-- UPDATE

update :: Http.Manager -> Stuff.ZelmSpecificCache -> ZelmRegistries -> IO (Either Exit.RegistryProblem ZelmRegistries)
update manager cache zelmRegistries =
update :: Http.Manager -> Stuff.ZokkaSpecificCache -> ZokkaRegistries -> IO (Either Exit.RegistryProblem ZokkaRegistries)
update manager cache zokkaRegistries =
do
let registriesMap = _registries zelmRegistries
let registriesMap = _registries zokkaRegistries
let listOfProblemsOrKeyRegistryPairs = traverse (\(k, v) -> fmap (fmap ((,) k)) (updateSingleRegistry manager k v)) (Map.toList registriesMap)
newRegistryOrError <- sequence <$> listOfProblemsOrKeyRegistryPairs
let newRegistryOrError' = fmap Map.fromList newRegistryOrError
Expand All @@ -211,9 +211,9 @@ update manager cache zelmRegistries =
Right newRegistry ->
do
-- FIXME: There's gotta be a faster way of doing this
let newZelmRegistries = zelmRegistriesFromRegistriesMap newRegistry
_ <- File.writeBinary (Stuff.registry cache) newZelmRegistries
pure $ Right newZelmRegistries
let newZokkaRegistries = zokkaRegistriesFromRegistriesMap newRegistry
_ <- File.writeBinary (Stuff.registry cache) newZokkaRegistries
pure $ Right newZokkaRegistries


-- = RepositoryUrlKey RepositoryUrl
Expand Down Expand Up @@ -292,13 +292,13 @@ customSingleRepositoryDataToRegistryKey CustomSingleRepositoryData{_repositoryUr
singlePackageLocationDataToRegistryKey :: SinglePackageLocationData -> RegistryKey
singlePackageLocationDataToRegistryKey SinglePackageLocationData{_url=url}= PackageUrlKey url

doesRegistryAgreeWithCustomRepositoriesData :: CustomRepositoriesData -> ZelmRegistries -> Bool
doesRegistryAgreeWithCustomRepositoriesData :: CustomRepositoriesData -> ZokkaRegistries -> Bool
doesRegistryAgreeWithCustomRepositoriesData (CustomRepositoriesData fullRepositories singlePackages) registry =
Set.fromList allRegistryKeys == Map.keysSet (_registries registry)
where
allRegistryKeys = (customSingleRepositoryDataToRegistryKey <$> fullRepositories) ++ (singlePackageLocationDataToRegistryKey <$> singlePackages)

latest :: Http.Manager -> CustomRepositoriesData -> Stuff.ZelmSpecificCache -> IO (Either Exit.RegistryProblem ZelmRegistries)
latest :: Http.Manager -> CustomRepositoriesData -> Stuff.ZokkaSpecificCache -> IO (Either Exit.RegistryProblem ZokkaRegistries)
latest manager customRepositoriesData cache =
do
maybeOldRegistry <- read cache
Expand All @@ -324,19 +324,19 @@ versionsToKnownVersions :: [V.Version] -> Maybe KnownVersions
versionsToKnownVersions = foldr (\v acc -> Just $ compareVersionToKnownVersions v acc) Nothing


getVersions :: Pkg.Name -> ZelmRegistries -> Maybe KnownVersions
getVersions name ZelmRegistries{_packagesToLocations=packagesToLocations} =
getVersions :: Pkg.Name -> ZokkaRegistries -> Maybe KnownVersions
getVersions name ZokkaRegistries{_packagesToLocations=packagesToLocations} =
do
versionsMap <- Map.lookup name packagesToLocations
let versions = Map.keys versionsMap
versionsToKnownVersions versions

getVersions' :: Pkg.Name -> ZelmRegistries -> Either [Pkg.Name] KnownVersions
getVersions' name zelmRegistry =
case getVersions name zelmRegistry of
getVersions' :: Pkg.Name -> ZokkaRegistries -> Either [Pkg.Name] KnownVersions
getVersions' name zokkaRegistry =
case getVersions name zokkaRegistry of
Just kvs -> Right kvs
-- FIXME: Maybe a faster way than just brute-force merging?
Nothing -> Left $ Pkg.nearbyNames name (Map.keys (_versions $ mergeRegistries zelmRegistry))
Nothing -> Left $ Pkg.nearbyNames name (Map.keys (_versions $ mergeRegistries zokkaRegistry))



Expand Down Expand Up @@ -391,12 +391,12 @@ instance Binary KnownVersions where
put (KnownVersions a b) = put a >> put b


instance Binary ZelmRegistries where
instance Binary ZokkaRegistries where
get = do
registries <- get :: Get (Map.Map RegistryKey Registry)
packagesToLocations <- get :: Get (Map.Map Pkg.Name (Map.Map V.Version RegistryKey))
pure $ ZelmRegistries{_registries=registries, _packagesToLocations=packagesToLocations}
pure $ ZokkaRegistries{_registries=registries, _packagesToLocations=packagesToLocations}

put (ZelmRegistries registries packagesToLocations) = do
put (ZokkaRegistries registries packagesToLocations) = do
put registries
put packagesToLocations
42 changes: 21 additions & 21 deletions builder/src/Deps/Solver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ import Elm.CustomRepositoryData (CustomRepositoriesData, customRepostoriesDataDe
import Data.Maybe (fromJust)
import Deps.CustomRepositoryDataIO (loadCustomRepositoriesData, loadCustomRepositoriesDataForReactorTH)
import Reporting.Exit (RegistryProblem(..))
import Stuff (ZelmCustomRepositoryConfigFilePath(unZelmCustomRepositoryConfigFilePath), zelmCacheToFilePath)
import Stuff (ZokkaCustomRepositoryConfigFilePath(unZokkaCustomRepositoryConfigFilePath), zokkaCacheToFilePath)
import qualified Data.Utf8 as Utf8
import Logging.Logger (printLog)
import File (getTime)
Expand All @@ -65,7 +65,7 @@ data State =
State
{ _cache :: Stuff.PackageCache
, _connection :: Connection
, _registry :: Registry.ZelmRegistries
, _registry :: Registry.ZokkaRegistries
, _constraints :: Map.Map (Pkg.Name, V.Version) Constraints
}

Expand Down Expand Up @@ -102,7 +102,7 @@ data Details =
deriving Show


verify :: Stuff.PackageCache -> Connection -> Registry.ZelmRegistries -> Map.Map Pkg.Name C.Constraint -> IO (Result (Map.Map Pkg.Name Details))
verify :: Stuff.PackageCache -> Connection -> Registry.ZokkaRegistries -> Map.Map Pkg.Name C.Constraint -> IO (Result (Map.Map Pkg.Name Details))
verify cache connection registry constraints =
Stuff.withRegistryLock cache $
case try constraints of
Expand Down Expand Up @@ -139,7 +139,7 @@ data AppSolution =
}


addToApp :: Stuff.PackageCache -> Connection -> Registry.ZelmRegistries -> Pkg.Name -> Outline.AppOutline -> IO (Result AppSolution)
addToApp :: Stuff.PackageCache -> Connection -> Registry.ZokkaRegistries -> Pkg.Name -> Outline.AppOutline -> IO (Result AppSolution)
addToApp cache connection registry pkg outline@(Outline.AppOutline _ _ direct indirect testDirect testIndirect _) =
Stuff.withRegistryLock cache $
let
Expand Down Expand Up @@ -393,7 +393,7 @@ constraintsDecoder =


data Env =
Env Stuff.PackageCache Http.Manager Connection Registry.ZelmRegistries Stuff.PackageOverridesCache
Env Stuff.PackageCache Http.Manager Connection Registry.ZokkaRegistries Stuff.PackageOverridesCache


initEnv :: IO (Either Exit.RegistryProblem Env)
Expand All @@ -402,19 +402,19 @@ initEnv =
_ <- forkIO $ putMVar mvar =<< Http.getManager
cache <- Stuff.getPackageCache
packageOverridesCache <- Stuff.getPackageOverridesCache
zelmCache <- Stuff.getZelmCache
customRepositoriesConfigLocation <- Stuff.getOrCreateZelmCustomRepositoryConfig
zokkaCache <- Stuff.getZokkaCache
customRepositoriesConfigLocation <- Stuff.getOrCreateZokkaCustomRepositoryConfig
customRepositoriesDataOrErr <- loadCustomRepositoriesData customRepositoriesConfigLocation
case customRepositoriesDataOrErr of
Left err -> pure $ Left (RP_BadCustomReposData err (unZelmCustomRepositoryConfigFilePath customRepositoriesConfigLocation))
Left err -> pure $ Left (RP_BadCustomReposData err (unZokkaCustomRepositoryConfigFilePath customRepositoriesConfigLocation))
Right customRepositoriesData ->
Stuff.withRegistryLock cache $
do maybeRegistry <- Registry.read zelmCache
do maybeRegistry <- Registry.read zokkaCache
manager <- readMVar mvar

case maybeRegistry of
Nothing ->
do eitherRegistry <- Registry.fetch manager zelmCache customRepositoriesData
do eitherRegistry <- Registry.fetch manager zokkaCache customRepositoriesData
case eitherRegistry of
Right latestRegistry ->
return $ Right $ Env cache manager (Online manager) latestRegistry packageOverridesCache
Expand All @@ -423,12 +423,12 @@ initEnv =
return $ Left $ problem

Just cachedRegistry ->
do modifiedTimeOfZelmCache <- getTime (zelmCacheToFilePath zelmCache)
do modifiedTimeOfZokkaCache <- getTime (zokkaCacheToFilePath zokkaCache)
-- FIXME: Think about whether I need a lock on the custom repository JSON file as well
modifiedTimeOfCustomRepositoriesData <- getTime (unZelmCustomRepositoryConfigFilePath customRepositoriesConfigLocation)
eitherRegistry <- if modifiedTimeOfZelmCache == modifiedTimeOfCustomRepositoriesData
then Registry.update manager zelmCache cachedRegistry
else Registry.fetch manager zelmCache customRepositoriesData
modifiedTimeOfCustomRepositoriesData <- getTime (unZokkaCustomRepositoryConfigFilePath customRepositoriesConfigLocation)
eitherRegistry <- if modifiedTimeOfZokkaCache == modifiedTimeOfCustomRepositoriesData
then Registry.update manager zokkaCache cachedRegistry
else Registry.fetch manager zokkaCache customRepositoriesData
case eitherRegistry of
Right latestRegistry ->
return $ Right $ Env cache manager (Online manager) latestRegistry packageOverridesCache
Expand All @@ -442,19 +442,19 @@ initEnvForReactorTH =
_ <- forkIO $ putMVar mvar =<< Http.getManager
cache <- Stuff.getPackageCache
packageOverridesCache <- Stuff.getPackageOverridesCache
zelmCache <- Stuff.getZelmCache
customRepositoriesConfigLocation <- Stuff.getOrCreateZelmCustomRepositoryConfig
zokkaCache <- Stuff.getZokkaCache
customRepositoriesConfigLocation <- Stuff.getOrCreateZokkaCustomRepositoryConfig
customRepositoriesDataOrErr <- loadCustomRepositoriesDataForReactorTH customRepositoriesConfigLocation
case customRepositoriesDataOrErr of
Left err -> pure $ Left (RP_BadCustomReposData err (unZelmCustomRepositoryConfigFilePath customRepositoriesConfigLocation))
Left err -> pure $ Left (RP_BadCustomReposData err (unZokkaCustomRepositoryConfigFilePath customRepositoriesConfigLocation))
Right customRepositoriesData ->
Stuff.withRegistryLock cache $
do maybeRegistry <- Registry.read zelmCache
do maybeRegistry <- Registry.read zokkaCache
manager <- readMVar mvar

case maybeRegistry of
Nothing ->
do eitherRegistry <- Registry.fetch manager zelmCache customRepositoriesData
do eitherRegistry <- Registry.fetch manager zokkaCache customRepositoriesData
case eitherRegistry of
Right latestRegistry ->
return $ Right $ Env cache manager (Online manager) latestRegistry packageOverridesCache
Expand All @@ -463,7 +463,7 @@ initEnvForReactorTH =
return $ Left $ problem

Just cachedRegistry ->
do eitherRegistry <- Registry.update manager zelmCache cachedRegistry
do eitherRegistry <- Registry.update manager zokkaCache cachedRegistry
case eitherRegistry of
Right latestRegistry ->
return $ Right $ Env cache manager (Online manager) latestRegistry packageOverridesCache
Expand Down
Loading

0 comments on commit 0b9fa76

Please sign in to comment.