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
|
||||
|
||||
import Prelude
|
||||
import Application (getApplicationRepl, shutdownApp)
|
||||
import Vervis.Application (getApplicationRepl, shutdownApp)
|
||||
|
||||
import Control.Exception (finally)
|
||||
import Control.Monad ((>=>))
|
||||
|
|
|
@ -15,7 +15,7 @@
|
|||
|
||||
{-# LANGUAGE PackageImports #-}
|
||||
|
||||
import "vervis" Application (develMain)
|
||||
import "vervis" Vervis.Application (develMain)
|
||||
import Prelude (IO)
|
||||
|
||||
main :: IO ()
|
||||
|
|
|
@ -13,8 +13,8 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
import Prelude (IO)
|
||||
import Application (appMain)
|
||||
import Prelude (IO)
|
||||
import Vervis.Application (appMain)
|
||||
|
||||
main :: IO ()
|
||||
main = appMain
|
||||
|
|
|
@ -15,7 +15,7 @@
|
|||
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
|
||||
module Application
|
||||
module Vervis.Application
|
||||
( getApplicationDev
|
||||
, appMain
|
||||
, develMain
|
||||
|
@ -33,7 +33,7 @@ where
|
|||
import Control.Monad.Logger (liftLoc, runLoggingT)
|
||||
import Database.Persist.Postgresql (createPostgresqlPool, pgConnStr,
|
||||
pgPoolSize, runSqlPool)
|
||||
import Import
|
||||
import Vervis.Import
|
||||
import Language.Haskell.TH.Syntax (qLocation)
|
||||
import Network.Wai (Middleware)
|
||||
import Network.Wai.Handler.Warp (Settings, defaultSettings,
|
||||
|
@ -49,10 +49,10 @@ import System.Log.FastLogger (defaultBufSize, newStdoutLoggerSet,
|
|||
|
||||
-- Import all relevant handler modules here.
|
||||
-- Don't forget to add new modules to your cabal file!
|
||||
import Handler.Common
|
||||
import Handler.Home
|
||||
import Handler.Person
|
||||
import Handler.Project
|
||||
import Vervis.Handler.Common
|
||||
import Vervis.Handler.Home
|
||||
import Vervis.Handler.Person
|
||||
import Vervis.Handler.Project
|
||||
|
||||
-- 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
|
|
@ -13,13 +13,13 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Field
|
||||
module Vervis.Field
|
||||
( loginField
|
||||
, passField
|
||||
)
|
||||
where
|
||||
|
||||
import Import
|
||||
import Vervis.Import
|
||||
|
||||
import Data.Char (isDigit)
|
||||
import Data.Char.Local (isAsciiLetter)
|
|
@ -13,15 +13,15 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Form
|
||||
module Vervis.Form
|
||||
( PersonNew (..)
|
||||
, formPersonNew
|
||||
)
|
||||
where
|
||||
|
||||
import Import
|
||||
import Vervis.Import
|
||||
|
||||
import Field
|
||||
import Vervis.Field
|
||||
|
||||
data PersonNew = PersonNew
|
||||
{ uLogin :: Text
|
|
@ -13,9 +13,9 @@
|
|||
- <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 Text.Hamlet (hamletFile)
|
||||
import Text.Jasmine (minifym)
|
|
@ -17,7 +17,7 @@
|
|||
{- LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{- LANGUAGE DeriveGeneric #-}
|
||||
|
||||
module Git
|
||||
module Vervis.Git
|
||||
( lastChange
|
||||
, timeAgo
|
||||
)
|
|
@ -14,10 +14,14 @@
|
|||
-}
|
||||
|
||||
-- | Common handler functions.
|
||||
module Handler.Common where
|
||||
module Vervis.Handler.Common
|
||||
( getFaviconR
|
||||
, getRobotsR
|
||||
)
|
||||
where
|
||||
|
||||
import Data.FileEmbed (embedFile)
|
||||
import Import
|
||||
import Vervis.Import
|
||||
|
||||
-- These handlers embed files in the executable at compile time to avoid a
|
||||
-- runtime dependency, and for efficiency.
|
|
@ -13,16 +13,16 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Handler.Home
|
||||
module Vervis.Handler.Home
|
||||
( getHomeR
|
||||
)
|
||||
where
|
||||
|
||||
import Import hiding ((==.))
|
||||
import Vervis.Import hiding ((==.))
|
||||
|
||||
import Database.Esqueleto
|
||||
import Git
|
||||
import Handler.Util (loggedIn)
|
||||
import Vervis.Git
|
||||
import Vervis.Handler.Util (loggedIn)
|
||||
|
||||
getHomeR :: Handler Html
|
||||
getHomeR = do
|
|
@ -13,7 +13,7 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Handler.Person
|
||||
module Vervis.Handler.Person
|
||||
( getPeopleR
|
||||
, postPeopleR
|
||||
, getPersonNewR
|
||||
|
@ -21,11 +21,11 @@ module Handler.Person
|
|||
)
|
||||
where
|
||||
|
||||
import Import hiding ((==.))
|
||||
import Vervis.Import hiding ((==.))
|
||||
--import Prelude
|
||||
|
||||
import Database.Esqueleto hiding (isNothing)
|
||||
import Form
|
||||
import Vervis.Form
|
||||
--import Model
|
||||
import Text.Blaze (text)
|
||||
import Yesod.Auth.HashDB (setPassword)
|
|
@ -13,13 +13,13 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Handler.Project
|
||||
module Vervis.Handler.Project
|
||||
( getProjectsR
|
||||
, getProjectR
|
||||
)
|
||||
where
|
||||
|
||||
import Import hiding ((==.))
|
||||
import Vervis.Import hiding ((==.))
|
||||
--import Prelude
|
||||
|
||||
import Text.Blaze (text)
|
|
@ -13,12 +13,12 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Handler.Util
|
||||
module Vervis.Handler.Util
|
||||
( loggedIn
|
||||
)
|
||||
where
|
||||
|
||||
import Import
|
||||
import Vervis.Import
|
||||
|
||||
loggedIn :: Handler Bool
|
||||
loggedIn = isJust <$> maybeAuthId
|
|
@ -13,7 +13,7 @@
|
|||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||
-}
|
||||
|
||||
module Import ( module Import ) where
|
||||
module Vervis.Import ( module Import ) where
|
||||
|
||||
import Foundation as Import
|
||||
import Import.NoFoundation as Import
|
||||
import Vervis.Foundation as Import
|
||||
import Vervis.Import.NoFoundation as Import
|
|
@ -13,13 +13,13 @@
|
|||
- <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 Style as Import
|
||||
import Model as Import
|
||||
import Settings as Import
|
||||
import Settings.StaticFiles as Import
|
||||
import Vervis.Style as Import
|
||||
import Vervis.Model as Import
|
||||
import Vervis.Settings as Import
|
||||
import Vervis.Settings.StaticFiles as Import
|
||||
import Yesod.Auth as Import
|
||||
import Yesod.Core.Types as Import (loggerSet)
|
||||
import Yesod.Default.Config2 as Import
|
|
@ -15,7 +15,7 @@
|
|||
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
|
||||
module Model where
|
||||
module Vervis.Model where
|
||||
|
||||
import ClassyPrelude.Yesod
|
||||
import Database.Persist.Quasi
|
|
@ -20,7 +20,7 @@
|
|||
-- In addition, you can configure a number of different aspects of Yesod
|
||||
-- by overriding methods in the Yesod typeclass. That instance is
|
||||
-- declared in the Foundation.hs file.
|
||||
module Settings where
|
||||
module Vervis.Settings where
|
||||
|
||||
import ClassyPrelude.Yesod
|
||||
import Control.Exception (throw)
|
|
@ -13,9 +13,9 @@
|
|||
- <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)
|
||||
|
||||
-- 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
|
||||
-- files.
|
||||
module Style
|
||||
module Vervis.Style
|
||||
( -- * Types
|
||||
Color ()
|
||||
, Hue ()
|
34
vervis.cabal
34
vervis.cabal
|
@ -34,23 +34,23 @@ flag library-only
|
|||
default: False
|
||||
|
||||
library
|
||||
exposed-modules: Application
|
||||
Data.Char.Local
|
||||
Field
|
||||
Form
|
||||
Foundation
|
||||
Git
|
||||
Import
|
||||
Import.NoFoundation
|
||||
Model
|
||||
Settings
|
||||
Settings.StaticFiles
|
||||
Handler.Common
|
||||
Handler.Home
|
||||
Handler.Person
|
||||
Handler.Project
|
||||
Handler.Util
|
||||
Style
|
||||
exposed-modules: Data.Char.Local
|
||||
Vervis.Application
|
||||
Vervis.Field
|
||||
Vervis.Form
|
||||
Vervis.Foundation
|
||||
Vervis.Git
|
||||
Vervis.Import
|
||||
Vervis.Import.NoFoundation
|
||||
Vervis.Model
|
||||
Vervis.Settings
|
||||
Vervis.Settings.StaticFiles
|
||||
Vervis.Handler.Common
|
||||
Vervis.Handler.Home
|
||||
Vervis.Handler.Person
|
||||
Vervis.Handler.Project
|
||||
Vervis.Handler.Util
|
||||
Vervis.Style
|
||||
-- other-modules:
|
||||
default-extensions: TemplateHaskell
|
||||
QuasiQuotes
|
||||
|
|
Loading…
Reference in a new issue