[Haskell-cafe] Problems with GHC API and error handling

2013-06-15 Thread Daniel F
Hello, everyone.

I am in need of setting up custom exception handlers when using GHC
API to compile modules. Right now I have the following piece of code:

* Main.hs:
--
import GHC
import GHC.Paths
import MonadUtils
import Exception
import Panic
import Unsafe.Coerce
import System.IO.Unsafe


handleException :: (ExceptionMonad m, MonadIO m)
   = m a - m (Either String a)
handleException m =
  ghandle (\(ex :: SomeException) - return (Left (show ex))) $
  handleGhcException (\ge - return (Left (showGhcException ge ))) $
  flip gfinally (liftIO restoreHandlers) $
  m = return . Right


initGhc :: Ghc ()
initGhc = do
  dfs - getSessionDynFlags
  setSessionDynFlags $ dfs { hscTarget = HscInterpreted
   , ghcLink = LinkInMemory }
  return ()

test :: IO (Either String Int)
test = handleException $ runGhc (Just libdir) $ do
  initGhc
  setTargets = sequence [ guessTarget ./test/file1.hs Nothing ]
  graph - depanal [] False
  loaded - load LoadAllTargets
  -- when (failed loaded) $ throw LoadingException
  setContext (map (IIModule . moduleName . ms_mod) graph)
  let expr = main
  ty - exprType expr -- throws exception if doesn't typecheck
  output ty
  res - unsafePerformIO . unsafeCoerce $ compileExpr expr
  return res

--

* file1.hs:


module Main where

main = do
  return x



The problem is when I run the 'test' function above I receive the
following output:

h test

test/file1.hs:4:10: Not in scope: `x'

Left Cannot add module Main to context: not a home module
it :: Either String Int


So, if I understand this correctly, my exception handler does indeed
catch an exception correctly,
however, I still receive some output which I want to be captured.
Is there a way to do this?

-- 
Sincerely yours,
-- Daniil Frumin

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Platform 2013.2.0.0 64bit.pkg

2013-06-15 Thread aditya bhargava
As a side note, I have stopped having cabal issues since I started using
hsenv. It sandboxes packages for you. So if you have install problems you
just need to delete a local .hsenv directory instead of reinstalling
everything.
On Jun 12, 2013 11:15 PM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:

 My original problem was that I wanted to load a particular set of
 packages using 'cabal install'.  It didn't work (cabal install issues)
 and while the maintainer reacted promptly and helpfully, cabal
 kept on trying to install the wrong version.

 Part of the problem was that blasting away ~/.cabal and ~/Library/Haskell
 wasn't enough:  it's necessary to blast away ~/.ghc as well (which I had
 forgotten existed and of course never saw).

 * It would be handy if 'uninstall-hs' had an option, say
 * uninstall-hs --user
 * so that a user could in one step make it as if they had never
 * used the Haskell Platform.

 (Sigh.  Changes to the GHC command line interface since 7.0 have
 broken one of the packages I used to have installed, and the
 maintainer's e-mail address doesn't work any more.  And sometimes
 it seems as if every time I install anything with cabal something
 else breaks.)

 PS. Earlier today cabal gave me some confusing messages which
 turned out to mean 'GSL isn't installed'.  Non-Haskell dependencies
 could be explained a little more clearly.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Improved ghc-pkg cache warnings

2013-06-15 Thread Andrew Pennebaker
When ghc-pkg observes your cache is out of date, it displays a helpful
warning, recommending ghc-pkg recache. However, sometimes running this
command does not fix the problem, because it targets the wrong cache.

For out of date global caches, ghc-pkg --global recache successfully
clears the warning. For out of date user caches, ghc-pkg --user recache
clears the warning.

In the future, could ghc-pkg display the command more specific to the
problem?

-- 
Cheers,

Andrew Pennebaker
www.yellosoft.us
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Christopher Howard
I'm working through some beginner-level keyboard problems I found at
users.csc.calpoly.edu. One problem is the Saddle Points problem:

quote:

Write a program to search for the saddle points in a 5 by 5 array of
integers. A saddle point is a cell whose value is greater than or equal
to any in its row, and less than or equal to any in its column. There
may be more than one saddle point in the array. Print out the
coordinates of any saddle points your program finds. Print out No
saddle points if there are none.


Let's say I use a simple list grid like so:

code:

array = Grid 5 [ [1,5,3,6,4]
   , [8,2,6,3,8]
   , [3,8,7,2,9]
   , [0,3,7,1,2]
   , [7,2,7,4,5] ]

data Grid = Grid Int [[Int]]


And let's say I take a brute force approach, moving through each cell,
checking to see if it is the greatest in its row and the least in its
column. And say I have functions like so for getting rows and columns:

code:

row (Grid s l) n = if (n = s) then [] else l !! n

col g@(Grid s l) n = if (n = s) then [] else col_ g n 0
where col_ (Grid s l) n i = if (i = s) then [] else (head l !! n) :
col_ (Grid s (tail l)) n (i + 1)


My question: With the way Haskell works (thunks, lazy evaluation, and
all that mystery), is it actually worth the trouble of /precalculating/
the maximum row values and minimum column values, to compare cell values
against? Or will, for example, something like (smallest_list_value (col
array 1)) definitely only evaluate once?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Tommy Thorn
I expect you'll get many replies...

 row (Grid s l) n = if (n = s) then [] else l !! n
 
 col g@(Grid s l) n = if (n = s) then [] else col_ g n 0
where col_ (Grid s l) n i = if (i = s) then [] else (head l !! n) :
 col_ (Grid s (tail l)) n (i + 1)

While such low-level approach (focus on the element) can certainly
be made to work, but Haskell encourages you to think in higher level
constructs.

I haven't seen this problem before but I would map the original array
from [[Int]] - [(Int, (Int, Int), Int, Int)], that is: a list of tuples 
consisting
of the original element, its coordinate, the row maximum and the column
minimum. From there its a trivial filter to find your results. (I'm sure there's
a more elegant solution).

 My question: With the way Haskell works (thunks, lazy evaluation, and
 all that mystery), is it actually worth the trouble of /precalculating/
 the maximum row values and minimum column values, to compare cell values
 against? Or will, for example, something like (smallest_list_value (col
 array 1)) definitely only evaluate once?

There's not enough context to answer the specific question,
but lazy evaluation isn't magic and the answer is probably no.

Tommy


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Christopher Howard
On 06/15/2013 04:39 PM, Tommy Thorn wrote:
 
 
 There's not enough context to answer the specific question,
 but lazy evaluation isn't magic and the answer is probably no.
 
 Tommy
 

Perhaps to simplify the question somewhat with a simpler example.
Suppose you have

code:

let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)


After calculating at x={0,1,2,3}, and the cycle repeats, are sin, cos,
etc. calculated anymore?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Christopher Howard
On 06/15/2013 05:02 PM, Christopher Howard wrote:
 On 06/15/2013 04:39 PM, Tommy Thorn wrote:
 
 Perhaps to simplify the question somewhat with a simpler example.
 Suppose you have
 
 code:
 
 let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)
 
 
 After calculating at x={0,1,2,3}, and the cycle repeats, are sin, cos,
 etc. calculated anymore?

That might have been ambiguous. What I meant was:

code:

let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)


If I calculate (f 0), and the cycle repeats after four values, are sin,
cos, etc. calculated anymore?


-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Clark Gaebel
Yes. In general, GHC won't CSE for you.

  - Clark

On Saturday, June 15, 2013, Christopher Howard wrote:

 On 06/15/2013 04:39 PM, Tommy Thorn wrote:
 
 
  There's not enough context to answer the specific question,
  but lazy evaluation isn't magic and the answer is probably no.
 
  Tommy
 

 Perhaps to simplify the question somewhat with a simpler example.
 Suppose you have

 code:
 
 let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)
 

 After calculating at x={0,1,2,3}, and the cycle repeats, are sin, cos,
 etc. calculated anymore?

 --
 frigidcode.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency/Evaluation Question

2013-06-15 Thread Tikhon Jelvis
There's a very good StackOverflow question which covers this: When is
memoization automatic in GHC?[1]. I found it really cleared up the issue
for me.

[1]:
http://stackoverflow.com/questions/3951012/when-is-memoization-automatic-in-ghc-haskell


On Sat, Jun 15, 2013 at 9:13 PM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Yes. In general, GHC won't CSE for you.

   - Clark


 On Saturday, June 15, 2013, Christopher Howard wrote:

 On 06/15/2013 04:39 PM, Tommy Thorn wrote:
 
 
  There's not enough context to answer the specific question,
  but lazy evaluation isn't magic and the answer is probably no.
 
  Tommy
 

 Perhaps to simplify the question somewhat with a simpler example.
 Suppose you have

 code:
 
 let f x = if (x  4) then f 0 else (sin x + 2 * cos x) : f (x + 1)
 

 After calculating at x={0,1,2,3}, and the cycle repeats, are sin, cos,
 etc. calculated anymore?

 --
 frigidcode.com


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe