diff --git a/yesod-auth/yesod-auth.cabal b/yesod-auth/yesod-auth.cabal index b1b59f6c..b9fca515 100644 --- a/yesod-auth/yesod-auth.cabal +++ b/yesod-auth/yesod-auth.cabal @@ -11,6 +11,7 @@ cabal-version: >= 1.6.0 build-type: Simple homepage: http://www.yesodweb.com/ extra-source-files: include/qq.h +description: Authentication for Yesod. flag ghc7 diff --git a/yesod-core/Yesod/Internal/RouteParsing.hs b/yesod-core/Yesod/Internal/RouteParsing.hs index 82489351..8a37a496 100644 --- a/yesod-core/Yesod/Internal/RouteParsing.hs +++ b/yesod-core/Yesod/Internal/RouteParsing.hs @@ -1,5 +1,6 @@ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DeriveDataTypeable #-} +{-# OPTIONS_GHC -fno-warn-missing-fields #-} -- QuasiQuoter module Yesod.Internal.RouteParsing ( createRoutes , createRender @@ -22,10 +23,8 @@ import Data.Either import Data.List import Data.Char (toLower) import qualified Data.Text -import Language.Haskell.TH.Syntax import Language.Haskell.TH.Quote import Data.Data -import Data.Maybe import qualified System.IO as SIO data Pieces = diff --git a/yesod-core/Test/CleanPath.hs b/yesod-core/test/Test/CleanPath.hs similarity index 88% rename from yesod-core/Test/CleanPath.hs rename to yesod-core/test/Test/CleanPath.hs index 1e13d69d..ce01a96d 100644 --- a/yesod-core/Test/CleanPath.hs +++ b/yesod-core/test/Test/CleanPath.hs @@ -1,15 +1,12 @@ {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} -module Test.CleanPath (cleanPathTest) where +module Test.CleanPath (cleanPathTest, Widget) where import Test.Hspec -import Test.Hspec.HUnit +import Test.Hspec.HUnit() import Yesod.Core hiding (Request) -import Yesod.Content -import Yesod.Dispatch -import Yesod.Handler (Route) import Network.Wai import Network.Wai.Test @@ -19,7 +16,10 @@ import qualified Data.ByteString.Lazy.Char8 as L8 import qualified Data.Text as TS data Subsite = Subsite + +getSubsite :: a -> Subsite getSubsite = const Subsite + data SubsiteRoute = SubsiteRoute [TS.Text] deriving (Eq, Show, Read) type instance Route Subsite = SubsiteRoute @@ -33,7 +33,7 @@ instance YesodDispatch Subsite master where ] $ L8.pack $ show pieces data Y = Y -mkYesod "Y" [$parseRoutes| +mkYesod "Y" [parseRoutes| /foo FooR GET /foo/#String FooStringR GET /bar BarR GET @@ -52,8 +52,13 @@ instance Yesod Y where where corrected = filter (not . TS.null) s +getFooR :: Handler RepPlain getFooR = return $ RepPlain "foo" + +getFooStringR :: String -> Handler RepPlain getFooStringR = return . RepPlain . toContent + +getBarR, getPlainR :: Handler RepPlain getBarR = return $ RepPlain "bar" getPlainR = return $ RepPlain "plain" @@ -69,8 +74,10 @@ cleanPathTest = , it "redirect with query string" redQueryString ] +runner :: Session () -> IO () runner f = toWaiApp Y >>= runSession f +removeTrailingSlash :: IO () removeTrailingSlash = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/foo/" @@ -78,6 +85,7 @@ removeTrailingSlash = runner $ do assertStatus 301 res assertHeader "Location" "http://test/foo" res +noTrailingSlash :: IO () noTrailingSlash = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/foo" @@ -86,6 +94,7 @@ noTrailingSlash = runner $ do assertContentType "text/plain; charset=utf-8" res assertBody "foo" res +addTrailingSlash :: IO () addTrailingSlash = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/bar" @@ -93,6 +102,7 @@ addTrailingSlash = runner $ do assertStatus 301 res assertHeader "Location" "http://test/bar/" res +hasTrailingSlash :: IO () hasTrailingSlash = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/bar/" @@ -101,6 +111,7 @@ hasTrailingSlash = runner $ do assertContentType "text/plain; charset=utf-8" res assertBody "bar" res +fooSomething :: IO () fooSomething = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/foo/something" @@ -109,6 +120,7 @@ fooSomething = runner $ do assertContentType "text/plain; charset=utf-8" res assertBody "something" res +subsiteDispatch :: IO () subsiteDispatch = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/subsite/1/2/3/" @@ -117,6 +129,7 @@ subsiteDispatch = runner $ do assertContentType "SUBSITE" res assertBody "[\"1\",\"2\",\"3\",\"\"]" res +redQueryString :: IO () redQueryString = runner $ do res <- request defaultRequest { pathInfo = decodePathSegments "/plain/" diff --git a/yesod-core/Test/Exceptions.hs b/yesod-core/test/Test/Exceptions.hs similarity index 72% rename from yesod-core/Test/Exceptions.hs rename to yesod-core/test/Test/Exceptions.hs index e1fa93a8..639ccbd1 100644 --- a/yesod-core/Test/Exceptions.hs +++ b/yesod-core/test/Test/Exceptions.hs @@ -1,23 +1,16 @@ {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} -module Test.Exceptions (exceptionsTest) where +module Test.Exceptions (exceptionsTest, Widget) where import Test.Hspec -import Test.Hspec.HUnit +import Test.Hspec.HUnit () import Yesod.Core hiding (Request) -import Yesod.Content -import Yesod.Dispatch -import Yesod.Handler (Route, ErrorResponse (InternalError)) - -import Network.Wai import Network.Wai.Test -import qualified Data.ByteString.Lazy.Char8 as L8 - data Y = Y -mkYesod "Y" [$parseRoutes| +mkYesod "Y" [parseRoutes| / RootR GET |] @@ -26,6 +19,7 @@ instance Yesod Y where errorHandler (InternalError e) = return $ chooseRep $ RepPlain $ toContent e errorHandler x = defaultErrorHandler x +getRootR :: Handler () getRootR = error "FOOBAR" >> return () exceptionsTest :: IO [IO Spec] @@ -33,8 +27,10 @@ exceptionsTest = describe "Test.Exceptions" [ it "500" case500 ] +runner :: Session () -> IO () runner f = toWaiApp Y >>= runSession f +case500 :: IO () case500 = runner $ do res <- request defaultRequest assertStatus 500 res diff --git a/yesod-core/Test/Links.hs b/yesod-core/test/Test/Links.hs similarity index 72% rename from yesod-core/Test/Links.hs rename to yesod-core/test/Test/Links.hs index c0a3eaf3..ac237f44 100644 --- a/yesod-core/Test/Links.hs +++ b/yesod-core/test/Test/Links.hs @@ -1,36 +1,35 @@ {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} -module Test.Links (linksTest) where +module Test.Links (linksTest, Widget) where import Test.Hspec -import Test.Hspec.HUnit +import Test.Hspec.HUnit () import Yesod.Core hiding (Request) import Text.Hamlet - -import Network.Wai import Network.Wai.Test -import qualified Data.ByteString.Lazy.Char8 as L8 - data Y = Y -mkYesod "Y" [$parseRoutes| +mkYesod "Y" [parseRoutes| / RootR GET |] instance Yesod Y where approot _ = "" -getRootR = defaultLayout $ addHamlet [$hamlet||] +getRootR :: Handler RepHtml +getRootR = defaultLayout $ addHamlet [hamlet||] linksTest :: IO [IO Spec] linksTest = describe "Test.Links" [ it "linkToHome" case_linkToHome ] +runner :: Session () -> IO () runner f = toWaiApp Y >>= runSession f +case_linkToHome :: IO () case_linkToHome = runner $ do res <- request defaultRequest assertBody "\n" res diff --git a/yesod-core/Test/Media.hs b/yesod-core/test/Test/Media.hs similarity index 80% rename from yesod-core/Test/Media.hs rename to yesod-core/test/Test/Media.hs index 8bbb85ef..1f86ecdb 100644 --- a/yesod-core/Test/Media.hs +++ b/yesod-core/test/Test/Media.hs @@ -1,23 +1,17 @@ {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} -module Test.Media (mediaTest) where +module Test.Media (mediaTest, Widget) where import Test.Hspec -import Test.Hspec.HUnit - +import Test.Hspec.HUnit () import Yesod.Core hiding (Request) - import Network.Wai import Network.Wai.Test -import Network.HTTP.Types (status200, decodePathSegments) - -import qualified Data.ByteString.Lazy.Char8 as L8 -import qualified Data.Text as TS import Text.Lucius data Y = Y -mkYesod "Y" [$parseRoutes| +mkYesod "Y" [parseRoutes| / RootR GET /static StaticR GET |] @@ -34,19 +28,25 @@ instance Yesod Y where else "all.css" _ -> return Nothing +getRootR :: Handler RepHtml getRootR = defaultLayout $ do - addCassius [$lucius|foo1{bar:baz}|] - addCassiusMedia "screen" [$lucius|foo2{bar:baz}|] - addCassius [$lucius|foo3{bar:baz}|] + addCassius [lucius|foo1{bar:baz}|] + addCassiusMedia "screen" [lucius|foo2{bar:baz}|] + addCassius [lucius|foo3{bar:baz}|] + +getStaticR :: Handler RepHtml getStaticR = getRootR +runner :: Session () -> IO () runner f = toWaiApp Y >>= runSession f +caseMedia :: IO () caseMedia = runner $ do res <- request defaultRequest assertStatus 200 res flip assertBody res "\n" +caseMediaLink :: IO () caseMediaLink = runner $ do res <- request defaultRequest { pathInfo = ["static"] } assertStatus 200 res diff --git a/yesod-core/Test/NoOverloadedStrings.hs b/yesod-core/test/Test/NoOverloadedStrings.hs similarity index 79% rename from yesod-core/Test/NoOverloadedStrings.hs rename to yesod-core/test/Test/NoOverloadedStrings.hs index e7948dcd..d0a2d6ce 100644 --- a/yesod-core/Test/NoOverloadedStrings.hs +++ b/yesod-core/test/Test/NoOverloadedStrings.hs @@ -1,18 +1,20 @@ {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} -module Test.NoOverloadedStrings (noOverloadedTest) where +module Test.NoOverloadedStrings (noOverloadedTest, Widget) where import Test.Hspec -import Test.Hspec.HUnit +import Test.Hspec.HUnit () import Yesod.Core hiding (Request) import Network.Wai.Test -import Network.Wai import Data.Monoid (mempty) import Data.String (fromString) data Subsite = Subsite + +getSubsite :: a -> Subsite getSubsite = const Subsite + mkYesodSub "Subsite" [] [parseRoutes| /bar BarR GET |] @@ -30,11 +32,16 @@ mkYesod "Y" [parseRoutes| instance Yesod Y where approot _ = fromString "" +getRootR :: Handler () getRootR = return () + +getFooR :: Handler () getFooR = return () +runner :: Session () -> IO () runner f = toWaiApp Y >>= runSession f +case_sanity :: IO () case_sanity = runner $ do res <- request defaultRequest assertBody mempty res diff --git a/yesod-core/Test/Widget.hs b/yesod-core/test/Test/Widget.hs similarity index 83% rename from yesod-core/Test/Widget.hs rename to yesod-core/test/Test/Widget.hs index c106db82..6052c51f 100644 --- a/yesod-core/Test/Widget.hs +++ b/yesod-core/test/Test/Widget.hs @@ -4,12 +4,9 @@ module Test.Widget (widgetTest) where import Test.Hspec -import Test.Hspec.HUnit +import Test.Hspec.HUnit () import Yesod.Core hiding (Request) -import Yesod.Content -import Yesod.Dispatch -import Yesod.Widget import Text.Julius import Text.Lucius import Text.Hamlet @@ -17,15 +14,13 @@ import Text.Hamlet import Network.Wai import Network.Wai.Test -import qualified Data.ByteString.Lazy.Char8 as L8 - data Y = Y mkMessage "Y" "test" "en" type Strings = [String] -mkYesod "Y" [$parseRoutes| +mkYesod "Y" [parseRoutes| / RootR GET /foo/*Strings MultiR GET /whamlet WhamletR GET @@ -35,7 +30,10 @@ mkYesod "Y" [$parseRoutes| instance Yesod Y where approot _ = "http://test" -getRootR = defaultLayout $ toWidgetBody [$julius||] +getRootR :: Handler RepHtml +getRootR = defaultLayout $ toWidgetBody [julius||] + +getMultiR :: [String] -> Handler () getMultiR _ = return () data Msg = Hello | Goodbye @@ -49,7 +47,7 @@ instance RenderMessage Y Msg where getTowidgetR :: Handler RepHtml getTowidgetR = defaultLayout $ do - toWidget [julius|foo|] + toWidget [julius|foo|] :: Widget toWidgetHead [julius|foo|] toWidgetBody [julius|foo|] @@ -60,7 +58,8 @@ getTowidgetR = defaultLayout $ do toWidgetHead [hamlet||] toWidgetBody [hamlet||] -getWhamletR = defaultLayout [$whamlet| +getWhamletR :: Handler RepHtml +getWhamletR = defaultLayout [whamlet|

Test

@{WhamletR}

_{Goodbye} @@ -68,7 +67,7 @@ getWhamletR = defaultLayout [$whamlet| ^{embed} |] where - embed = [$whamlet|

Embed|] + embed = [whamlet|

Embed|] widgetTest :: IO [IO Spec] widgetTest = describe "Test.Widget" @@ -76,12 +75,15 @@ widgetTest = describe "Test.Widget" , it "whamlet" case_whamlet ] +runner :: Session () -> IO () runner f = toWaiApp Y >>= runSession f +case_addJuliusBody :: IO () case_addJuliusBody = runner $ do res <- request defaultRequest assertBody "\n" res +case_whamlet :: IO () case_whamlet = runner $ do res <- request defaultRequest { pathInfo = ["whamlet"] diff --git a/yesod-core/runtests.hs b/yesod-core/test/main.hs similarity index 100% rename from yesod-core/runtests.hs rename to yesod-core/test/main.hs diff --git a/yesod-core/yesod-core.cabal b/yesod-core/yesod-core.cabal index 6ba39440..e7bd0591 100644 --- a/yesod-core/yesod-core.cabal +++ b/yesod-core/yesod-core.cabal @@ -11,7 +11,7 @@ description: The Yesod documentation site has much more information, tutorials and information on some of the supporting packages, like Hamlet and Persistent. category: Web, Yesod stability: Stable -cabal-version: >= 1.6 +cabal-version: >= 1.8 build-type: Simple homepage: http://www.yesodweb.com/ @@ -78,7 +78,8 @@ library test-suite runtests type: exitcode-stdio-1.0 - main-is: test/main.hs + main-is: main.hs + hs-source-dirs: test if flag(ghc7) type: exitcode-stdio-1.0 @@ -92,10 +93,17 @@ test-suite runtests cpp-options: -DTEST build-depends: hspec >= 0.6.1 && < 0.7 ,wai-test + ,wai + ,yesod-core + ,bytestring + ,hamlet + ,shakespeare-css + ,shakespeare-js + ,text + ,http-types ,HUnit ,QuickCheck >= 2 && < 3 ghc-options: -Wall - main-is: runtests.hs source-repository head type: git diff --git a/yesod-form/yesod-form.cabal b/yesod-form/yesod-form.cabal index 53ca69fb..5038761d 100644 --- a/yesod-form/yesod-form.cabal +++ b/yesod-form/yesod-form.cabal @@ -10,6 +10,7 @@ stability: Stable cabal-version: >= 1.6 build-type: Simple homepage: http://www.yesodweb.com/ +description: Form handling support for Yesod Web Framework library build-depends: base >= 4 && < 5 diff --git a/yesod-json/yesod-json.cabal b/yesod-json/yesod-json.cabal index cb690df7..0b4194dc 100644 --- a/yesod-json/yesod-json.cabal +++ b/yesod-json/yesod-json.cabal @@ -10,6 +10,7 @@ stability: Stable cabal-version: >= 1.6 build-type: Simple homepage: http://www.yesodweb.com/ +description: Generate content for Yesod using the aeson package. library build-depends: base >= 4 && < 5 diff --git a/yesod-newsfeed/yesod-newsfeed.cabal b/yesod-newsfeed/yesod-newsfeed.cabal index 9c61fb11..426917f1 100644 --- a/yesod-newsfeed/yesod-newsfeed.cabal +++ b/yesod-newsfeed/yesod-newsfeed.cabal @@ -9,7 +9,8 @@ category: Web, Yesod stability: Stable cabal-version: >= 1.6 build-type: Simple -homepage: http://docs.yesodweb.com/ +homepage: http://www.yesodweb.com/ +description: Helper functions and data types for producing News feeds. library build-depends: base >= 4 && < 5 @@ -26,4 +27,4 @@ library source-repository head type: git - location: git://github.com/snoyberg/yesod-newsfeed.git + location: git://github.com/yesodweb/yesod.git diff --git a/yesod-persistent/yesod-persistent.cabal b/yesod-persistent/yesod-persistent.cabal index 039eb0e8..c4e18a6d 100644 --- a/yesod-persistent/yesod-persistent.cabal +++ b/yesod-persistent/yesod-persistent.cabal @@ -10,6 +10,7 @@ stability: Stable cabal-version: >= 1.6 build-type: Simple homepage: http://www.yesodweb.com/ +description: Some helpers for using Persistent from Yesod. library build-depends: base >= 4 && < 5 diff --git a/yesod-sitemap/yesod-sitemap.cabal b/yesod-sitemap/yesod-sitemap.cabal index be80b159..f55a99a6 100644 --- a/yesod-sitemap/yesod-sitemap.cabal +++ b/yesod-sitemap/yesod-sitemap.cabal @@ -9,7 +9,8 @@ category: Web, Yesod stability: Stable cabal-version: >= 1.6 build-type: Simple -homepage: http://docs.yesodweb.com/ +homepage: http://www.yesodweb.com/ +description: Generate XML sitemaps. library build-depends: base >= 4 && < 5 @@ -21,4 +22,4 @@ library source-repository head type: git - location: git://github.com/snoyberg/yesod-sitemap.git + location: git://github.com/yesodweb/yesod.git diff --git a/yesod-static/Yesod/Static.hs b/yesod-static/Yesod/Static.hs index 69903680..45340add 100644 --- a/yesod-static/Yesod/Static.hs +++ b/yesod-static/Yesod/Static.hs @@ -128,9 +128,11 @@ instance Yesod master => YesodDispatch Static master where \req -> staticApp set req { pathInfo = textPieces } notHidden :: Prelude.FilePath -> Bool -notHidden ('.':_) = False notHidden "tmp" = False -notHidden _ = True +notHidden s = + case s of + '.':_ -> False + _ -> True getFileListPieces :: Prelude.FilePath -> IO [[String]] getFileListPieces = flip go id diff --git a/yesod-static/tests/runtests.hs b/yesod-static/tests/runtests.hs index be62852b..a1dcb983 100644 --- a/yesod-static/tests/runtests.hs +++ b/yesod-static/tests/runtests.hs @@ -1,10 +1,9 @@ {-# LANGUAGE OverloadedStrings #-} -import Yesod.Static +import Yesod.Static () import Test.Hspec import Test.Hspec.HUnit () -- import Test.Hspec.QuickCheck (prop) -import Test.HUnit ((@?=)) main :: IO () main = hspecX $ return [] {- FIXME specs diff --git a/yesod-static/yesod-static.cabal b/yesod-static/yesod-static.cabal index d3f10dcc..dbae5362 100644 --- a/yesod-static/yesod-static.cabal +++ b/yesod-static/yesod-static.cabal @@ -10,6 +10,7 @@ stability: Stable cabal-version: >= 1.8 build-type: Simple homepage: http://www.yesodweb.com/ +description: Static file serving subsite for Yesod Web Framework. flag test description: Build the executable to run unit tests