Merge yesod-routes into yesod-core entirely
This commit is contained in:
parent
88b9217e25
commit
f779004d19
@ -17,7 +17,6 @@ import Data.ByteString.Lazy.Char8 ()
|
|||||||
import Data.List (foldl')
|
import Data.List (foldl')
|
||||||
|
|
||||||
import Yesod.Routes.TH
|
import Yesod.Routes.TH
|
||||||
import Yesod.Routes.TH.Simple (mkSimpleDispatchClause)
|
|
||||||
import Yesod.Routes.Parse
|
import Yesod.Routes.Parse
|
||||||
import Yesod.Core.Types
|
import Yesod.Core.Types
|
||||||
import Yesod.Core.Content
|
import Yesod.Core.Content
|
||||||
@ -116,7 +115,7 @@ mkDispatchInstance :: Type -- ^ The master site type
|
|||||||
-> [ResourceTree a] -- ^ The resource
|
-> [ResourceTree a] -- ^ The resource
|
||||||
-> DecsQ
|
-> DecsQ
|
||||||
mkDispatchInstance master res = do
|
mkDispatchInstance master res = do
|
||||||
clause' <- mkSimpleDispatchClause (mkMDS [|yesodRunner|]) res
|
clause' <- mkDispatchClause (mkMDS [|yesodRunner|]) res
|
||||||
let thisDispatch = FunD 'yesodDispatch [clause']
|
let thisDispatch = FunD 'yesodDispatch [clause']
|
||||||
return [InstanceD [] yDispatch [thisDispatch]]
|
return [InstanceD [] yDispatch [thisDispatch]]
|
||||||
where
|
where
|
||||||
@ -124,7 +123,7 @@ mkDispatchInstance master res = do
|
|||||||
|
|
||||||
mkYesodSubDispatch :: [ResourceTree a] -> Q Exp
|
mkYesodSubDispatch :: [ResourceTree a] -> Q Exp
|
||||||
mkYesodSubDispatch res = do
|
mkYesodSubDispatch res = do
|
||||||
clause' <- mkSimpleDispatchClause (mkMDS [|subHelper . fmap toTypedContent|]) res
|
clause' <- mkDispatchClause (mkMDS [|subHelper . fmap toTypedContent|]) res
|
||||||
inner <- newName "inner"
|
inner <- newName "inner"
|
||||||
let innerFun = FunD inner [clause']
|
let innerFun = FunD inner [clause']
|
||||||
helper <- newName "helper"
|
helper <- newName "helper"
|
||||||
|
|||||||
@ -7,7 +7,6 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
{-# OPTIONS_GHC -ddump-splices #-}
|
|
||||||
module Hierarchy
|
module Hierarchy
|
||||||
( hierarchy
|
( hierarchy
|
||||||
, Dispatcher (..)
|
, Dispatcher (..)
|
||||||
@ -25,7 +24,6 @@ import Yesod.Routes.Parse
|
|||||||
import Yesod.Routes.TH
|
import Yesod.Routes.TH
|
||||||
import Yesod.Routes.Class
|
import Yesod.Routes.Class
|
||||||
import Language.Haskell.TH.Syntax
|
import Language.Haskell.TH.Syntax
|
||||||
import qualified Yesod.Routes.Class as YRC
|
|
||||||
import Data.Text (Text, pack, unpack, append)
|
import Data.Text (Text, pack, unpack, append)
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import qualified Data.ByteString.Char8 as S8
|
import qualified Data.ByteString.Char8 as S8
|
||||||
@ -41,18 +39,18 @@ type Handler2 sub master a = a
|
|||||||
type Handler site a = Handler2 site site a
|
type Handler site a = Handler2 site site a
|
||||||
|
|
||||||
type Request = ([Text], ByteString) -- path info, method
|
type Request = ([Text], ByteString) -- path info, method
|
||||||
type App sub master = Request -> (Text, Maybe (YRC.Route master))
|
type App sub master = Request -> (Text, Maybe (Route master))
|
||||||
data Env sub master = Env
|
data Env sub master = Env
|
||||||
{ envToMaster :: YRC.Route sub -> YRC.Route master
|
{ envToMaster :: Route sub -> Route master
|
||||||
, envSub :: sub
|
, envSub :: sub
|
||||||
, envMaster :: master
|
, envMaster :: master
|
||||||
}
|
}
|
||||||
|
|
||||||
subDispatch
|
subDispatch
|
||||||
:: (Env sub master -> App sub master)
|
:: (Env sub master -> App sub master)
|
||||||
-> (Handler2 sub master Text -> Env sub master -> Maybe (YRC.Route sub) -> App sub master)
|
-> (Handler2 sub master Text -> Env sub master -> Maybe (Route sub) -> App sub master)
|
||||||
-> (master -> sub)
|
-> (master -> sub)
|
||||||
-> (YRC.Route sub -> YRC.Route master)
|
-> (Route sub -> Route master)
|
||||||
-> Env master master
|
-> Env master master
|
||||||
-> App sub master
|
-> App sub master
|
||||||
subDispatch handler _runHandler getSub toMaster env req =
|
subDispatch handler _runHandler getSub toMaster env req =
|
||||||
@ -1,6 +1,10 @@
|
|||||||
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
|
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-} -- hah, the test should be renamed...
|
||||||
|
-- Not actually a problem, we're now requiring overloaded strings, we just need
|
||||||
|
-- to make the docs more explicit about it.
|
||||||
module YesodCoreTest.NoOverloadedStringsSub where
|
module YesodCoreTest.NoOverloadedStringsSub where
|
||||||
|
|
||||||
import Yesod.Core
|
import Yesod.Core
|
||||||
|
|||||||
@ -25,7 +25,6 @@ extra-source-files:
|
|||||||
library
|
library
|
||||||
build-depends: base >= 4.3 && < 5
|
build-depends: base >= 4.3 && < 5
|
||||||
, time >= 1.1.4
|
, time >= 1.1.4
|
||||||
, yesod-routes >= 1.2.1 && < 1.3
|
|
||||||
, wai >= 1.4
|
, wai >= 1.4
|
||||||
, wai-extra >= 1.3
|
, wai-extra >= 1.3
|
||||||
, bytestring >= 0.9.1.4
|
, bytestring >= 0.9.1.4
|
||||||
@ -91,6 +90,17 @@ library
|
|||||||
Yesod.Core.Class.Dispatch
|
Yesod.Core.Class.Dispatch
|
||||||
Yesod.Core.Class.Breadcrumbs
|
Yesod.Core.Class.Breadcrumbs
|
||||||
Paths_yesod_core
|
Paths_yesod_core
|
||||||
|
|
||||||
|
Yesod.Routes.TH
|
||||||
|
Yesod.Routes.Class
|
||||||
|
Yesod.Routes.Parse
|
||||||
|
Yesod.Routes.Overlap
|
||||||
|
Yesod.Routes.TH.Dispatch
|
||||||
|
Yesod.Routes.TH.RenderRoute
|
||||||
|
Yesod.Routes.TH.ParseRoute
|
||||||
|
Yesod.Routes.TH.RouteAttrs
|
||||||
|
Yesod.Routes.TH.Types
|
||||||
|
|
||||||
ghc-options: -Wall
|
ghc-options: -Wall
|
||||||
-- Following line added due to: https://github.com/yesodweb/yesod/issues/545
|
-- Following line added due to: https://github.com/yesodweb/yesod/issues/545
|
||||||
-- This looks like a GHC bug
|
-- This looks like a GHC bug
|
||||||
@ -99,6 +109,24 @@ library
|
|||||||
-- Workaround for: http://ghc.haskell.org/trac/ghc/ticket/8443
|
-- Workaround for: http://ghc.haskell.org/trac/ghc/ticket/8443
|
||||||
extensions: TemplateHaskell
|
extensions: TemplateHaskell
|
||||||
|
|
||||||
|
test-suite test-routes
|
||||||
|
type: exitcode-stdio-1.0
|
||||||
|
main-is: RouteSpec.hs
|
||||||
|
hs-source-dirs: test, .
|
||||||
|
|
||||||
|
-- Workaround for: http://ghc.haskell.org/trac/ghc/ticket/8443
|
||||||
|
extensions: TemplateHaskell
|
||||||
|
|
||||||
|
build-depends: base
|
||||||
|
, hspec
|
||||||
|
, containers
|
||||||
|
, bytestring
|
||||||
|
, template-haskell
|
||||||
|
, text
|
||||||
|
, random
|
||||||
|
, path-pieces
|
||||||
|
, HUnit
|
||||||
|
|
||||||
test-suite tests
|
test-suite tests
|
||||||
type: exitcode-stdio-1.0
|
type: exitcode-stdio-1.0
|
||||||
main-is: test.hs
|
main-is: test.hs
|
||||||
|
|||||||
@ -1,20 +0,0 @@
|
|||||||
Copyright (c) 2012 Michael Snoyman, http://www.yesodweb.com/
|
|
||||||
|
|
||||||
Permission is hereby granted, free of charge, to any person obtaining
|
|
||||||
a copy of this software and associated documentation files (the
|
|
||||||
"Software"), to deal in the Software without restriction, including
|
|
||||||
without limitation the rights to use, copy, modify, merge, publish,
|
|
||||||
distribute, sublicense, and/or sell copies of the Software, and to
|
|
||||||
permit persons to whom the Software is furnished to do so, subject to
|
|
||||||
the following conditions:
|
|
||||||
|
|
||||||
The above copyright notice and this permission notice shall be
|
|
||||||
included in all copies or substantial portions of the Software.
|
|
||||||
|
|
||||||
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
|
|
||||||
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
|
|
||||||
MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
|
|
||||||
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
|
|
||||||
LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION
|
|
||||||
OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION
|
|
||||||
WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
|
|
||||||
@ -1,7 +0,0 @@
|
|||||||
#!/usr/bin/env runhaskell
|
|
||||||
|
|
||||||
> module Main where
|
|
||||||
> import Distribution.Simple
|
|
||||||
|
|
||||||
> main :: IO ()
|
|
||||||
> main = defaultMain
|
|
||||||
@ -1,57 +0,0 @@
|
|||||||
name: yesod-routes
|
|
||||||
version: 1.2.1
|
|
||||||
license: MIT
|
|
||||||
license-file: LICENSE
|
|
||||||
author: Michael Snoyman <michael@snoyman.com>
|
|
||||||
maintainer: Michael Snoyman <michael@snoyman.com>
|
|
||||||
synopsis: Efficient routing for Yesod.
|
|
||||||
description: Provides an efficient routing system, a parser and TH code generation.
|
|
||||||
category: Web, Yesod
|
|
||||||
stability: Stable
|
|
||||||
cabal-version: >= 1.8
|
|
||||||
build-type: Simple
|
|
||||||
homepage: http://www.yesodweb.com/
|
|
||||||
extra-source-files:
|
|
||||||
test/main.hs
|
|
||||||
|
|
||||||
library
|
|
||||||
build-depends: base >= 4 && < 5
|
|
||||||
, text >= 0.5
|
|
||||||
, vector >= 0.8 && < 0.11
|
|
||||||
, containers >= 0.2
|
|
||||||
, template-haskell
|
|
||||||
, path-pieces >= 0.1 && < 0.2
|
|
||||||
, bytestring
|
|
||||||
, random
|
|
||||||
|
|
||||||
exposed-modules: Yesod.Routes.TH
|
|
||||||
Yesod.Routes.Class
|
|
||||||
Yesod.Routes.Parse
|
|
||||||
Yesod.Routes.Overlap
|
|
||||||
other-modules: Yesod.Routes.TH.Dispatch
|
|
||||||
Yesod.Routes.TH.RenderRoute
|
|
||||||
Yesod.Routes.TH.ParseRoute
|
|
||||||
Yesod.Routes.TH.RouteAttrs
|
|
||||||
Yesod.Routes.TH.Types
|
|
||||||
ghc-options: -Wall
|
|
||||||
|
|
||||||
test-suite runtests
|
|
||||||
type: exitcode-stdio-1.0
|
|
||||||
main-is: main.hs
|
|
||||||
hs-source-dirs: test
|
|
||||||
other-modules: Hierarchy
|
|
||||||
|
|
||||||
build-depends: base >= 4.3 && < 5
|
|
||||||
, yesod-routes
|
|
||||||
, text >= 0.5
|
|
||||||
, HUnit >= 1.2 && < 1.3
|
|
||||||
, hspec >= 1.3
|
|
||||||
, containers
|
|
||||||
, template-haskell
|
|
||||||
, path-pieces
|
|
||||||
, bytestring
|
|
||||||
ghc-options: -Wall
|
|
||||||
|
|
||||||
source-repository head
|
|
||||||
type: git
|
|
||||||
location: https://github.com/yesodweb/yesod
|
|
||||||
Loading…
Reference in New Issue
Block a user