diff --git a/Test/CleanPath.hs b/Test/CleanPath.hs index d6248ff2..9c7306cf 100644 --- a/Test/CleanPath.hs +++ b/Test/CleanPath.hs @@ -3,7 +3,7 @@ {-# LANGUAGE FlexibleInstances #-} module Test.CleanPath (cleanPathTest) where -import Yesod.Core +import Yesod.Core hiding (Request) import Yesod.Content import Yesod.Dispatch import Yesod.Handler (Route) diff --git a/Test/Exceptions.hs b/Test/Exceptions.hs index 01a7c7c1..e64900a8 100644 --- a/Test/Exceptions.hs +++ b/Test/Exceptions.hs @@ -3,7 +3,7 @@ {-# LANGUAGE FlexibleInstances #-} module Test.Exceptions (exceptionsTest) where -import Yesod.Core +import Yesod.Core hiding (Request) import Yesod.Content import Yesod.Dispatch import Yesod.Handler (Route, ErrorResponse (InternalError)) diff --git a/Test/Widget.hs b/Test/Widget.hs index b3edabff..d9497378 100644 --- a/Test/Widget.hs +++ b/Test/Widget.hs @@ -3,7 +3,7 @@ {-# LANGUAGE FlexibleInstances #-} module Test.Widget (widgetTest) where -import Yesod.Core +import Yesod.Core hiding (Request) import Yesod.Content import Yesod.Dispatch import Yesod.Widget @@ -20,12 +20,14 @@ import qualified Data.ByteString.Lazy.Char8 as L8 data Y = Y mkYesod "Y" [$parseRoutes| / RootR GET +/foo/*Strings MultiR GET |] instance Yesod Y where approot _ = "http://test" getRootR = defaultLayout $ addJuliusBody [$julius||] +getMultiR _ = return () widgetTest :: Test widgetTest = testGroup "Test.Exceptions" diff --git a/Yesod/Internal/Dispatch.hs b/Yesod/Internal/Dispatch.hs index e70d49ad..45e3e178 100644 --- a/Yesod/Internal/Dispatch.hs +++ b/Yesod/Internal/Dispatch.hs @@ -228,11 +228,11 @@ mkSimpleExp segments [MultiPiece _] frontVars x = do fmp <- [|fromMultiPiece|] let exp = CaseE (fmp `AppE` segments) [ Match - (ConP (mkName "Left") [WildP]) + (ConP (mkName "Nothing") []) (NormalB nothing) [] , Match - (ConP (mkName "Right") [VarP next']) + (ConP (mkName "Just") [VarP next']) (NormalB innerExp) [] ]