Re: [Haskell-cafe] Running ghci in a Cabal sandbox

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-g... 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.

ghc including ghci does not know about sandboxes. At all. That is what cabal/stack exec is for; it runs a command inside the sandbox. There are sandboxing mechanisms that don't require this, but they require your shell dotfiles to be set up in a way almost nobody does these days (proper separation of environment variables; otherwise you get things like the sandbox's package database, but the wrong $PATH). hsenv used to work that way. On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com javascript:_e(%7B%7D,'cvml','78emil@gmail.com');> wrote:
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.
_______________________________________________ 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.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I guess I get your point in the general case with various tools working together. But in this case, only ghci is used, and it seems that it gets some information from the variables `CABAL_SANDBOX_CONFIG`, `CABAL_SANDBOX_PACKAGE_PATH` and `GHC_PACKAGE_PATH` (set by `cabal exec`) that it doesn't get from the flag `-package-db`. At least I find that a little strange. / Emil Den 2017-08-04 kl. 16:58, skrev Brandon Allbery:
ghc including ghci does not know about sandboxes. At all. That is what cabal/stack exec is for; it runs a command inside the sandbox.
There are sandboxing mechanisms that don't require this, but they require your shell dotfiles to be set up in a way almost nobody does these days (proper separation of environment variables; otherwise you get things like the sandbox's package database, but the wrong $PATH). hsenv used to work that way.
On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com javascript:_e(%7B%7D,'cvml','78emil@gmail.com');> wrote:
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.
_______________________________________________ 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.

GHC_PACKAGE_PATH is the only one of those that it knows about. And the difference is that --package-db appends to the package database path, whereas GHC_PACKAGE_PATH sets the entire path. You would need an additional option to override the *user* entry on the standard package db path with that of the sandbox, to be compatible with how sandboxes work using only command line options. On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com> wrote:
I guess I get your point in the general case with various tools working together. But in this case, only ghci is used, and it seems that it gets some information from the variables `CABAL_SANDBOX_CONFIG`, `CABAL_SANDBOX_PACKAGE_PATH` and `GHC_PACKAGE_PATH` (set by `cabal exec`) that it doesn't get from the flag `-package-db`.
At least I find that a little strange.
/ Emil
Den 2017-08-04 kl. 16:58, skrev Brandon Allbery:
ghc including ghci does not know about sandboxes. At all. That is what cabal/stack exec is for; it runs a command inside the sandbox.
There are sandboxing mechanisms that don't require this, but they require your shell dotfiles to be set up in a way almost nobody does these days (proper separation of environment variables; otherwise you get things like the sandbox's package database, but the wrong $PATH). hsenv used to work that way.
On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com javascript:_e(%7B%7D,'cvml','78emil@gmail.com');> wrote:
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.
_______________________________________________
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.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Ah, I see. I still don't understand what went wrong in this particular case, but at least it makes sense that there's a difference between `-package-db` and `cabal exec`. I'll leave it at that. Thanks! / Emil Den 2017-08-04 kl. 18:45, skrev Brandon Allbery:
GHC_PACKAGE_PATH is the only one of those that it knows about. And the difference is that --package-db appends to the package database path, whereas GHC_PACKAGE_PATH sets the entire path. You would need an additional option to override the *user* entry on the standard package db path with that of the sandbox, to be compatible with how sandboxes work using only command line options.
On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com> wrote:
I guess I get your point in the general case with various tools working together. But in this case, only ghci is used, and it seems that it gets some information from the variables `CABAL_SANDBOX_CONFIG`, `CABAL_SANDBOX_PACKAGE_PATH` and `GHC_PACKAGE_PATH` (set by `cabal exec`) that it doesn't get from the flag `-package-db`.
At least I find that a little strange.
/ Emil
Den 2017-08-04 kl. 16:58, skrev Brandon Allbery:
ghc including ghci does not know about sandboxes. At all. That is what cabal/stack exec is for; it runs a command inside the sandbox.
There are sandboxing mechanisms that don't require this, but they require your shell dotfiles to be set up in a way almost nobody does these days (proper separation of environment variables; otherwise you get things like the sandbox's package database, but the wrong $PATH). hsenv used to work that way.
On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com javascript:_e(%7B%7D,'cvml','78emil@gmail.com');> wrote:
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.
_______________________________________________
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.

The db path i searched in order from left to right; --package-db appends on the right, whereas stack and cabal normally replace the second entry on the path. (The first is special; it *must* contain the base package with the runtime system. iirc this has caused stack issues in the past, when it needed to override some package other than base living in the first package db. It's also why cabal can't hide stuff installed in the global db.) So with --package-db, cabal will see the user package db before the sandbox --- when it needs to see the sandbox either before or in place of the user db. On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com> wrote:
Ah, I see. I still don't understand what went wrong in this particular case, but at least it makes sense that there's a difference between `-package-db` and `cabal exec`.
I'll leave it at that.
Thanks!
/ Emil
Den 2017-08-04 kl. 18:45, skrev Brandon Allbery:
GHC_PACKAGE_PATH is the only one of those that it knows about. And the difference is that --package-db appends to the package database path, whereas GHC_PACKAGE_PATH sets the entire path. You would need an additional option to override the *user* entry on the standard package db path with that of the sandbox, to be compatible with how sandboxes work using only command line options.
On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com> wrote:
I guess I get your point in the general case with various tools working
together. But in this case, only ghci is used, and it seems that it gets some information from the variables `CABAL_SANDBOX_CONFIG`, `CABAL_SANDBOX_PACKAGE_PATH` and `GHC_PACKAGE_PATH` (set by `cabal exec`) that it doesn't get from the flag `-package-db`.
At least I find that a little strange.
/ Emil
Den 2017-08-04 kl. 16:58, skrev Brandon Allbery:
ghc including ghci does not know about sandboxes. At all. That is what
cabal/stack exec is for; it runs a command inside the sandbox.
There are sandboxing mechanisms that don't require this, but they require your shell dotfiles to be set up in a way almost nobody does these days (proper separation of environment variables; otherwise you get things like the sandbox's package database, but the wrong $PATH). hsenv used to work that way.
On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com javascript:_e(%7B%7D,'cvml','78emil@gmail.com');> wrote:
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. > > _______________________________________________ >
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.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Hi Emil, On Fri, Aug 04, 2017 at 07:10:09PM +0300, Emil Axelsson wrote:
Ah, I see. I still don't understand what went wrong in this particular case, but at least it makes sense that there's a difference between `-package-db` and `cabal exec`.
can you please test if `cabal-cargs` behaves in the same way as `cabal exec` if you add a `-no-user-package-db` or/and replace `-packabe-db` by `-user-package-db`. Greetings, Daniel

Den 2017-08-04 kl. 19:33, skrev Daniel Trstenjak:
Hi Emil,
On Fri, Aug 04, 2017 at 07:10:09PM +0300, Emil Axelsson wrote:
Ah, I see. I still don't understand what went wrong in this particular case, but at least it makes sense that there's a difference between `-package-db` and `cabal exec`.
can you please test if `cabal-cargs` behaves in the same way as `cabal exec` if you add a `-no-user-package-db` or/and replace `-packabe-db` by `-user-package-db`.
Yes! `-no-user-package-db` does the trick. I have to admit I had forgotten completely about the user DB. When running `cabal sandbox hc-pkg list` I only see the global one and the one in the sandbox. But `ghc-pkg` shows the user DB and indeed it contains `hashable-1.2.6.1` which was causing me trouble. Cool, problem solved. Would it make sense then for `cabal-cargs` to always emit `-no-user-package-db` when it discovers a sandbox? Cheers / Emil
Greetings, Daniel _______________________________________________ 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.

Strictly speaking, the second option (specifying the sandbox as the user db) is a more correct match with what cabal-install does. On Friday, August 4, 2017, Emil Axelsson <78emil@gmail.com> wrote:
Den 2017-08-04 kl. 19:33, skrev Daniel Trstenjak:
Hi Emil,
On Fri, Aug 04, 2017 at 07:10:09PM +0300, Emil Axelsson wrote:
Ah, I see. I still don't understand what went wrong in this particular case, but at least it makes sense that there's a difference between `-package-db` and `cabal exec`.
can you please test if `cabal-cargs` behaves in the same way as `cabal exec` if you add a `-no-user-package-db` or/and replace `-packabe-db` by `-user-package-db`.
Yes! `-no-user-package-db` does the trick.
I have to admit I had forgotten completely about the user DB. When running `cabal sandbox hc-pkg list` I only see the global one and the one in the sandbox. But `ghc-pkg` shows the user DB and indeed it contains `hashable-1.2.6.1` which was causing me trouble.
Cool, problem solved.
Would it make sense then for `cabal-cargs` to always emit `-no-user-package-db` when it discovers a sandbox?
Cheers
/ Emil
Greetings,
Daniel _______________________________________________ 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.
_______________________________________________ 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.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Not for this case; it's more for setups that want to skip that slot
entirely (possibly stack, possibly third party setups --- I suspect some of
the big in-house folks would use it for custom sandboxing).
On Friday, August 4, 2017, Daniel Trstenjak
Strictly speaking, the second option (specifying the sandbox as the user db) is a more correct match with what cabal-install does
Ok, is there then a need for the `-no-user-package-db`?
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (3)
-
Brandon Allbery
-
Daniel Trstenjak
-
Emil Axelsson