2012-07-31 12:17:31 -04:00
|
|
|
{- git-annex assistant webapp thread
|
2012-07-25 21:26:13 -04:00
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-06-04 21:02:09 -04:00
|
|
|
{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE CPP #-}
|
2012-07-28 21:21:22 -04:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
2012-07-25 21:26:13 -04:00
|
|
|
|
|
|
|
module Assistant.Threads.WebApp where
|
|
|
|
|
|
|
|
import Assistant.Common
|
2012-07-31 01:11:32 -04:00
|
|
|
import Assistant.WebApp
|
2012-09-02 00:27:48 -04:00
|
|
|
import Assistant.WebApp.Types
|
2012-07-31 01:11:32 -04:00
|
|
|
import Assistant.WebApp.DashBoard
|
|
|
|
import Assistant.WebApp.SideBar
|
|
|
|
import Assistant.WebApp.Notifications
|
2013-03-12 21:51:03 -04:00
|
|
|
import Assistant.WebApp.RepoList
|
2012-07-31 01:11:32 -04:00
|
|
|
import Assistant.WebApp.Configurators
|
2012-08-31 15:17:12 -04:00
|
|
|
import Assistant.WebApp.Configurators.Local
|
|
|
|
import Assistant.WebApp.Configurators.Ssh
|
2012-09-08 00:26:47 -04:00
|
|
|
import Assistant.WebApp.Configurators.Pairing
|
2012-11-24 16:30:15 -04:00
|
|
|
import Assistant.WebApp.Configurators.AWS
|
2013-04-25 12:23:36 -04:00
|
|
|
import Assistant.WebApp.Configurators.IA
|
2012-11-17 15:30:11 -04:00
|
|
|
import Assistant.WebApp.Configurators.WebDAV
|
2012-10-26 14:17:09 -04:00
|
|
|
import Assistant.WebApp.Configurators.XMPP
|
2013-03-03 17:07:27 -04:00
|
|
|
import Assistant.WebApp.Configurators.Preferences
|
2013-03-31 16:38:05 -04:00
|
|
|
import Assistant.WebApp.Configurators.Edit
|
|
|
|
import Assistant.WebApp.Configurators.Delete
|
2012-07-31 02:30:26 -04:00
|
|
|
import Assistant.WebApp.Documentation
|
2013-01-03 15:16:40 -04:00
|
|
|
import Assistant.WebApp.Control
|
2012-09-18 17:50:07 -04:00
|
|
|
import Assistant.WebApp.OtherRepos
|
2012-10-29 19:07:10 -04:00
|
|
|
import Assistant.Types.ThreadedMonad
|
2012-07-25 21:26:13 -04:00
|
|
|
import Utility.WebApp
|
2013-05-12 19:19:28 -04:00
|
|
|
import Utility.Tmp
|
2013-01-03 18:50:30 -04:00
|
|
|
import Utility.FileMode
|
2012-07-26 02:45:01 -04:00
|
|
|
import Git
|
2012-07-25 21:26:13 -04:00
|
|
|
|
|
|
|
import Yesod
|
2013-04-08 15:04:35 -04:00
|
|
|
import Network.Socket (SockAddr, HostName)
|
2012-07-31 01:11:32 -04:00
|
|
|
import Data.Text (pack, unpack)
|
2012-07-26 04:50:09 -04:00
|
|
|
|
2012-07-31 01:11:32 -04:00
|
|
|
mkYesodDispatch "WebApp" $(parseRoutesFile "Assistant/WebApp/routes")
|
2012-07-25 21:26:13 -04:00
|
|
|
|
2012-08-01 16:10:26 -04:00
|
|
|
type Url = String
|
|
|
|
|
2012-10-29 00:15:43 -04:00
|
|
|
webAppThread
|
|
|
|
:: AssistantData
|
2012-09-08 19:57:15 -04:00
|
|
|
-> UrlRenderer
|
2012-10-29 00:15:43 -04:00
|
|
|
-> Bool
|
2013-04-08 15:04:35 -04:00
|
|
|
-> Maybe HostName
|
2013-06-10 23:16:18 -04:00
|
|
|
-> Maybe (IO Url)
|
2012-08-01 16:10:26 -04:00
|
|
|
-> Maybe (Url -> FilePath -> IO ())
|
2012-09-06 14:56:04 -04:00
|
|
|
-> NamedThread
|
2013-04-08 15:04:35 -04:00
|
|
|
webAppThread assistantdata urlrenderer noannex listenhost postfirstrun onstartup = thread $ liftIO $ do
|
2013-05-02 16:47:42 -04:00
|
|
|
#ifdef __ANDROID__
|
|
|
|
when (isJust listenhost) $
|
|
|
|
-- See Utility.WebApp
|
|
|
|
error "Sorry, --listen is not currently supported on Android"
|
|
|
|
#endif
|
2012-07-31 12:17:31 -04:00
|
|
|
webapp <- WebApp
|
2012-10-29 00:15:43 -04:00
|
|
|
<$> pure assistantdata
|
2012-07-31 12:17:31 -04:00
|
|
|
<*> (pack <$> genRandomToken)
|
2012-10-29 00:15:43 -04:00
|
|
|
<*> getreldir
|
2013-04-17 01:37:08 -04:00
|
|
|
<*> pure staticRoutes
|
2012-08-01 16:10:26 -04:00
|
|
|
<*> pure postfirstrun
|
2012-10-29 00:15:43 -04:00
|
|
|
<*> pure noannex
|
2013-04-08 15:04:35 -04:00
|
|
|
<*> pure listenhost
|
2012-09-08 19:57:15 -04:00
|
|
|
setUrlRenderer urlrenderer $ yesodRender webapp (pack "")
|
2012-07-26 23:55:51 -04:00
|
|
|
app <- toWaiAppPlain webapp
|
2012-07-25 21:26:13 -04:00
|
|
|
app' <- ifM debugEnabled
|
|
|
|
( return $ httpDebugLogger app
|
|
|
|
, return app
|
|
|
|
)
|
2013-04-08 15:04:35 -04:00
|
|
|
runWebApp listenhost app' $ \addr -> if noannex
|
2013-05-12 19:19:28 -04:00
|
|
|
then withTmpFile "webapp.html" $ \tmpfile _ ->
|
2013-01-09 23:17:52 -04:00
|
|
|
go addr webapp tmpfile Nothing
|
2012-10-29 00:15:43 -04:00
|
|
|
else do
|
|
|
|
let st = threadState assistantdata
|
2012-09-18 17:50:07 -04:00
|
|
|
htmlshim <- runThreadState st $ fromRepo gitAnnexHtmlShim
|
|
|
|
urlfile <- runThreadState st $ fromRepo gitAnnexUrlFile
|
2013-01-09 23:17:52 -04:00
|
|
|
go addr webapp htmlshim (Just urlfile)
|
2012-10-29 14:30:10 -04:00
|
|
|
where
|
2013-01-26 17:09:33 +11:00
|
|
|
thread = namedThread "WebApp"
|
2012-10-29 14:30:10 -04:00
|
|
|
getreldir
|
|
|
|
| noannex = return Nothing
|
|
|
|
| otherwise = Just <$>
|
|
|
|
(relHome =<< absPath
|
|
|
|
=<< runThreadState (threadState assistantdata) (fromRepo repoPath))
|
2013-01-09 23:17:52 -04:00
|
|
|
go addr webapp htmlshim urlfile = do
|
|
|
|
let url = myUrl webapp addr
|
2013-01-03 18:50:30 -04:00
|
|
|
maybe noop (`writeFileProtected` url) urlfile
|
|
|
|
writeHtmlShim "Starting webapp..." url htmlshim
|
2012-10-29 14:30:10 -04:00
|
|
|
maybe noop (\a -> a url htmlshim) onstartup
|
2012-07-25 23:13:01 -04:00
|
|
|
|
2013-01-09 23:17:52 -04:00
|
|
|
myUrl :: WebApp -> SockAddr -> Url
|
2013-03-12 22:18:36 -04:00
|
|
|
myUrl webapp addr = unpack $ yesodRender webapp urlbase DashboardR []
|
2012-10-29 14:30:10 -04:00
|
|
|
where
|
2013-01-09 23:17:52 -04:00
|
|
|
urlbase = pack $ "http://" ++ show addr
|