Fix fromMultiPiece call
This commit is contained in:
parent
372bcf52d8
commit
5e5125a5ac
@ -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)
|
||||
|
||||
@ -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))
|
||||
|
||||
@ -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|<not escaped>|]
|
||||
getMultiR _ = return ()
|
||||
|
||||
widgetTest :: Test
|
||||
widgetTest = testGroup "Test.Exceptions"
|
||||
|
||||
@ -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)
|
||||
[]
|
||||
]
|
||||
|
||||
Loading…
Reference in New Issue
Block a user