Rename module: Entry.Kind -> Model.Entry.Kind
This commit is contained in:
parent
02fd91cb77
commit
66cb093387
6 changed files with 8 additions and 7 deletions
|
@ -21,8 +21,8 @@ import Yesod.Core.Types (Logger)
|
|||
import qualified Yesod.Core.Unsafe as Unsafe
|
||||
|
||||
import Package
|
||||
import Entry.Kind ( EntryKind, allEntryKinds, pluralise )
|
||||
import Model.Cache ( getCached )
|
||||
import Model.Entry.Kind ( EntryKind, allEntryKinds, pluralise )
|
||||
|
||||
import Data.Aeson ( encode, object )
|
||||
import qualified Text.Blaze.Internal as B
|
||||
|
|
|
@ -11,7 +11,7 @@ import Yesod.Sitemap
|
|||
|
||||
import Import
|
||||
|
||||
import Entry.Kind ( EntryKind, allEntryKinds )
|
||||
import Model.Entry.Kind ( EntryKind, allEntryKinds )
|
||||
import Widget.Entry ( entryR )
|
||||
|
||||
-- These handlers embed files in the executable at compile time to avoid a
|
||||
|
|
|
@ -6,13 +6,14 @@ module Handler.Entries where
|
|||
import Import
|
||||
|
||||
import Yesod.AtomFeed ( atomLink )
|
||||
import qualified Data.Text as T
|
||||
|
||||
import qualified Entry.Kind as K
|
||||
import Model.Cache ( getCached )
|
||||
import Widget.Entry ( entryR, hEntry )
|
||||
import Widget.Feed ( hFeed )
|
||||
|
||||
import qualified Data.Text as T
|
||||
import qualified Model.Entry.Kind as K
|
||||
|
||||
getEntriesR :: K.EntryKind -> Handler Html
|
||||
getEntriesR kind = do
|
||||
entries <- runDB $ selectList [EntryKind ==. kind] [Desc EntryPublished]
|
||||
|
|
|
@ -8,7 +8,7 @@ import Data.Time.Clock.POSIX ( posixSecondsToUTCTime )
|
|||
import Widget.Entry ( entryR )
|
||||
|
||||
import qualified Data.Text as T
|
||||
import qualified Entry.Kind as K
|
||||
import qualified Model.Entry.Kind as K
|
||||
|
||||
getFeedR :: Handler TypedContent
|
||||
getFeedR = do
|
||||
|
|
|
@ -16,7 +16,7 @@ import Web.Slug ( Slug )
|
|||
import Text.Mustache ( (~>) )
|
||||
import qualified Text.Mustache as M
|
||||
|
||||
import Entry.Kind ( EntryKind )
|
||||
import Model.Entry.Kind ( EntryKind )
|
||||
|
||||
-- You can define all of your database entities in the entities file.
|
||||
-- You can find more information on persistent and how to declare entities
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module Entry.Kind where
|
||||
module Model.Entry.Kind where
|
||||
|
||||
import Database.Persist.TH ( derivePersistField )
|
||||
import Yesod.Core.Dispatch ( PathPiece, toPathPiece, fromPathPiece )
|
Loading…
Reference in a new issue