mirror of
https://code.sup39.dev/repos/Wqawg
synced 2024-12-27 15:34:51 +09:00
Put all modules under a new Vervis module
This commit is contained in:
parent
9154ad8f8b
commit
004fdb118e
20 changed files with 65 additions and 61 deletions
|
@ -46,7 +46,7 @@
|
||||||
module DevelMain where
|
module DevelMain where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
import Application (getApplicationRepl, shutdownApp)
|
import Vervis.Application (getApplicationRepl, shutdownApp)
|
||||||
|
|
||||||
import Control.Exception (finally)
|
import Control.Exception (finally)
|
||||||
import Control.Monad ((>=>))
|
import Control.Monad ((>=>))
|
||||||
|
|
|
@ -15,7 +15,7 @@
|
||||||
|
|
||||||
{-# LANGUAGE PackageImports #-}
|
{-# LANGUAGE PackageImports #-}
|
||||||
|
|
||||||
import "vervis" Application (develMain)
|
import "vervis" Vervis.Application (develMain)
|
||||||
import Prelude (IO)
|
import Prelude (IO)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
|
|
@ -13,8 +13,8 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
import Prelude (IO)
|
import Prelude (IO)
|
||||||
import Application (appMain)
|
import Vervis.Application (appMain)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = appMain
|
main = appMain
|
||||||
|
|
|
@ -15,7 +15,7 @@
|
||||||
|
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
module Application
|
module Vervis.Application
|
||||||
( getApplicationDev
|
( getApplicationDev
|
||||||
, appMain
|
, appMain
|
||||||
, develMain
|
, develMain
|
||||||
|
@ -33,7 +33,7 @@ where
|
||||||
import Control.Monad.Logger (liftLoc, runLoggingT)
|
import Control.Monad.Logger (liftLoc, runLoggingT)
|
||||||
import Database.Persist.Postgresql (createPostgresqlPool, pgConnStr,
|
import Database.Persist.Postgresql (createPostgresqlPool, pgConnStr,
|
||||||
pgPoolSize, runSqlPool)
|
pgPoolSize, runSqlPool)
|
||||||
import Import
|
import Vervis.Import
|
||||||
import Language.Haskell.TH.Syntax (qLocation)
|
import Language.Haskell.TH.Syntax (qLocation)
|
||||||
import Network.Wai (Middleware)
|
import Network.Wai (Middleware)
|
||||||
import Network.Wai.Handler.Warp (Settings, defaultSettings,
|
import Network.Wai.Handler.Warp (Settings, defaultSettings,
|
||||||
|
@ -49,10 +49,10 @@ import System.Log.FastLogger (defaultBufSize, newStdoutLoggerSet,
|
||||||
|
|
||||||
-- Import all relevant handler modules here.
|
-- Import all relevant handler modules here.
|
||||||
-- Don't forget to add new modules to your cabal file!
|
-- Don't forget to add new modules to your cabal file!
|
||||||
import Handler.Common
|
import Vervis.Handler.Common
|
||||||
import Handler.Home
|
import Vervis.Handler.Home
|
||||||
import Handler.Person
|
import Vervis.Handler.Person
|
||||||
import Handler.Project
|
import Vervis.Handler.Project
|
||||||
|
|
||||||
-- This line actually creates our YesodDispatch instance. It is the second half
|
-- This line actually creates our YesodDispatch instance. It is the second half
|
||||||
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
|
@ -13,13 +13,13 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Field
|
module Vervis.Field
|
||||||
( loginField
|
( loginField
|
||||||
, passField
|
, passField
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Import
|
import Vervis.Import
|
||||||
|
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
import Data.Char.Local (isAsciiLetter)
|
import Data.Char.Local (isAsciiLetter)
|
|
@ -13,15 +13,15 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Form
|
module Vervis.Form
|
||||||
( PersonNew (..)
|
( PersonNew (..)
|
||||||
, formPersonNew
|
, formPersonNew
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Import
|
import Vervis.Import
|
||||||
|
|
||||||
import Field
|
import Vervis.Field
|
||||||
|
|
||||||
data PersonNew = PersonNew
|
data PersonNew = PersonNew
|
||||||
{ uLogin :: Text
|
{ uLogin :: Text
|
|
@ -13,9 +13,9 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Foundation where
|
module Vervis.Foundation where
|
||||||
|
|
||||||
import Import.NoFoundation
|
import Vervis.Import.NoFoundation
|
||||||
import Database.Persist.Sql (ConnectionPool, runSqlPool)
|
import Database.Persist.Sql (ConnectionPool, runSqlPool)
|
||||||
import Text.Hamlet (hamletFile)
|
import Text.Hamlet (hamletFile)
|
||||||
import Text.Jasmine (minifym)
|
import Text.Jasmine (minifym)
|
|
@ -17,7 +17,7 @@
|
||||||
{- LANGUAGE GeneralizedNewtypeDeriving #-}
|
{- LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
{- LANGUAGE DeriveGeneric #-}
|
{- LANGUAGE DeriveGeneric #-}
|
||||||
|
|
||||||
module Git
|
module Vervis.Git
|
||||||
( lastChange
|
( lastChange
|
||||||
, timeAgo
|
, timeAgo
|
||||||
)
|
)
|
|
@ -14,10 +14,14 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
-- | Common handler functions.
|
-- | Common handler functions.
|
||||||
module Handler.Common where
|
module Vervis.Handler.Common
|
||||||
|
( getFaviconR
|
||||||
|
, getRobotsR
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
import Data.FileEmbed (embedFile)
|
import Data.FileEmbed (embedFile)
|
||||||
import Import
|
import Vervis.Import
|
||||||
|
|
||||||
-- These handlers embed files in the executable at compile time to avoid a
|
-- These handlers embed files in the executable at compile time to avoid a
|
||||||
-- runtime dependency, and for efficiency.
|
-- runtime dependency, and for efficiency.
|
|
@ -13,16 +13,16 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Handler.Home
|
module Vervis.Handler.Home
|
||||||
( getHomeR
|
( getHomeR
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Import hiding ((==.))
|
import Vervis.Import hiding ((==.))
|
||||||
|
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
import Git
|
import Vervis.Git
|
||||||
import Handler.Util (loggedIn)
|
import Vervis.Handler.Util (loggedIn)
|
||||||
|
|
||||||
getHomeR :: Handler Html
|
getHomeR :: Handler Html
|
||||||
getHomeR = do
|
getHomeR = do
|
|
@ -13,7 +13,7 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Handler.Person
|
module Vervis.Handler.Person
|
||||||
( getPeopleR
|
( getPeopleR
|
||||||
, postPeopleR
|
, postPeopleR
|
||||||
, getPersonNewR
|
, getPersonNewR
|
||||||
|
@ -21,11 +21,11 @@ module Handler.Person
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Import hiding ((==.))
|
import Vervis.Import hiding ((==.))
|
||||||
--import Prelude
|
--import Prelude
|
||||||
|
|
||||||
import Database.Esqueleto hiding (isNothing)
|
import Database.Esqueleto hiding (isNothing)
|
||||||
import Form
|
import Vervis.Form
|
||||||
--import Model
|
--import Model
|
||||||
import Text.Blaze (text)
|
import Text.Blaze (text)
|
||||||
import Yesod.Auth.HashDB (setPassword)
|
import Yesod.Auth.HashDB (setPassword)
|
|
@ -13,13 +13,13 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Handler.Project
|
module Vervis.Handler.Project
|
||||||
( getProjectsR
|
( getProjectsR
|
||||||
, getProjectR
|
, getProjectR
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Import hiding ((==.))
|
import Vervis.Import hiding ((==.))
|
||||||
--import Prelude
|
--import Prelude
|
||||||
|
|
||||||
import Text.Blaze (text)
|
import Text.Blaze (text)
|
|
@ -13,12 +13,12 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Handler.Util
|
module Vervis.Handler.Util
|
||||||
( loggedIn
|
( loggedIn
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Import
|
import Vervis.Import
|
||||||
|
|
||||||
loggedIn :: Handler Bool
|
loggedIn :: Handler Bool
|
||||||
loggedIn = isJust <$> maybeAuthId
|
loggedIn = isJust <$> maybeAuthId
|
|
@ -13,7 +13,7 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Import ( module Import ) where
|
module Vervis.Import ( module Import ) where
|
||||||
|
|
||||||
import Foundation as Import
|
import Vervis.Foundation as Import
|
||||||
import Import.NoFoundation as Import
|
import Vervis.Import.NoFoundation as Import
|
|
@ -13,13 +13,13 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Import.NoFoundation ( module Import ) where
|
module Vervis.Import.NoFoundation ( module Import ) where
|
||||||
|
|
||||||
import ClassyPrelude.Yesod as Import
|
import ClassyPrelude.Yesod as Import
|
||||||
import Style as Import
|
import Vervis.Style as Import
|
||||||
import Model as Import
|
import Vervis.Model as Import
|
||||||
import Settings as Import
|
import Vervis.Settings as Import
|
||||||
import Settings.StaticFiles as Import
|
import Vervis.Settings.StaticFiles as Import
|
||||||
import Yesod.Auth as Import
|
import Yesod.Auth as Import
|
||||||
import Yesod.Core.Types as Import (loggerSet)
|
import Yesod.Core.Types as Import (loggerSet)
|
||||||
import Yesod.Default.Config2 as Import
|
import Yesod.Default.Config2 as Import
|
|
@ -15,7 +15,7 @@
|
||||||
|
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
|
||||||
module Model where
|
module Vervis.Model where
|
||||||
|
|
||||||
import ClassyPrelude.Yesod
|
import ClassyPrelude.Yesod
|
||||||
import Database.Persist.Quasi
|
import Database.Persist.Quasi
|
|
@ -20,7 +20,7 @@
|
||||||
-- In addition, you can configure a number of different aspects of Yesod
|
-- In addition, you can configure a number of different aspects of Yesod
|
||||||
-- by overriding methods in the Yesod typeclass. That instance is
|
-- by overriding methods in the Yesod typeclass. That instance is
|
||||||
-- declared in the Foundation.hs file.
|
-- declared in the Foundation.hs file.
|
||||||
module Settings where
|
module Vervis.Settings where
|
||||||
|
|
||||||
import ClassyPrelude.Yesod
|
import ClassyPrelude.Yesod
|
||||||
import Control.Exception (throw)
|
import Control.Exception (throw)
|
|
@ -13,9 +13,9 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Settings.StaticFiles where
|
module Vervis.Settings.StaticFiles where
|
||||||
|
|
||||||
import Settings (appStaticDir, compileTimeAppSettings)
|
import Vervis.Settings (appStaticDir, compileTimeAppSettings)
|
||||||
import Yesod.Static (staticFiles)
|
import Yesod.Static (staticFiles)
|
||||||
|
|
||||||
-- This generates easy references to files in the static directory at compile time,
|
-- This generates easy references to files in the static directory at compile time,
|
|
@ -15,7 +15,7 @@
|
||||||
|
|
||||||
-- | Style component palette for use in page templates, in particular Cassius
|
-- | Style component palette for use in page templates, in particular Cassius
|
||||||
-- files.
|
-- files.
|
||||||
module Style
|
module Vervis.Style
|
||||||
( -- * Types
|
( -- * Types
|
||||||
Color ()
|
Color ()
|
||||||
, Hue ()
|
, Hue ()
|
34
vervis.cabal
34
vervis.cabal
|
@ -34,23 +34,23 @@ flag library-only
|
||||||
default: False
|
default: False
|
||||||
|
|
||||||
library
|
library
|
||||||
exposed-modules: Application
|
exposed-modules: Data.Char.Local
|
||||||
Data.Char.Local
|
Vervis.Application
|
||||||
Field
|
Vervis.Field
|
||||||
Form
|
Vervis.Form
|
||||||
Foundation
|
Vervis.Foundation
|
||||||
Git
|
Vervis.Git
|
||||||
Import
|
Vervis.Import
|
||||||
Import.NoFoundation
|
Vervis.Import.NoFoundation
|
||||||
Model
|
Vervis.Model
|
||||||
Settings
|
Vervis.Settings
|
||||||
Settings.StaticFiles
|
Vervis.Settings.StaticFiles
|
||||||
Handler.Common
|
Vervis.Handler.Common
|
||||||
Handler.Home
|
Vervis.Handler.Home
|
||||||
Handler.Person
|
Vervis.Handler.Person
|
||||||
Handler.Project
|
Vervis.Handler.Project
|
||||||
Handler.Util
|
Vervis.Handler.Util
|
||||||
Style
|
Vervis.Style
|
||||||
-- other-modules:
|
-- other-modules:
|
||||||
default-extensions: TemplateHaskell
|
default-extensions: TemplateHaskell
|
||||||
QuasiQuotes
|
QuasiQuotes
|
||||||
|
|
Loading…
Reference in a new issue