[Haskell-cafe] Running ghci in a Cabal sandbox

Emil Axelsson 78emil at gmail.com
Fri Aug 4 12:57:26 UTC 2017


Thanks for your reply! But I actually don't want `cabal repl`. The 
bigger picture is explained here:

http://fun-discoveries.blogspot.com/2017/08/building-haskell-projects-with-ghc.html

Towards the end of that post I suggest using `cabal exec` to integrate 
with a Cabal sandbox; however, as Daniel Trstenjak pointed out, that 
shouldn't be needed since `cabal-cargs` already sets the `-package-db` 
flag for GHC.

So my question is why `cabal exec` is needed (in this particular case) 
even though `-package-db` is given?

I know `cabal exec` sets a few environment variables 
(`CABAL_SANDBOX_CONFIG`, `CABAL_SANDBOX_PACKAGE_PATH` and 
`GHC_PACKAGE_PATH`). I've checked that these are all set correctly, so 
Cabal seems to be doing its job. But it's not clear why ghci gets 
confused when these variables are not set (and `-package-db` is given), 
but not when the variables are set.

Cheers

/ Emil

Den 2017-08-04 kl. 15:31, skrev nek0:
> Hi Emil,
> 
> What you want is hidden behind the `cabal repl` command, which starts
> ghci with the package-db of the sandbox.
> 
> Greetings,
> 
> nek0
> 
> On 4.8.2017 13:41, Emil Axelsson wrote:
>> Hi!
>>
>> I have a small file Test.hs alone in a directory:
>>
>>      {-# LANGUAGE DeriveGeneric #-}
>>
>>      module Test where
>>
>>      import Data.Hashable
>>      import Data.Scientific
>>      import GHC.Generics
>>
>>      data Sc = Sc Scientific deriving (Generic)
>>
>>      instance Hashable Sc
>>
>> To be able to load this file, I set up a Cabal sandbox:
>>
>>      $ ghc --numeric-version
>>      8.0.2
>>
>>      $ cabal --numeric-version
>>      1.24.0.2
>>
>>      $ cabal sandbox init
>>      ...
>>
>>      $ cabal install hashable-1.2.6.0 scientific
>>      ...
>>
>> (Note: not the latest version of hashable.)
>>
>> Now, if I try to run GHCi and point it to the sandbox' package database
>> I get this error:
>>
>>      $ ghci
>> -package-db=.cabal-sandbox/x86_64-linux-ghc-8.0.2-packages.conf.d
>> Test.hs GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
>>      [1 of 1] Compiling Test             ( Test.hs, interpreted )
>>
>>      Test.hs:12:14: error:
>>          • No instance for (Hashable Scientific)
>>              arising from a use of
>> ‘hashable-1.2.6.1:Data.Hashable.Class.$dmhashWithSalt’
>>          • In the expression:
>>              hashable-1.2.6.1:Data.Hashable.Class.$dmhashWithSalt @Sc
>>            In an equation for ‘hashWithSalt’:
>>                hashWithSalt
>>                  = hashable-1.2.6.1:Data.Hashable.Class.$dmhashWithSalt @Sc
>>            In the instance declaration for ‘Hashable Sc’
>>
>> Somehow it mixes in version 1.2.6.1 of hashable, even though this
>> package isn't installed (neither in the sandbox nor the global database).
>>
>> It turns out that wrapping the command in `cabal exec` fixes the problem:
>>
>>      $ cabal exec -- ghci
>> -package-db=.cabal-sandbox/x86_64-linux-ghc-8.0.2-packages.conf.d Test.hs
>>      GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
>>      [1 of 1] Compiling Test             ( Test.hs, interpreted )
>>      Ok, modules loaded: Test.
>>      *Test>
>>
>> Any idea what's going on?
>>
>> / Emil
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.


More information about the Haskell-Cafe mailing list