[web-devel] problems using yesod scaffolding

Sven Koschnicke s.koschnicke at gfxpro.com
Thu Apr 28 10:12:31 CEST 2011


Thanks for the fast fix. I'm afraid there is a similar problem with yesod-auth:

Yesod/Helpers/Auth.hs:177:35: Not in scope: `toSinglePiece'

Yesod/Helpers/Auth.hs:234:28: Not in scope: `fromSinglePiece'
Updating documentation index /Users/darkunicorn/Library/Haskell/doc/index.html
cabal: Error: some packages failed to install:
yesod-0.8.0 depends on yesod-auth-0.4.0 which failed to install.
yesod-auth-0.4.0 failed during the building phase. The exception was:
ExitFailure 1

Sven

Am 27.04.2011 um 22:52 schrieb Michael Litchard:

> Tried that, exact same problem. Is there a way to get more information
> to see what's going on?
> 
> On Tue, Apr 26, 2011 at 9:16 PM, Michael Snoyman <michael at snoyman.com> wrote:
>> 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
>> 
> 
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel




More information about the web-devel mailing list