Removed Yesod.Internal
This commit is contained in:
parent
9559c2a345
commit
5c4ddfad6c
@ -55,12 +55,12 @@ module Yesod.Core
|
||||
) where
|
||||
|
||||
import Yesod.Internal.Core
|
||||
import Yesod.Internal (Header(..))
|
||||
import Yesod.Content
|
||||
import Yesod.Dispatch
|
||||
import Yesod.Handler
|
||||
import Yesod.Widget
|
||||
import Yesod.Core.Json
|
||||
import Yesod.Core.Types
|
||||
import Text.Shakespeare.I18N
|
||||
|
||||
import Control.Monad.Logger
|
||||
|
||||
@ -20,6 +20,7 @@ import Control.Monad.Logger (LogLevel (LevelInfo, LevelO
|
||||
import qualified Data.ByteString.Char8 as S8
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import Data.List (foldl')
|
||||
import Data.List (nub)
|
||||
import qualified Data.Map as Map
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Monoid
|
||||
@ -51,7 +52,6 @@ import qualified Web.ClientSession as CS
|
||||
import Web.Cookie (parseCookies)
|
||||
import Web.Cookie (SetCookie (..))
|
||||
import Yesod.Core.Types
|
||||
import Yesod.Internal
|
||||
import Yesod.Internal.Session
|
||||
import Yesod.Widget
|
||||
|
||||
@ -399,6 +399,9 @@ $newline never
|
||||
: attrs
|
||||
)
|
||||
|
||||
runUniqueList :: Eq x => UniqueList x -> [x]
|
||||
runUniqueList (UniqueList x) = nub $ x []
|
||||
|
||||
-- | Helper function for 'defaultErrorHandler'.
|
||||
applyLayout' :: Yesod master
|
||||
=> Html -- ^ title
|
||||
|
||||
@ -2,7 +2,7 @@
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module Yesod.Core.Run where
|
||||
|
||||
import Blaze.ByteString.Builder (fromLazyByteString, toByteString,
|
||||
@ -13,6 +13,8 @@ import Control.Exception (SomeException, fromException,
|
||||
import Control.Exception.Lifted (catch)
|
||||
import Control.Monad.IO.Class (MonadIO)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Control.Monad.Logger (LogLevel (LevelError), LogSource,
|
||||
liftLoc)
|
||||
import Control.Monad.Trans.Resource (runResourceT)
|
||||
import Data.ByteString (ByteString)
|
||||
import qualified Data.ByteString as S
|
||||
@ -30,22 +32,20 @@ import qualified Data.Text as T
|
||||
import Data.Text.Encoding (encodeUtf8)
|
||||
import Data.Text.Encoding (decodeUtf8With)
|
||||
import Data.Text.Encoding.Error (lenientDecode)
|
||||
import Language.Haskell.TH.Syntax (Loc, qLocation)
|
||||
import qualified Network.HTTP.Types as H
|
||||
import Network.Wai
|
||||
import Prelude hiding (catch)
|
||||
import System.Log.FastLogger (Logger)
|
||||
import System.Log.FastLogger (LogStr, toLogStr)
|
||||
import System.Random (newStdGen)
|
||||
import Web.Cookie (renderSetCookie)
|
||||
import Yesod.Content
|
||||
import Yesod.Core.Class
|
||||
import Yesod.Core.Types
|
||||
import Yesod.Internal (tokenKey)
|
||||
import Yesod.Internal.Request (parseWaiRequest,
|
||||
import Yesod.Internal.Request (parseWaiRequest, tokenKey,
|
||||
tooLargeResponse)
|
||||
import Yesod.Routes.Class (Route, renderRoute)
|
||||
import Language.Haskell.TH.Syntax (Loc, qLocation)
|
||||
import Control.Monad.Logger (LogSource, LogLevel (LevelError), liftLoc)
|
||||
import System.Log.FastLogger (LogStr, toLogStr)
|
||||
|
||||
yarToResponse :: YesodResponse -> [(CI ByteString, ByteString)] -> Response
|
||||
yarToResponse (YRWai a) _ = a
|
||||
|
||||
@ -130,7 +130,6 @@ module Yesod.Handler
|
||||
|
||||
import Prelude hiding (catch)
|
||||
import Yesod.Internal.Request
|
||||
import Yesod.Internal
|
||||
import Data.Time (UTCTime, getCurrentTime, addUTCTime)
|
||||
|
||||
import Control.Exception hiding (Handler, catch, finally)
|
||||
|
||||
@ -1,53 +0,0 @@
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
-- | Normal users should never need access to these.
|
||||
--
|
||||
-- Note that no guarantees of API stability are provided on this module. Use at your own risk.
|
||||
module Yesod.Internal
|
||||
( -- * Error responses
|
||||
ErrorResponse (..)
|
||||
, HandlerContents (..)
|
||||
-- * Header
|
||||
, Header (..)
|
||||
-- * Cookie names
|
||||
, langKey
|
||||
-- * Widgets
|
||||
, GWData (..)
|
||||
, Location (..)
|
||||
, UniqueList (..)
|
||||
, Script (..)
|
||||
, Stylesheet (..)
|
||||
, Title (..)
|
||||
, Head (..)
|
||||
, Body (..)
|
||||
, locationToHtmlUrl
|
||||
, runUniqueList
|
||||
, toUnique
|
||||
-- * Names
|
||||
, tokenKey
|
||||
) where
|
||||
|
||||
import Text.Hamlet (HtmlUrl)
|
||||
import Text.Blaze.Html (toHtml)
|
||||
import Data.List (nub)
|
||||
|
||||
import Data.String (IsString)
|
||||
import Yesod.Core.Types
|
||||
|
||||
langKey :: IsString a => a
|
||||
langKey = "_LANG"
|
||||
|
||||
locationToHtmlUrl :: Location url -> HtmlUrl url
|
||||
locationToHtmlUrl (Local url) render = toHtml $ render url []
|
||||
locationToHtmlUrl (Remote s) _ = toHtml s
|
||||
|
||||
runUniqueList :: Eq x => UniqueList x -> [x]
|
||||
runUniqueList (UniqueList x) = nub $ x []
|
||||
toUnique :: x -> UniqueList x
|
||||
toUnique = UniqueList . (:)
|
||||
|
||||
tokenKey :: IsString a => a
|
||||
tokenKey = "_TOKEN"
|
||||
@ -13,13 +13,15 @@ module Yesod.Internal.Request
|
||||
, mkFileInfoSource
|
||||
, FileUpload (..)
|
||||
, tooLargeResponse
|
||||
, tokenKey
|
||||
, langKey
|
||||
-- The below are exported for testing.
|
||||
, randomString
|
||||
) where
|
||||
|
||||
import Data.String (IsString)
|
||||
import Control.Arrow (second)
|
||||
import qualified Network.Wai.Parse as NWP
|
||||
import Yesod.Internal
|
||||
import qualified Network.Wai as W
|
||||
import System.Random (RandomGen, randomRs)
|
||||
import Web.Cookie (parseCookiesText)
|
||||
@ -165,3 +167,9 @@ mkFileInfoFile name ct fp = FileInfo name ct (sourceFile fp) (\dst -> runResourc
|
||||
|
||||
mkFileInfoSource :: Text -> Text -> Source (ResourceT IO) ByteString -> FileInfo
|
||||
mkFileInfoSource name ct src = FileInfo name ct src (\dst -> runResourceT $ src $$ sinkFile dst)
|
||||
|
||||
tokenKey :: IsString a => a
|
||||
tokenKey = "_TOKEN"
|
||||
|
||||
langKey :: IsString a => a
|
||||
langKey = "_LANG"
|
||||
|
||||
@ -57,7 +57,6 @@ import Yesod.Handler
|
||||
)
|
||||
import Text.Shakespeare.I18N (RenderMessage)
|
||||
import Yesod.Content (toContent)
|
||||
import Yesod.Internal
|
||||
import Control.Monad (liftM)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Map as Map
|
||||
@ -229,3 +228,6 @@ tell w = GWidget $ return ((), w)
|
||||
-- messages.
|
||||
liftW :: GHandler sub master a -> GWidget sub master a
|
||||
liftW = lift
|
||||
|
||||
toUnique :: x -> UniqueList x
|
||||
toUnique = UniqueList . (:)
|
||||
|
||||
@ -95,8 +95,7 @@ library
|
||||
Yesod.Handler
|
||||
Yesod.Widget
|
||||
Yesod.Internal.TestApi
|
||||
other-modules: Yesod.Internal
|
||||
Yesod.Internal.Core
|
||||
other-modules: Yesod.Internal.Core
|
||||
Yesod.Internal.Session
|
||||
Yesod.Internal.Request
|
||||
Yesod.Core.Time
|
||||
|
||||
Loading…
Reference in New Issue
Block a user