
I'm doing a database action, inside a Form action. I had wanted to do it inside a Handler, as I had figured out how to make it work. But I could not figure out how to pass the data the Form needs from the Handler. Here's the error, followed by the code I am trying to use.
Handler/Manager.hs:68:16: No instance for (PersistBackend (YesodPersistBackend master0) (GGHandler sub0 master0 IO) ) arising from a use of `isFree' Possible fix: add an instance declaration for (PersistBackend (YesodPersistBackend master0) (GGHandler sub0 master0 IO)) In a stmt of a 'do' expression: testFree <- isFree testDay In the expression: do { pInfo <- liftIO getUIdata; let products = V.toList $ V.map productACC $ fst pInfo versions = V.toList $ V.map versionsACC $ snd pInfo ....; testFree <- isFree testDay; (productRes, productView) <- mreq (radioField products) "Placeholder" No thing; .... } In an equation for `productForm': productForm extra = do { pInfo <- liftIO getUIdata; let products = ... ....; testFree <- isFree testDay; .... }
Handler/Manager.hs:68:16: Couldn't match expected type `Control.Monad.Trans.RWS.Lazy.RWST (Maybe (Env, FileEnv), Scheduler, [Yesod.For m.Types.Lang]) Enctype Ints (GGHandler Scheduler Scheduler IO) t0' with actual type `GGHandler sub0 master0 monad0 Bool' In the return type of a call of `isFree' In a stmt of a 'do' expression: testFree <- isFree testDay In the expression: do { pInfo <- liftIO getUIdata; let products = V.toList $ V.map productACC $ fst pInfo versions = V.toList $ V.map versionsACC $ snd pInfo ....; testFree <- isFree testDay; (productRes, productView) <- mreq (radioField products) "Placeholder" Nothing;
postManagerR :: Handler RepHtml postManagerR = do ((res, widget), enctype) <- runFormPost productForm dataInsert <- case (addEntry res) of Left blank -> blank Right result -> result -- let testDay = C.fromGregorian 2011 12 27 -- I would prefer to have the code in the Handler if I could figure out how to get it to the Form? State Monad? -- testFree <- isFree testDay defaultLayout [whamlet| <p>Result:#{show dataInsert} <form enctype=#{enctype}> ^{widget} |]
productForm :: Html -> Form Scheduler Scheduler (FormResult SelectedProduct, Widget) productForm extra = do pInfo <- liftIO getUIdata let products = V.toList $ V.map productACC $ fst pInfo versions = V.toList $ V.map versionsACC $ snd pInfo testDay = C.fromGregorian 2011 12 27 testFree <- isFree testDay (productRes, productView) <- mreq (radioField products) "Placeholder" Nothing versionInfo <- mapM generateVersionSelectFields versions -- (dateRes, dateView) <- mreq requestedDayField "Schedule" Nothing (dateRes, dateView) <- mreq (jqueryDayField def { jdsChangeYear = True , jdsYearRange = "2011:2012" }) "Schedule" Nothing
isFree day = do match <- runDB $ selectList [TestStartDate ==. day, TestStatus !=. Passed, TestStatus !=. Failed] [] if (L.null match) then liftIOHandler (return True) else
let versionRes = map fst versionInfo versionViews = map snd versionInfo widget = do toWidget [whamlet| #{extra} <p> ^{fvInput productView} $forall versionView <- versionViews ^{fvInput versionView} ^{fvInput dateView} <input type=submit value="Request Test"> |] return (makeSelected productRes versionRes dateRes, widget) liftIOHandler (return False) I don't think the lack of an instance declaration is the real problem but an indication I am just doing it wrong. What 'it' is, is a mystery to me. ghci tells me this
isFree :: (YesodPersist master, PersistBackend (YesodPersistBackend master) (GGHandler sub master IO), Control.Monad.IO.Class.MonadIO monad) => Day -> GGHandler sub master monad Bool
I believe I am using liftIOHandler correctly, I'm not sure what I am doing wrong. What I am sure of is it probably has to do with not understanding Yesod monads well enough. Feedback welcome.