Scaffold update

This commit is contained in:
Michael Snoyman 2014-07-15 19:06:27 +03:00
parent 4745676200
commit 972efd0ca4
6 changed files with 208 additions and 114 deletions

View File

@ -211,6 +211,13 @@ instance Yesod App where
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- Routes not requiring authenitcation.
isAuthorized (AuthR _) _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
-- Default to Authorized for now.
isAuthorized _ _ = return Authorized
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
@ -609,17 +616,21 @@ combineScripts = combineScripts' development combineSettings
--
-- cabal repl --ghc-options="-O0 -fobject-code"
--
-- run with:
--
-- :l DevelMain
-- DevelMain.update
--
-- You will need to add these packages to your .cabal file
-- * foreign-store (very light-weight)
-- * foreign-store >= 0.1 (very light-weight)
-- * warp (you already depend on this, it just isn't in your .cabal file)
--
-- If you don't use cabal repl, you will need
-- to run the following in GHCi or to add it to
-- your .ghci file.
-- to add settings to your .ghci file.
--
-- :set -DDEVELOPMENT
--
-- There is more information about this approach,
-- There is more information about using ghci
-- on the wiki: https://github.com/yesodweb/yesod/wiki/ghci
module DevelMain where
@ -633,27 +644,31 @@ import Foreign.Store
import Network.Wai.Handler.Warp
-- | Start or restart the server.
-- A Store holds onto some data across ghci reloads
update :: IO ()
update = do
mtidStore <- lookupStore tid_1
mtidStore <- lookupStore tidStoreNum
case mtidStore of
-- no server running
Nothing -> do
done <- newEmptyMVar
_done_0 <- newStore done
done <- storeAction doneStore newEmptyMVar
tid <- start done
tidRef <- newIORef tid
_tid_1 <- newStore tidRef
_ <- storeAction (Store tidStoreNum) (newIORef tid)
return ()
Just tidStore -> do
tidRef <- readStore tidStore
tid <- readIORef tidRef
done <- readStore (Store done_0)
killThread tid
takeMVar done
newTid <- start done
writeIORef tidRef newTid
where tid_1 = 1
done_0 = 0
-- server is already running
Just tidStore ->
-- shut the server down with killThread and wait for the done signal
modifyStoredIORef tidStore $ \tid -> do
killThread tid
withStore doneStore takeMVar >> readStore doneStore >>= start
where
doneStore = Store 0
tidStoreNum = 1
modifyStoredIORef :: Store (IORef a) -> (a -> IO a) -> IO ()
modifyStoredIORef store f = withStore store $ \ref -> do
v <- readIORef ref
f v >>= writeIORef ref
-- | Start the server in a separate thread.
start :: MVar () -- ^ Written to when the thread is killed.

View File

@ -218,6 +218,13 @@ instance Yesod App where
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- Routes not requiring authenitcation.
isAuthorized (AuthR _) _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
-- Default to Authorized for now.
isAuthorized _ _ = return Authorized
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
@ -365,6 +372,7 @@ import Yesod
import Data.Text (Text)
import Database.Persist.Quasi
import Data.Typeable (Typeable)
import Prelude
-- You can define all of your database entities in the entities file.
-- You can find more information on persistent and how to declare entities
@ -612,17 +620,21 @@ combineScripts = combineScripts' development combineSettings
--
-- cabal repl --ghc-options="-O0 -fobject-code"
--
-- run with:
--
-- :l DevelMain
-- DevelMain.update
--
-- You will need to add these packages to your .cabal file
-- * foreign-store (very light-weight)
-- * foreign-store >= 0.1 (very light-weight)
-- * warp (you already depend on this, it just isn't in your .cabal file)
--
-- If you don't use cabal repl, you will need
-- to run the following in GHCi or to add it to
-- your .ghci file.
-- to add settings to your .ghci file.
--
-- :set -DDEVELOPMENT
--
-- There is more information about this approach,
-- There is more information about using ghci
-- on the wiki: https://github.com/yesodweb/yesod/wiki/ghci
module DevelMain where
@ -636,27 +648,31 @@ import Foreign.Store
import Network.Wai.Handler.Warp
-- | Start or restart the server.
-- A Store holds onto some data across ghci reloads
update :: IO ()
update = do
mtidStore <- lookupStore tid_1
mtidStore <- lookupStore tidStoreNum
case mtidStore of
-- no server running
Nothing -> do
done <- newEmptyMVar
_done_0 <- newStore done
done <- storeAction doneStore newEmptyMVar
tid <- start done
tidRef <- newIORef tid
_tid_1 <- newStore tidRef
_ <- storeAction (Store tidStoreNum) (newIORef tid)
return ()
Just tidStore -> do
tidRef <- readStore tidStore
tid <- readIORef tidRef
done <- readStore (Store done_0)
killThread tid
takeMVar done
newTid <- start done
writeIORef tidRef newTid
where tid_1 = 1
done_0 = 0
-- server is already running
Just tidStore ->
-- shut the server down with killThread and wait for the done signal
modifyStoredIORef tidStore $ \tid -> do
killThread tid
withStore doneStore takeMVar >> readStore doneStore >>= start
where
doneStore = Store 0
tidStoreNum = 1
modifyStoredIORef :: Store (IORef a) -> (a -> IO a) -> IO ()
modifyStoredIORef store f = withStore store $ \ref -> do
v <- readIORef ref
f v >>= writeIORef ref
-- | Start the server in a separate thread.
start :: MVar () -- ^ Written to when the thread is killed.

View File

@ -222,6 +222,13 @@ instance Yesod App where
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- Routes not requiring authenitcation.
isAuthorized (AuthR _) _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
-- Default to Authorized for now.
isAuthorized _ _ = return Authorized
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
@ -397,6 +404,7 @@ import Yesod
import Data.Text (Text)
import Database.Persist.Quasi
import Data.Typeable (Typeable)
import Prelude
-- You can define all of your database entities in the entities file.
-- You can find more information on persistent and how to declare entities
@ -661,17 +669,21 @@ combineScripts = combineScripts' development combineSettings
--
-- cabal repl --ghc-options="-O0 -fobject-code"
--
-- run with:
--
-- :l DevelMain
-- DevelMain.update
--
-- You will need to add these packages to your .cabal file
-- * foreign-store (very light-weight)
-- * foreign-store >= 0.1 (very light-weight)
-- * warp (you already depend on this, it just isn't in your .cabal file)
--
-- If you don't use cabal repl, you will need
-- to run the following in GHCi or to add it to
-- your .ghci file.
-- to add settings to your .ghci file.
--
-- :set -DDEVELOPMENT
--
-- There is more information about this approach,
-- There is more information about using ghci
-- on the wiki: https://github.com/yesodweb/yesod/wiki/ghci
module DevelMain where
@ -685,27 +697,31 @@ import Foreign.Store
import Network.Wai.Handler.Warp
-- | Start or restart the server.
-- A Store holds onto some data across ghci reloads
update :: IO ()
update = do
mtidStore <- lookupStore tid_1
mtidStore <- lookupStore tidStoreNum
case mtidStore of
-- no server running
Nothing -> do
done <- newEmptyMVar
_done_0 <- newStore done
done <- storeAction doneStore newEmptyMVar
tid <- start done
tidRef <- newIORef tid
_tid_1 <- newStore tidRef
_ <- storeAction (Store tidStoreNum) (newIORef tid)
return ()
Just tidStore -> do
tidRef <- readStore tidStore
tid <- readIORef tidRef
done <- readStore (Store done_0)
killThread tid
takeMVar done
newTid <- start done
writeIORef tidRef newTid
where tid_1 = 1
done_0 = 0
-- server is already running
Just tidStore ->
-- shut the server down with killThread and wait for the done signal
modifyStoredIORef tidStore $ \tid -> do
killThread tid
withStore doneStore takeMVar >> readStore doneStore >>= start
where
doneStore = Store 0
tidStoreNum = 1
modifyStoredIORef :: Store (IORef a) -> (a -> IO a) -> IO ()
modifyStoredIORef store f = withStore store $ \ref -> do
v <- readIORef ref
f v >>= writeIORef ref
-- | Start the server in a separate thread.
start :: MVar () -- ^ Written to when the thread is killed.

View File

@ -218,6 +218,13 @@ instance Yesod App where
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- Routes not requiring authenitcation.
isAuthorized (AuthR _) _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
-- Default to Authorized for now.
isAuthorized _ _ = return Authorized
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
@ -365,6 +372,7 @@ import Yesod
import Data.Text (Text)
import Database.Persist.Quasi
import Data.Typeable (Typeable)
import Prelude
-- You can define all of your database entities in the entities file.
-- You can find more information on persistent and how to declare entities
@ -612,17 +620,21 @@ combineScripts = combineScripts' development combineSettings
--
-- cabal repl --ghc-options="-O0 -fobject-code"
--
-- run with:
--
-- :l DevelMain
-- DevelMain.update
--
-- You will need to add these packages to your .cabal file
-- * foreign-store (very light-weight)
-- * foreign-store >= 0.1 (very light-weight)
-- * warp (you already depend on this, it just isn't in your .cabal file)
--
-- If you don't use cabal repl, you will need
-- to run the following in GHCi or to add it to
-- your .ghci file.
-- to add settings to your .ghci file.
--
-- :set -DDEVELOPMENT
--
-- There is more information about this approach,
-- There is more information about using ghci
-- on the wiki: https://github.com/yesodweb/yesod/wiki/ghci
module DevelMain where
@ -636,27 +648,31 @@ import Foreign.Store
import Network.Wai.Handler.Warp
-- | Start or restart the server.
-- A Store holds onto some data across ghci reloads
update :: IO ()
update = do
mtidStore <- lookupStore tid_1
mtidStore <- lookupStore tidStoreNum
case mtidStore of
-- no server running
Nothing -> do
done <- newEmptyMVar
_done_0 <- newStore done
done <- storeAction doneStore newEmptyMVar
tid <- start done
tidRef <- newIORef tid
_tid_1 <- newStore tidRef
_ <- storeAction (Store tidStoreNum) (newIORef tid)
return ()
Just tidStore -> do
tidRef <- readStore tidStore
tid <- readIORef tidRef
done <- readStore (Store done_0)
killThread tid
takeMVar done
newTid <- start done
writeIORef tidRef newTid
where tid_1 = 1
done_0 = 0
-- server is already running
Just tidStore ->
-- shut the server down with killThread and wait for the done signal
modifyStoredIORef tidStore $ \tid -> do
killThread tid
withStore doneStore takeMVar >> readStore doneStore >>= start
where
doneStore = Store 0
tidStoreNum = 1
modifyStoredIORef :: Store (IORef a) -> (a -> IO a) -> IO ()
modifyStoredIORef store f = withStore store $ \ref -> do
v <- readIORef ref
f v >>= writeIORef ref
-- | Start the server in a separate thread.
start :: MVar () -- ^ Written to when the thread is killed.

View File

@ -196,6 +196,13 @@ instance Yesod App where
Just $ uncurry (joinPath y (Settings.staticRoot $ settings y)) $ renderRoute s
urlRenderOverride _ _ = Nothing
-- Routes not requiring authenitcation.
isAuthorized (AuthR _) _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
-- Default to Authorized for now.
isAuthorized _ _ = return Authorized
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
@ -531,17 +538,21 @@ combineScripts = combineScripts' development combineSettings
--
-- cabal repl --ghc-options="-O0 -fobject-code"
--
-- run with:
--
-- :l DevelMain
-- DevelMain.update
--
-- You will need to add these packages to your .cabal file
-- * foreign-store (very light-weight)
-- * foreign-store >= 0.1 (very light-weight)
-- * warp (you already depend on this, it just isn't in your .cabal file)
--
-- If you don't use cabal repl, you will need
-- to run the following in GHCi or to add it to
-- your .ghci file.
-- to add settings to your .ghci file.
--
-- :set -DDEVELOPMENT
--
-- There is more information about this approach,
-- There is more information about using ghci
-- on the wiki: https://github.com/yesodweb/yesod/wiki/ghci
module DevelMain where
@ -555,27 +566,31 @@ import Foreign.Store
import Network.Wai.Handler.Warp
-- | Start or restart the server.
-- A Store holds onto some data across ghci reloads
update :: IO ()
update = do
mtidStore <- lookupStore tid_1
mtidStore <- lookupStore tidStoreNum
case mtidStore of
-- no server running
Nothing -> do
done <- newEmptyMVar
_done_0 <- newStore done
done <- storeAction doneStore newEmptyMVar
tid <- start done
tidRef <- newIORef tid
_tid_1 <- newStore tidRef
_ <- storeAction (Store tidStoreNum) (newIORef tid)
return ()
Just tidStore -> do
tidRef <- readStore tidStore
tid <- readIORef tidRef
done <- readStore (Store done_0)
killThread tid
takeMVar done
newTid <- start done
writeIORef tidRef newTid
where tid_1 = 1
done_0 = 0
-- server is already running
Just tidStore ->
-- shut the server down with killThread and wait for the done signal
modifyStoredIORef tidStore $ \tid -> do
killThread tid
withStore doneStore takeMVar >> readStore doneStore >>= start
where
doneStore = Store 0
tidStoreNum = 1
modifyStoredIORef :: Store (IORef a) -> (a -> IO a) -> IO ()
modifyStoredIORef store f = withStore store $ \ref -> do
v <- readIORef ref
f v >>= writeIORef ref
-- | Start the server in a separate thread.
start :: MVar () -- ^ Written to when the thread is killed.

View File

@ -218,6 +218,13 @@ instance Yesod App where
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- Routes not requiring authenitcation.
isAuthorized (AuthR _) _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
-- Default to Authorized for now.
isAuthorized _ _ = return Authorized
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
@ -365,6 +372,7 @@ import Yesod
import Data.Text (Text)
import Database.Persist.Quasi
import Data.Typeable (Typeable)
import Prelude
-- You can define all of your database entities in the entities file.
-- You can find more information on persistent and how to declare entities
@ -612,17 +620,21 @@ combineScripts = combineScripts' development combineSettings
--
-- cabal repl --ghc-options="-O0 -fobject-code"
--
-- run with:
--
-- :l DevelMain
-- DevelMain.update
--
-- You will need to add these packages to your .cabal file
-- * foreign-store (very light-weight)
-- * foreign-store >= 0.1 (very light-weight)
-- * warp (you already depend on this, it just isn't in your .cabal file)
--
-- If you don't use cabal repl, you will need
-- to run the following in GHCi or to add it to
-- your .ghci file.
-- to add settings to your .ghci file.
--
-- :set -DDEVELOPMENT
--
-- There is more information about this approach,
-- There is more information about using ghci
-- on the wiki: https://github.com/yesodweb/yesod/wiki/ghci
module DevelMain where
@ -636,27 +648,31 @@ import Foreign.Store
import Network.Wai.Handler.Warp
-- | Start or restart the server.
-- A Store holds onto some data across ghci reloads
update :: IO ()
update = do
mtidStore <- lookupStore tid_1
mtidStore <- lookupStore tidStoreNum
case mtidStore of
-- no server running
Nothing -> do
done <- newEmptyMVar
_done_0 <- newStore done
done <- storeAction doneStore newEmptyMVar
tid <- start done
tidRef <- newIORef tid
_tid_1 <- newStore tidRef
_ <- storeAction (Store tidStoreNum) (newIORef tid)
return ()
Just tidStore -> do
tidRef <- readStore tidStore
tid <- readIORef tidRef
done <- readStore (Store done_0)
killThread tid
takeMVar done
newTid <- start done
writeIORef tidRef newTid
where tid_1 = 1
done_0 = 0
-- server is already running
Just tidStore ->
-- shut the server down with killThread and wait for the done signal
modifyStoredIORef tidStore $ \tid -> do
killThread tid
withStore doneStore takeMVar >> readStore doneStore >>= start
where
doneStore = Store 0
tidStoreNum = 1
modifyStoredIORef :: Store (IORef a) -> (a -> IO a) -> IO ()
modifyStoredIORef store f = withStore store $ \ref -> do
v <- readIORef ref
f v >>= writeIORef ref
-- | Start the server in a separate thread.
start :: MVar () -- ^ Written to when the thread is killed.