[web-devel] problems using yesod scaffolding
Michael Snoyman
michael at snoyman.com
Wed Apr 27 06:16:32 CEST 2011
On Wed, Apr 27, 2011 at 1:21 AM, Michael Litchard <michael at schmong.org> wrote:
> running yesod with the mini option caused some problems. I got
> complaints of not being able to find Settings.hs, so I made some
> changes to the import statements.
> Also, I changed the directory config to Config to accommodate my changes.
>
> Here's what the import sections look like now
>
> Aframe.hs
>
> module Aframe
> ( Aframe (..)
> , AframeRoute (..)
> , resourcesAframe
> , Handler
> , Widget
> , module Yesod.Core
> , module Config.Settings <---- made a change here
> , StaticRoute (..)
> , lift
> , liftIO
> ) where
>
> import Yesod.Core
> import Yesod.Helpers.Static
> import qualified Config.Settings as Settings <---- made a change here
> import System.Directory
> import qualified Data.ByteString.Lazy as L
> import Config.Settings (hamletFile, cassiusFile, juliusFile,
> widgetFile) <----- made a change here
> import Config.StaticFiles <----- made a change here
> import Control.Monad (unless)
>
>
> Controller.hs
> {-# LANGUAGE TemplateHaskell #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE OverloadedStrings #-}
> {-# OPTIONS_GHC -fno-warn-orphans #-}
> module Controller
> ( withAframe
> , withDevelApp
> ) where
>
> import Aframe
> import qualified Config.Settings as Settings <---- made a change here
> import Yesod.Helpers.Static
> import Data.ByteString (ByteString)
> import Network.Wai (Application)
> import Data.Dynamic (Dynamic, toDyn)
>
>
> that said, I get out of scope errors when I try to run the scaffolding
> generated code
>
> mlitchard at apotheosis:~/repository/Aframe$ wai-handler-devel 3000
> Aframe withDevelApp
> Attempting to interpret your app...
> Compile failed:
>
> Not in scope: `withDevelApp'
>
> also get the same problem when trying withAframe
>
> I can't see the reason for the out of scope problem. I think it has to
> do with the changes I made. Anything suspicious pop out for anyone?
>
I think you want to use wai-handler-devel 3000 Controller withAframe
Michael
More information about the web-devel
mailing list