@@ -7,8 +7,8 @@ module Distribution.Server (
77 checkpoint ,
88
99 -- * Server configuration
10- Config (.. ),
11- defaultConfig ,
10+ ServerConfig (.. ),
11+ defaultServerConfig ,
1212 hasSavedState ,
1313
1414 -- * First time initialisation of the database
@@ -17,29 +17,23 @@ module Distribution.Server (
1717 initState ,
1818 ) where
1919
20- import Distribution.Package (packageName )
2120import Happstack.Server hiding (port , host )
2221import qualified Happstack.Server
2322import Happstack.State hiding (Version )
2423
25- import Distribution.Server.ServerParts (guardAuth )
26- import qualified Distribution.Server.Import as Import ( importTar )
24+ import qualified Distribution.Server.Import as Import (importTar )
2725
2826import Distribution.Server.Packages.ServerParts
2927import Distribution.Server.Users.ServerParts
30- import Distribution.Server.Distributions.ServerParts
31- import Distribution.Server.Users.Permissions (GroupName (.. ))
28+ -- import Distribution.Server.Distributions.ServerParts -- this will take some effort to revamp
3229
3330import qualified Distribution.Server.Feature as Feature
3431import qualified Distribution.Server.Features as Features
3532
3633import Distribution.Server.State as State
37- import Distribution.Server.Packages.State as State hiding (buildReports , bulkImport )
34+ import Distribution.Server.Packages.State as State hiding (bulkImport )
3835import Distribution.Server.Users.State as State
3936import qualified Distribution.Server.Cache as Cache
40- import Distribution.Server.Packages.Types
41- ( PkgInfo (.. ) )
42- import qualified Distribution.Server.ResourceTypes as Resource
4337import qualified Distribution.Server.Util.BlobStorage as BlobStorage
4438import Distribution.Server.Util.BlobStorage (BlobStorage )
4539import qualified Distribution.Server.BulkImport as BulkImport
@@ -49,62 +43,60 @@ import qualified Distribution.Server.Users.Users as Users
4943import qualified Distribution.Server.Users.Types as Users
5044
5145import Distribution.Server.Export.ServerParts (export )
52- import Distribution.Server.Auth.Types (PasswdPlain (.. ))
46+ import qualified Distribution.Server.Auth.Types as Auth
47+ import qualified Distribution.Server.Auth.Basic as Auth
48+ import qualified Distribution.Server.Auth.Crypt as Auth
5349
54- import Distribution.Server.Resource (addResponse , serverTreeEmpty , renderServerTree , spiffyResources )
55- import Data.List (foldl' )
50+ import Distribution.Server.Resource -- (addResponse, serverTreeEmpty, renderServerTree)
51+ -- import Data.List (foldl')
5652
5753import System.FilePath ((</>) )
58- import System.Directory
59- ( createDirectoryIfMissing , doesDirectoryExist )
54+ import System.Directory (createDirectoryIfMissing , doesDirectoryExist )
6055import Control.Concurrent.MVar (MVar )
6156import Control.Monad.Trans
6257import Control.Monad (when , msum )
6358import Data.ByteString.Lazy.Char8 (ByteString )
64- import Network.URI
65- ( URIAuth (URIAuth ) )
66- import Network.BSD
67- ( getHostName )
68- import qualified Data.Map as Map (empty )
59+ import Network.URI (URIAuth (URIAuth ))
60+ import Network.BSD (getHostName )
61+ import Data.Char (toUpper )
6962
7063import qualified Data.ByteString.Lazy.Char8 as BS
7164
7265import Paths_hackage_server (getDataDir )
7366
74- data Config = Config {
67+ data ServerConfig = ServerConfig {
7568 confHostName :: String ,
7669 confPortNum :: Int ,
7770 confStateDir :: FilePath ,
7871 confStaticDir :: FilePath
7972} deriving (Show )
8073
81- confHappsStateDir , confBlobStoreDir :: Config -> FilePath
74+ confHappsStateDir , confBlobStoreDir :: ServerConfig -> FilePath
8275confHappsStateDir config = confStateDir config </> " db"
8376confBlobStoreDir config = confStateDir config </> " blobs"
8477
85- defaultConfig :: IO Config
86- defaultConfig = do
78+ defaultServerConfig :: IO ServerConfig
79+ defaultServerConfig = do
8780 hostName <- getHostName
8881 dataDir <- getDataDir
89- return Config {
82+ return ServerConfig {
9083 confHostName = hostName,
9184 confPortNum = 8080 ,
9285 confStateDir = " state" ,
9386 confStaticDir = dataDir </> " static"
9487 }
9588
9689data Server = Server {
97- serverTxControl :: MVar TxControl ,
98- serverFeatureConfig :: Feature. Config ,
99- serverPort :: Int ,
100- serverCache :: Cache. Cache
90+ serverTxControl :: MVar TxControl ,
91+ serverPort :: Int ,
92+ serverConfig :: Config
10193}
10294
10395-- | If we made a server instance from this 'Config', would we find some
10496-- existing saved state or would it be a totally clean instance with no
10597-- existing state.
10698--
107- hasSavedState :: Config -> IO Bool
99+ hasSavedState :: ServerConfig -> IO Bool
108100hasSavedState = doesDirectoryExist . confHappsStateDir
109101
110102-- | Make a server instance from the server configuration.
@@ -115,9 +107,8 @@ hasSavedState = doesDirectoryExist . confHappsStateDir
115107-- Note: the server instance must eventually be 'shutdown' or you'll end up
116108-- with stale lock files.
117109--
118- initialise :: Config -> IO Server
119- initialise config@ (Config hostName portNum stateDir staticDir) = do
120-
110+ initialise :: ServerConfig -> IO Server
111+ initialise config@ (ServerConfig hostName portNum stateDir staticDir) = do
121112 exists <- doesDirectoryExist staticDir
122113 when (not exists) $
123114 fail $ " The static files directory " ++ staticDir ++ " does not exist."
@@ -126,17 +117,20 @@ initialise config@(Config hostName portNum stateDir staticDir) = do
126117 store <- BlobStorage. open blobStoreDir
127118
128119 txCtl <- runTxSystem (Queue (FileSaver happsStateDir)) hackageEntryPoint
129- cache <- Cache. new =<< stateToCache hostURI =<< query GetPackagesState
120+ cache <- do
121+ packages <- query GetPackagesState
122+ users <- query GetUserDb
123+ Cache. new =<< stateToCache hostURI packages users
130124
131125 return Server {
132126 serverTxControl = txCtl,
133- serverFeatureConfig = Feature. Config {
134- Feature. serverStore = store,
135- Feature. serverStaticDir = staticDir,
136- Feature. serverURI = hostURI
137- },
138127 serverPort = portNum,
139- serverCache = cache
128+ serverConfig = Config {
129+ serverStore = store,
130+ serverStaticDir = staticDir,
131+ serverURI = hostURI,
132+ serverCache = cache
133+ }
140134 }
141135
142136 where
@@ -156,13 +150,20 @@ run server = simpleHTTP conf $ mungeRequest $ impl server
156150 where
157151 conf = nullConf { Happstack.Server. port = serverPort server }
158152 mungeRequest = localRq mungeMethod
153+ -- this is not restful.
159154 mungeMethod req = case (rqMethod req, lookup " _method" (rqInputs req)) of
160- (POST , Just input) -> case reads ( BS. unpack ( inputValue input)) of
155+ (POST , Just input) -> case reads . map toUpper . BS. unpack $ inputValue input of
161156 [(newMethod, " " )] -> req { rqMethod = newMethod }
162157 _ -> req
163158 _ -> req
164159 -- todo: given a .json or .html suffix, munge it into an Accept header
160+ -- can use MessageWrap.pathEls to reparse rqPath
161+
165162
163+ {- case lookup "_patharg" (rqInputs req) of
164+ Just param -> req' { rqUri = rqUri req </> SURI.escape param, rqPath = rqPath req ++ [param] }
165+ _ -> req'
166+ where req' = -}
166167-- | Perform a clean shutdown of the server.
167168--
168169shutdown :: Server -> IO ()
@@ -181,7 +182,7 @@ bulkImport :: Server
181182 -> Maybe String -- users
182183 -> Maybe String -- admin users
183184 -> IO [UploadLog. Entry ]
184- bulkImport (Server _ ( Feature. Config store _ host) _ cache)
185+ bulkImport (Server _ _ ( Config store _ host cache) )
185186 indexFile logFile archiveFile htPasswdFile adminsFile = do
186187 pkgIndex <- either fail return (BulkImport. importPkgIndex indexFile)
187188 uploadLog <- either fail return (BulkImport. importUploadLog logFile)
@@ -192,19 +193,18 @@ bulkImport (Server _ (Feature.Config store _ host) _ cache)
192193 (pkgsInfo, users, badLogEntries) <- either fail return
193194 (BulkImport. mergePkgInfo pkgIndex uploadLog tarballs accounts)
194195
195- update $ BulkImport pkgsInfo users
196+ update $ BulkImport pkgsInfo
197+ update $ ReplaceUserDb users
196198
197- admPerms <- case admins of
198- Nothing -> return []
199+ case admins of
200+ Nothing -> return ()
199201 Just adminUsers -> do
200- state <- query GetPackagesState
201- uids <- either fail return $ lookupUsers (userDb state) adminUsers
202- return $ map (\ uid -> (uid, Administrator )) uids
203-
204- let uploadPerms
205- = map (\ pkg -> (pkgUploadUser pkg, PackageMaintainer (packageName pkg))) pkgsInfo
202+ userDb <- query GetUserDb
203+ uids <- either fail return $ lookupUsers userDb adminUsers
204+ mapM_ (\ uid -> update $ AddHackageAdmin uid) uids
206205
207- update $ BulkImportPermissions (admPerms ++ uploadPerms)
206+ -- let uploadPerms = map (\pkg -> (pkgUploadUser pkg, PackageMaintainer (packageName pkg))) pkgsInfo
207+ -- update $ BulkImportPermissions (admPerms ++ uploadPerms)
208208
209209 updateCache cache host
210210
@@ -221,7 +221,7 @@ bulkImport (Server _ (Feature.Config store _ host) _ cache)
221221 Just uid -> Right uid
222222
223223importTar :: Server -> ByteString -> IO (Maybe String )
224- importTar (Server _ ( Feature. Config store _ host) _ cache) tar = do
224+ importTar (Server _ _ ( Config store _ host cache) ) tar = do
225225 res <- Import. importTar store tar
226226 case res of
227227 Nothing -> updateCache cache host
@@ -231,66 +231,56 @@ importTar (Server _ (Feature.Config store _ host) _ cache) tar = do
231231-- An alternative to an import.
232232-- Starts the server off to a sane initial state.
233233initState :: MonadIO m => Server -> m ()
234- initState (Server _ ( Feature. Config _ _ host) _ cache) = do
234+ initState (Server _ _ ( Config _ _ host cache) ) = do
235235 -- clear off existing state
236- update $ BulkImport [] Users. empty
237- update $ BulkImportPermissions []
236+ update $ BulkImport []
237+ update $ ReplaceUserDb Users. empty
238+ -- update $ BulkImportPermissions []
238239
239240 -- create default admin user
240241 let userName = Users. UserName " admin"
241- userAuth <- newPasswd ( PasswdPlain " admin" )
242- res <- update $ AddUser userName userAuth
242+ userAuth = Auth. newDigestPass userName ( Auth. PasswdPlain " admin" ) " hackage "
243+ res <- update $ AddUser userName ( Users. UserAuth userAuth Auth. DigestAuth )
243244
244245 case res of
245- Just user -> update $ AddToGroup Administrator user
246+ Just user -> update $ State. AddHackageAdmin user
246247 _ -> fail " Failed to create admin user!"
247248
248249 updateCache cache host
249250
250251
251252impl :: Server -> ServerPart Response
252- impl server = flip renderServerTree Map. empty $ spiffyResources $ foldl' ( flip $ uncurry addResponse) serverTreeEmpty $ ([] , core server): concatMap ( Feature. serverParts) Features. hackageFeatures
253+ impl server = renderServerTree (serverConfig server) [] $ foldr ( uncurry addResponse) serverTreeEmpty $ ([] , \ _ _ -> core server): concatMap Feature. locations Features. hackageFeatures
253254
254255core :: Server -> ServerPart Response
255- core (Server _ (Feature. Config store static host) _ cache) = msum
256- [ dir " packages" $
257- methodSP GET $
258- ok . Cache. packagesPage =<< Cache. get cache
259- , dir " package" $ msum
256+ core (Server _ _ (Config store static _ cache)) = msum
257+ {- [ dir "package" $ msum
260258 [ path $ msum . handlePackageById store
261259 , path $ servePackage store
262- ]
263- , dir " buildreports" $ msum (buildReports store)
260+ ]-}
261+ [ dir " buildreports" $ msum (buildReports store)
264262-- , dir "groups" (groupInterface)
265263 , dir " recent.rss" $ msum
266264 [ methodSP GET $ ok . Cache. packagesFeed =<< Cache. get cache ]
267265 , dir " recent.html" $ msum
268266 [ methodSP GET $ ok . Cache. recentChanges =<< Cache. get cache ]
269- , dir " upload" $ msum
270- [ uploadPackage store cache host ]
271- , dir " 00-index.tar.gz" $ msum
272- [ methodSP GET $ do
273- cacheState <- Cache. get cache
274- ok $ toResponse $ Resource. IndexTarball (Cache. indexTarball cacheState)
275- ]
276267 , dir " admin" $ admin static store
277268 , dir " check" checkPackage
278- , dir " htpasswd" $ msum
279- [ changePassword ]
280- , dir " distro" distros
269+ -- , dir "htpasswd" $ msum [ changePassword ]
270+ -- , dir "distro" distros
281271 , fileServe [" hackage.html" ] static
282272 ]
283273
284274-- Top level server part for administrative actions under the "admin"
285275-- directory
286276admin :: FilePath -> BlobStorage -> ServerPart Response
287277admin static storage = do
288-
289- guardAuth [ Administrator ]
290-
291- msum
292- [ dir " users" userAdmin
293- , dir " export.tar.gz" (export storage)
294- , adminDist
295- , fileServe [" admin.html" ] static
296- ]
278+ userDb <- query State. GetUserDb
279+ let admins = Users. adminList userDb
280+ Auth. requireHackageAuth userDb ( Just admins) Nothing
281+ msum
282+ [ dir " users" userAdmin
283+ , dir " export.tar.gz" (export storage)
284+ -- , adminDist
285+ , fileServe [" admin.html" ] static
286+ ]
0 commit comments