[Haskell-cafe] Mutable arrays

2008-02-02 Thread Jeff φ
Hello,

I'm trying to write code that will take a mutable 2D array and normalize it
by dividing all elements by the largest element.

I managed to write code to do this, but it seems overly complex.  I could
write something much simpler in Clean or C++.  Most likely, my code is
complex because I don't have any experience with mutable arrays in Haskell.
I couldn't find any tutorials on the Internet.  I'd be grateful for
suggestions on simplifying the following code.   Thanks.


{-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception #-}

-- normalize_ary This takes a mutable array.  Determines the largest
-- element in the array (max_elem) and then divides every element by
-- max_elem.
normalize_ary :: (Num t1,
  Num t,
  Ix t,
  Ix t1,
  MArray a e t2,
  Ord e,
  Fractional e,
  Enum t,
  Enum t1) =
 a (t, t1) e - t2 ()
normalize_ary ary =
do
-- The following two commented out lines of code show my first
-- attempt at determining a value for max_elem.  However, this
-- produces a stack overflow.

-- elem_ary - getElems ary
 -- let max_elem = foldl1 max elem_ary

max_elem - calc_max_2d_elem ary
max_elem `seq` map_in_place_2d_arr (\x - x / max_elem) ary


map_in_place_2d_arr :: (MArray a e t, Enum t2, Enum t1, Ix t1, Ix t2) =
   (e - e) - a (t1, t2) e - t ()
map_in_place_2d_arr fn arr = ret
where
  ret = do ((i1,j1),(i2,j2)) - getBounds arr
   ( mapM_ (\i -  do v - readArray arr i
  writeArray arr i (fn v) )
   [(i,j) | i - [i1..i2], j - [j1..j2]])


calc_max_2d_elem :: (Ord t, MArray a t t1, Ix t2, Ix t3, Num t3, Num t2) =
a (t3, t2) t - t1 t
calc_max_2d_elem arr =
do m - readArray arr (0,0)
   (_,(i_max, j_max)) - getBounds arr
   let calc_max_loop arr m (i,j)
 | j == j_max = return m
 | otherwise  = do e - readArray arr (i,j)
   let m2 = max e m
   m2 `seq` calc_max_loop arr m2 nxt_idx
 where nxt_idx | i == i_max - 1 = (0,j+1)
   | otherwise  = (i+1,j)
   calc_max_loop arr m (0,0)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Luke Palmer
I prerequest your forgiveness if I sound patronizing, I'm just writing
everything that comes to mind.

2008/2/2 Jeff φ [EMAIL PROTECTED]:
 {-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception #-}

 -- normalize_ary This takes a mutable array.  Determines the largest
  -- element in the array (max_elem) and then divides every element by
 -- max_elem.
  normalize_ary :: (Num t1,
   Num t,
Ix t,
   Ix t1,
MArray a e t2,
   Ord e,
Fractional e,
   Enum t,
Enum t1) =
  a (t, t1) e - t2 ()

Yagh!  Look at that type signature.  That looks like it came from
ghci.  That type should raise a few alarms, such as the Num t, Num t1.
  Why should the indices be numbers?  That indicates that your
implementation is not as general as it should be, so maybe try another
method.  (Really it's calc_max_2d_elem which is losing that
generality).  I usually write my type signatures first, and then let
that guide my implementation.  But you will find differing valid
opinions on this list on that issue.  Anyway, without further ado,
into the guts we go.

  normalize_ary ary =
 do
  -- The following two commented out lines of code show my first
 -- attempt at determining a value for max_elem.  However, this
  -- produces a stack overflow.

 -- elem_ary - getElems ary
   -- let max_elem = foldl1 max elem_ary

Hmm, how big is the array?   If it's pretty big, that's
understandable.  Frankly, it's because foldl sucks: I have never seen
a reason to use it.  You should be using the strict variant foldl'
here.  (I don't think there is a foldl1').  And that will get rid of
your big function calc_max_2d_elem.


 max_elem - calc_max_2d_elem ary
  max_elem `seq` map_in_place_2d_arr (\x - x / max_elem) ary

I don't think that max_elem `seq` is doing anything useful here  (but
I could be missing something subtle).

Oh and a really low level thing which may or may not make a
difference:  floating point division is expensive.  You'd be better
off precalculating 1 / max_elem and then multiplying by that instead.

  map_in_place_2d_arr :: (MArray a e t, Enum t2, Enum t1, Ix t1, Ix t2) =
(e - e) - a (t1, t2) e - t ()

Another conspicuous type signature.  Enum t2, Enum t1 is the red flag
here.  It's because you're using [i1..i2] instead of range (i1,i2)
from Data.Ix.

  map_in_place_2d_arr fn arr = ret
 where
ret = do ((i1,j1),(i2,j2)) - getBounds arr
( mapM_ (\i -  do v - readArray arr i
writeArray arr i (fn v) )
[(i,j) | i - [i1..i2], j - [j1..j2]])

This looks pretty good modulo the [i1..i2] I mentioned above. For this
kind of stuff I prefer to use forM_, as it is a more
imperative-looking construct for imperative-looking code (then you can
lose the parentheses around (\i - ...))...

 calc_max_2d_elem :: (Ord t, MArray a t t1, Ix t2, Ix t3, Num t3, Num t2) =
  a (t3, t2) t - t1 t
 calc_max_2d_elem arr =
  do m - readArray arr (0,0)
(_,(i_max, j_max)) - getBounds arr
 let calc_max_loop arr m (i,j)
  | j == j_max = return m
   | otherwise  = do e - readArray arr (i,j)
let m2 = max e m
 m2 `seq` calc_max_loop arr m2 nxt_idx
  where nxt_idx | i == i_max - 1 = (0,j+1)
 | otherwise  = (i+1,j)
calc_max_loop arr m (0,0)

Hopefully we have done away with this thing given the foldl' thing.
There are a lot of implicit assumptions hiding in this code, such as
indices being zero-based integers.  Writing your type signature first
would have caught those assumptions, since you wouldn't have had (Num
t3, Num t2)  ;-).

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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-02 Thread Alfonso Acosta
On Feb 1, 2008 10:33 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
  Actually it would maybe be better to create common high-level
  interface that could include unary, binary and decimal arithmetic so
  that the library could be easily reused in other projects (people like
  Bjorn, seem to be using the unary implementation). I don't know if it
  would be feasible though.

 I'd say, let's start with the decimal thing.  We can extend our package later
 if there's a need to do this, can't we?

OK, let's do it like that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Rodrigo Queiro
This is my attempt at some nicer code:

maximum' (x:xs) = foldl' max x xs
maximum' _ = undefined

modifyArray :: (MArray a e m, Ix i) = (e - e) - a i e - m ()
modifyArray fn arr = do
bounds - getBounds arr
forM_ (range bounds) (modifyElement fn arr)

modifyElement :: (MArray a e m, Ix i) = (e - e) - a i e - i - m ()
modifyElement fn arr i = do
x - readArray arr i
writeArray arr i (fn x)

normalizeArray :: (MArray a e m, Ix i, Fractional e, Ord e) = a i e - m ()
normalizeArray arr = do
arr_elems - getElems arr
let max_elem = maximum' arr_elems
modifyArray (/max_elem) arr

On 02/02/2008, Jeff φ [EMAIL PROTECTED] wrote:
 Hello,

 I'm trying to write code that will take a mutable 2D array and normalize
it
 by dividing all elements by the largest element.

 I managed to write code to do this, but it seems overly complex.  I could
 write something much simpler in Clean or C++.  Most likely, my code is
 complex because I don't have any experience with mutable arrays in
Haskell.
 I couldn't find any tutorials on the Internet.  I'd be grateful for
 suggestions on simplifying the following code.   Thanks.


 {-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception #-}

 -- normalize_ary This takes a mutable array.  Determines the largest
  -- element in the array (max_elem) and then divides every element by
 -- max_elem.
  normalize_ary :: (Num t1,
   Num t,
Ix t,
   Ix t1,
MArray a e t2,
   Ord e,
Fractional e,
   Enum t,
Enum t1) =
  a (t, t1) e - t2 ()
  normalize_ary ary =
 do
  -- The following two commented out lines of code show my first
 -- attempt at determining a value for max_elem.  However, this
  -- produces a stack overflow.

 -- elem_ary - getElems ary
   -- let max_elem = foldl1 max elem_ary

 max_elem - calc_max_2d_elem ary
  max_elem `seq` map_in_place_2d_arr (\x - x / max_elem) ary


  map_in_place_2d_arr :: (MArray a e t, Enum t2, Enum t1, Ix t1, Ix t2) =
(e - e) - a (t1, t2) e - t ()
  map_in_place_2d_arr fn arr = ret
 where
ret = do ((i1,j1),(i2,j2)) - getBounds arr
( mapM_ (\i -  do v - readArray arr i
writeArray arr i (fn v)
 )
[(i,j) | i - [i1..i2], j - [j1..j2]])


 calc_max_2d_elem :: (Ord t, MArray a t t1, Ix t2, Ix t3, Num t3, Num t2)
=
  a (t3, t2) t - t1 t
 calc_max_2d_elem arr =
  do m - readArray arr (0,0)
(_,(i_max, j_max)) - getBounds arr
 let calc_max_loop arr m (i,j)
  | j == j_max = return m
   | otherwise  = do e - readArray arr (i,j)
let m2 = max e m
 m2 `seq` calc_max_loop
 arr m2 nxt_idx
  where nxt_idx | i == i_max - 1 = (0,j+1)
 | otherwise  = (i+1,j)
calc_max_loop arr m (0,0)


 ___
 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


Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Rodrigo Queiro
Sorry, I was lazy. New maximum':
maximum' = foldl1' max

On 02/02/2008, Rodrigo Queiro [EMAIL PROTECTED] wrote:

 This is my attempt at some nicer code:

 maximum' (x:xs) = foldl' max x xs
 maximum' _ = undefined

 modifyArray :: (MArray a e m, Ix i) = (e - e) - a i e - m ()
 modifyArray fn arr = do
 bounds - getBounds arr
 forM_ (range bounds) (modifyElement fn arr)

 modifyElement :: (MArray a e m, Ix i) = (e - e) - a i e - i - m ()
 modifyElement fn arr i = do
 x - readArray arr i
 writeArray arr i (fn x)

 normalizeArray :: (MArray a e m, Ix i, Fractional e, Ord e) = a i e - m
 ()
 normalizeArray arr = do
 arr_elems - getElems arr
 let max_elem = maximum' arr_elems
 modifyArray (/max_elem) arr

 On 02/02/2008, Jeff φ [EMAIL PROTECTED] wrote:
  Hello,
 
  I'm trying to write code that will take a mutable 2D array and normalize
 it
  by dividing all elements by the largest element.
 
  I managed to write code to do this, but it seems overly complex.  I
 could
  write something much simpler in Clean or C++.  Most likely, my code is
  complex because I don't have any experience with mutable arrays in
 Haskell.
  I couldn't find any tutorials on the Internet.  I'd be grateful for
  suggestions on simplifying the following code.   Thanks.
 
 
  {-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception #-}
 
  -- normalize_ary This takes a mutable array.  Determines the largest
   -- element in the array (max_elem) and then divides every element by
  -- max_elem.
   normalize_ary :: (Num t1,
Num t,
 Ix t,
Ix t1,
 MArray a e t2,
Ord e,
 Fractional e,
Enum t,
 Enum t1) =
   a (t, t1) e - t2 ()
   normalize_ary ary =
  do
   -- The following two commented out lines of code show my first
  -- attempt at determining a value for max_elem.  However, this
   -- produces a stack overflow.
 
  -- elem_ary - getElems ary
-- let max_elem = foldl1 max elem_ary
 
  max_elem - calc_max_2d_elem ary
   max_elem `seq` map_in_place_2d_arr (\x - x / max_elem) ary
 
 
   map_in_place_2d_arr :: (MArray a e t, Enum t2, Enum t1, Ix t1, Ix t2)
 =
 (e - e) - a (t1, t2) e - t ()
   map_in_place_2d_arr fn arr = ret
  where
 ret = do ((i1,j1),(i2,j2)) - getBounds arr
 ( mapM_ (\i -  do v - readArray arr i
 writeArray arr i (fn v)
  )
 [(i,j) | i - [i1..i2], j - [j1..j2]])
 
 
  calc_max_2d_elem :: (Ord t, MArray a t t1, Ix t2, Ix t3, Num t3, Num t2)
 =
   a (t3, t2) t - t1 t
  calc_max_2d_elem arr =
   do m - readArray arr (0,0)
 (_,(i_max, j_max)) - getBounds arr
  let calc_max_loop arr m (i,j)
   | j == j_max = return m
| otherwise  = do e - readArray arr (i,j)
 let m2 = max e m
  m2 `seq` calc_max_loop
  arr m2 nxt_idx
   where nxt_idx | i == i_max - 1 = (0,j+1)
  | otherwise  = (i+1,j)
 calc_max_loop arr m (0,0)
 
 
  ___
  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


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-02 Thread Alfonso Acosta
On Feb 1, 2008 10:32 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Freitag, 1. Februar 2008 13:00 schrieb Alfonso Acosta:
  On Jan 31, 2008 11:35 PM, Wolfgang Jeltsch [EMAIL PROTECTED]
   This is essentially what I had in mind.  While Oleg's implementation
   needs a thrusted core, the GADT solution doesn't.
 
  True. However using GADTs doesn't allow to internally make use of
  Arrays, which (tell me if I'm wrong) are likely to be faster than the
  naive GADT implementation.

 It depends.  My first GADT implementation is equivalent to the [] type and
 often [] is better than arrays.  For example, if you read the contents of a
 file and process it with maps, filters, etc., [] is likely to give you
 constant space usage which arrays don't.  If you want to lookup elements by
 index, then arrays are better, of course.  For my purpose, it would be fine
 to use a []-like implementation, I think.

For mine it would be fine too. Let's implement our needs and then
maybe extend it if someone rants about it.

  To make it friendlier for the end user I thought about defining
  aliases for lets say the first 1 numbers using Template Haskell.
  That could even make error reports friendlier (not sure to what point
  though). What do you think?

 I have no clear opinion about that at the moment.  Maybe it's okay to use the
 representation directly.  This way, we don't introduce a dependeny on the
 Template Haskell language extension (which is only supported by GHC), and the
 actual representation will occur in error messages anyway whenever the
 message shows a computed number.

Well, my EDSL already makes extensive use of TH. So, being selfish, it
wouldn't be a problem for me (or any other GHC user) and I think it
would make the library much more usable.

Just compare

f :: List (() :- D1 :- D0 :- D0 :- 1000) Int - List (() :- D1 :- D0
:- D0 :- D0) Int

with, let's say

f :: List A1000 Int - List A1000 Int

Again, if someone complains about the TH dependency, the aliases could
be generated by TH but saved statically in a module for each release.

  So, we'll be making two separate libraries then. We should think about
  names.
 
  What about FixedVector for the vector library and DecTypArith (maybe
  too long) or DecTypes for the type-level decimal arithmetic library?

 Alas, there is an inconsistency in naming packages already.  Some prefer names
 which are entirely lowercase, some prefer camel case.  I prefer lowercase,
 with hyphens separating parts of the name.  And I also don't like unusual
 abbreviations like typ (not much shorter than type).  To mention
 arithmetics is not so important.  So maybe something
 like type-level-decimals?

 Maybe it's better to put different type-level programming things into a single
 package.  Then we could name this package type-level or something similar.
 We could start with our decimals.  Other type-level things could be added
 later.  I already have some code about type-level booleans.  It's not very
 sensible to put these few lines into a separate package.  It might be nice if
 we had a general type-level programming package where I could put this code
 into.

Sounds sensible. However, I would rather prefer something like
type-level-comp (from type level computations) or type-level-prog
(from type level programming). Type level by itself doesn't describe
the functionality of the package.

 As for the name of the fixed-size list package, I have to say that I don't
 like the term vector in this context.  A vector is actually something with
 addition and scalar multiplication defined on it.  Maybe we should make also
 this package's scope wider.  What about something like safe-data or
 similar?

I think safe-data is a bit too general and might lead to confusion
with other safe data packages (namely Mitchell's Safe library). Since
the main particularity of the library is that safety properties are
achieved via emulating dependent types I think that
light-dependent-types (from lightweight dependent types),
number-parameterized-data or simply parameterized-data (this is the
name I like best) would be more appropiate.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-02 Thread Alfonso Acosta
On Feb 2, 2008 2:54 PM, Alfonso Acosta [EMAIL PROTECTED] wrote:
 Just compare

 f :: List (() :- D1 :- D0 :- D0 :- 1000) Int - List (() :- D1 :- D0
 :- D0 :- D0) Int

I meant

f :: List (() :- D1 :- D0 :- D0 :- D0) Int - List (() :- D1 :- D0 :-
D0 :- D0) Int

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


Re: [Haskell-cafe] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Duncan Coutts

On Fri, 2008-02-01 at 11:42 +, Magnus Therning wrote:
 Is it possible to get Cabal to use 'cl' (Microsoft's C/C++ compiler
 shipped with Visual Studio Express)?

The problem is to get GHC to use 'cl'. That's a longer term project that
GHC HQ are interested in. There's something about it on the GHC dev wiki
I think. Don't hold your breath.

 I've found the Wiki page on using Visual Studio to create a DLL, then
 convert it to a .a file so that GHC can consume it.  I'd rather skip
 using Visual Studio to build things and just ship a Cabalised package.

You can create .dlls without using VS of course, if that's what you're
trying to do.

Duncan

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


Re: [Haskell-cafe] Issues with hsql-sqllite build; errors from the hackage download

2008-02-02 Thread Duncan Coutts

On Fri, 2008-02-01 at 17:05 -0500, bbrown wrote:
 There seems to be an issue with the hsql-sqlite3.  Anyone have a fix.  Should
 I use what is from darcs?

HSQL is currently unmaintained. Frederik Eaton was considering taking it
over: http://www.nabble.com/HSQL-defunct--td14978532.html

Gentoo has a fix:
http://haskell.org/~gentoo/gentoo-haskell/dev-haskell/hsql-sqlite/hsql-sqlite-1.7.ebuild
The code in src_unpack() is replacing the Setup.hs with a default copy
and then adding 'extra-libraries: sqlite3' to the .cabal file. Pretty
straightforward. This does assume that you have sqlite3 installed in the
default global location.

You may also like to consider alternatives like HDBC-sqlite3.

Duncan

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


Re: [Haskell-cafe] Issues with hsql-sqllite build; errors from the hackage download

2008-02-02 Thread Sterling Clover
Just noticed, by the way, that haskelldb doesn't build correctly  
because it still hasn't updated the cabal for the base split. On the  
other hand, the development repo (which is 0.11 -- 0.10 is on  
hackage) builds fine. Are the maintainers planning to get an updated  
version on hackage?


--S

On Feb 2, 2008, at 10:16 AM, Duncan Coutts wrote:



On Fri, 2008-02-01 at 17:05 -0500, bbrown wrote:
There seems to be an issue with the hsql-sqlite3.  Anyone have a  
fix.  Should

I use what is from darcs?


HSQL is currently unmaintained. Frederik Eaton was considering  
taking it

over: http://www.nabble.com/HSQL-defunct--td14978532.html

Gentoo has a fix:
http://haskell.org/~gentoo/gentoo-haskell/dev-haskell/hsql-sqlite/ 
hsql-sqlite-1.7.ebuild

The code in src_unpack() is replacing the Setup.hs with a default copy
and then adding 'extra-libraries: sqlite3' to the .cabal file. Pretty
straightforward. This does assume that you have sqlite3 installed  
in the

default global location.

You may also like to consider alternatives like HDBC-sqlite3.

Duncan

___
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


Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Chaddaï Fouché
2008/2/2, Rodrigo Queiro [EMAIL PROTECTED]:
 Sorry, I was lazy. New maximum':
 maximum' = foldl1' max

Sorry but none of those propositions change the heart of the problem :
the list of elements is totally produced before she can be consumed
due to the strict monadic (IO or ST) nature of getElems. Thus you get
an extraordinary waste of memory as well as resources...

To address this I propose this function :
foldl1MArray' :: (MArray a e m, Ix i) = (e - e - e) - a i e - m e
foldl1MArray' f a = do
  (l,u) - getBounds a
  firstElem - readArray a l
  foldM (\a mb - a `seq` mb = return . f a)
firstElem (map (readArray a) (range (l,u)))

With this, we can rewrite the original program using the excellent
modifyArray from Rodrigo :
normalizeArray :: (MArray a e m, Ix i, Fractional e, Ord e) = a i e - m ()
normalizeArray arr = do
max_elem - foldl1MArray' max arr
modifyArray (* (1/max_elem)) arr

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


Re: [Haskell-cafe] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Felix Martini
Magnus Therning wrote:
 Is it possible to get Cabal to use 'cl' (Microsoft's C/C++ compiler
 shipped with Visual Studio Express)?

Duncan Coutts wrote:
 The problem is to get GHC to use 'cl'. That's a longer term project that
 GHC HQ are interested in. There's something about it on the GHC dev wiki
 I think. Don't hold your breath.

When using the native code generator only foreign C code must be
compiled with a C compiler. Presently Cabal passes C sources that are
listed in the 'c-sources' field of a cabal file to GHC. It would be
nice to have a Cabal field to specify the compiler for C sources, say
'c-sources-compiler: msvc'. The default would still be gcc, but with a
Cabal flag the user would be able to change that to e.g. Sun's C
compiler.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: HList error with hFoldr

2008-02-02 Thread Denis Bueno
On Jan 28, 2008 12:45 AM,  [EMAIL PROTECTED] wrote:
 It seems strange that you need the types e and e' (perhaps this is a
 quirk or a bug of GHC 6.8). With GHC 6.6, I have derived the following


 instance (Floating f, MetricSpace e f, HFoldr ApplyDistSum Float l1 f,
   HZip (HCons e l) (HCons e l) (HCons (e,e) l1))
  = MetricSpace (HCons e l) f where
 c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c')

 which matches my intuitive understanding, and also sufficient to run
 the given examples.

This also works in GHC 6.8.  Thanks!

 When I wrote `I derived with GHC' I meant it literally. First I wrote
 the instance without any constraints:

 instance ()
  = MetricSpace (HCons e l) f where
 c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c')

 GHC of course complained about many missing constraints. I started
 adding the constraints from the list of complaints, until GHC was
 satisfied. This is basically a cut-and-paste job from the Emacs buffer
 with GHC error messages to the buffer with the code.

Wow.  I will try this next time I post.  Thanks very much.

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


Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Stefan O'Rear
On Sat, Feb 02, 2008 at 12:57:47PM +, Rodrigo Queiro wrote:
 This is my attempt at some nicer code:
 
 maximum' (x:xs) = foldl' max x xs
 maximum' _ = undefined
 
 modifyArray :: (MArray a e m, Ix i) = (e - e) - a i e - m ()
 modifyArray fn arr = do
 bounds - getBounds arr
 forM_ (range bounds) (modifyElement fn arr)
 
 modifyElement :: (MArray a e m, Ix i) = (e - e) - a i e - i - m ()
 modifyElement fn arr i = do
 x - readArray arr i
 writeArray arr i (fn x)
 
 normalizeArray :: (MArray a e m, Ix i, Fractional e, Ord e) = a i e - m ()
 normalizeArray arr = do
 arr_elems - getElems arr
 let max_elem = maximum' arr_elems
 modifyArray (/max_elem) arr

Note that by using getElems, you are throwing away most of the
advantages of arrays, since it is strict (it has to be, since it's
effectively an IO function and lazy IO is unsound wrt Haskell's normal
semantics) and converts the whole thing into a list.

If I just had this one bit of code to do, I'd use explicit loop:

normalizeArray arr = do b - getBounds arr ; m - findMax b
forM_ (range b) (edit m)
  where
findMax  (i:is)= findMax' is = readArray arr i
findMax' (i:is) !v = findMax' is . max v = readArray arr i
findMax' [] !v = return v

edit mx i = writeArray arr i . (/mx) = readArray arr i

With a little more, I'd probably set the scene with a few
array-modifying combinators, inspired by Oleg's left-fold idea:

-- yes, I'm passing four arguments to foldr.  this is not a mistake.
foldA fn ac arr = getBounds arr = \b -
  foldr (\ i ct acc - ct = fn i ac = readArray arr i)
(\_ - return ac) (range b) ac

foldAp fn = foldA (\i a b - return (fn a b))

maxA = foldAp max minBound
mapA fn ar = foldA (\i _ v - writeArray ar i (fn v)) () ar

normalize arr = maxA arr = \ m - mapA (/m) arr

Stefan


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


Re: [Haskell-cafe] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Duncan Coutts

On Sat, 2008-02-02 at 18:15 +0100, Felix Martini wrote:
 Magnus Therning wrote:
  Is it possible to get Cabal to use 'cl' (Microsoft's C/C++ compiler
  shipped with Visual Studio Express)?
 
 Duncan Coutts wrote:
  The problem is to get GHC to use 'cl'. That's a longer term project that
  GHC HQ are interested in. There's something about it on the GHC dev wiki
  I think. Don't hold your breath.
 
 When using the native code generator only foreign C code must be
 compiled with a C compiler. Presently Cabal passes C sources that are
 listed in the 'c-sources' field of a cabal file to GHC. It would be
 nice to have a Cabal field to specify the compiler for C sources, say
 'c-sources-compiler: msvc'. The default would still be gcc, but with a
 Cabal flag the user would be able to change that to e.g. Sun's C
 compiler.

It would be reasonable to use the system C compiler rather than ghc,
however we will have to do more work to find what extra include dirs get
used and have Cabal pass those.

Currently we pass the -package flags to ghc which ghc uses to look up
what include dirs those packages add, and then it calls the C compiler
with those extra include dirs. Cabal would have to do that itself.

Duncan

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


Re: [Haskell-cafe] Refactoring from State monad to ST monad, for STUArray

2008-02-02 Thread Derek Elkins
On Sat, 2008-02-02 at 12:33 -0500, Denis Bueno wrote:
 Is it possible to use the ST monad as a (drop-in) replacement for the
 State monad in the following situation?  If not, is there a best
 practice for refactoring?
 
 I have a bunch of functions that return state actions:
 
 type MyState = ...
 
 foo1 :: T1 - State MyState a
 foo2 :: T2 - State MyState a
 ...
 foon :: Tn - State MyState a
 
 And I'd like to refactor this to use the ST monad, mechanically, if
 possible.  All uses of the MyState inside State are single-threaded.
 
 In my application, MyState is a record with 5 or so fields.  One of
 those fields uses a list to keep track of some information, and I'd
 like to change that to STUArray, because it changes my bottleneck
 operations from O(n) to O(1).  This, of course, requires having the ST
 monad around, in order to achieve the proper time complexity.
 
 Is there an easy way to do this?  In the future, should I *start out*
 with the ST monad if I suspect I'll need to use an imperative data
 structure for efficiency reasons?  I started out with State because
 I'm modeling a transition system, so it seemed natural.
 
 Any advice is appreciated.

%s/State MyState/MyMonad s/g

type MyState s = ... s ...

type MyMonad s = StateT (MyState s) (ST s)


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


Re: [Haskell-cafe] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Magnus Therning
Duncan Coutts wrote:
[..]
 It would be reasonable to use the system C compiler rather than ghc,
 however we will have to do more work to find what extra include dirs get
 used and have Cabal pass those.
 
 Currently we pass the -package flags to ghc which ghc uses to look up
 what include dirs those packages add, and then it calls the C compiler
 with those extra include dirs. Cabal would have to do that itself.

Well it sounds like I'll have to settle for a two-step build procedure
for the time being.  Luckily I managed to recall the existence of CMake
just today, so it seems I can make my Haskell-hacking-on-Windows
experience somewhat bearable...

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus.therning@gmail.com
http://therning.org/magnus

What if I don't want to obey the laws? Do they throw me in jail with
the other bad monads?
 -- Daveman



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] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Duncan Coutts

On Sat, 2008-02-02 at 18:50 +, Magnus Therning wrote:
 Duncan Coutts wrote:
 [..]
  It would be reasonable to use the system C compiler rather than ghc,
  however we will have to do more work to find what extra include dirs get
  used and have Cabal pass those.
  
  Currently we pass the -package flags to ghc which ghc uses to look up
  what include dirs those packages add, and then it calls the C compiler
  with those extra include dirs. Cabal would have to do that itself.
 
 Well it sounds like I'll have to settle for a two-step build procedure
 for the time being.  Luckily I managed to recall the existence of CMake
 just today, so it seems I can make my Haskell-hacking-on-Windows
 experience somewhat bearable...

Just so I'm sure I understand...

So you're building a .dll using just C code and then you want to link
that in with a Haskell prog that uses that .dll. And it is essential
that the C code be built using MS's C compiler and not gcc.

Is that right? And you'd like to have the .dll built using Cabal rather
than having to hack an external C/Makefile.

Or are you just trying to link some C code statically into a haskell
program, but it just so happens that this C code relies on being built
with MS's C compiler rather than gcc.

Perhaps you could clarify what it is you're trying to do (the end goal,
just just the minutia) so we can see what feature it is that Cabal is
missing that would help your situation. When we figure that out we can
file a feature request so it is not forgotten.

Duncan

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


Re: [Haskell-cafe] Refactoring from State monad to ST monad, for STUArray

2008-02-02 Thread Ryan Ingram
You can also do something like the following:

newtype StateST st s a = StateST { internalRunStateST :: ReaderT
(STRef st s) (ST st) a }

instance MonadState s (StateST s st) where
get = ask = readSTRef
put s = ask = \ref - writeSTRef ref s

runStateST :: StateST st s a - s - ST st a
runStateST m s = do
ref - newSTRef s
runReaderT (internalRunStateST m) ref

  -- ryan


On Feb 2, 2008 9:05 AM, Derek Elkins [EMAIL PROTECTED] wrote:
 On Sat, 2008-02-02 at 12:33 -0500, Denis Bueno wrote:
  Is it possible to use the ST monad as a (drop-in) replacement for the
  State monad in the following situation?  If not, is there a best
  practice for refactoring?
 
  I have a bunch of functions that return state actions:
 
  type MyState = ...
 
  foo1 :: T1 - State MyState a
  foo2 :: T2 - State MyState a
  ...
  foon :: Tn - State MyState a
 
  And I'd like to refactor this to use the ST monad, mechanically, if
  possible.  All uses of the MyState inside State are single-threaded.
 
  In my application, MyState is a record with 5 or so fields.  One of
  those fields uses a list to keep track of some information, and I'd
  like to change that to STUArray, because it changes my bottleneck
  operations from O(n) to O(1).  This, of course, requires having the ST
  monad around, in order to achieve the proper time complexity.
 
  Is there an easy way to do this?  In the future, should I *start out*
  with the ST monad if I suspect I'll need to use an imperative data
  structure for efficiency reasons?  I started out with State because
  I'm modeling a transition system, so it seemed natural.
 
  Any advice is appreciated.

 %s/State MyState/MyMonad s/g

 type MyState s = ... s ...

 type MyMonad s = StateT (MyState s) (ST s)



 ___
 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


Re: [Haskell-cafe] Issues with hsql-sqllite build; errors from the hackage download

2008-02-02 Thread Bjorn Bringert
Yes. It would be nice to have an updated HSQL release first though.

/Björn

On Feb 2, 2008 6:07 PM, Sterling Clover [EMAIL PROTECTED] wrote:
 Just noticed, by the way, that haskelldb doesn't build correctly
 because it still hasn't updated the cabal for the base split. On the
 other hand, the development repo (which is 0.11 -- 0.10 is on
 hackage) builds fine. Are the maintainers planning to get an updated
 version on hackage?

 --S


 On Feb 2, 2008, at 10:16 AM, Duncan Coutts wrote:

 
  On Fri, 2008-02-01 at 17:05 -0500, bbrown wrote:
  There seems to be an issue with the hsql-sqlite3.  Anyone have a
  fix.  Should
  I use what is from darcs?
 
  HSQL is currently unmaintained. Frederik Eaton was considering
  taking it
  over: http://www.nabble.com/HSQL-defunct--td14978532.html
 
  Gentoo has a fix:
  http://haskell.org/~gentoo/gentoo-haskell/dev-haskell/hsql-sqlite/
  hsql-sqlite-1.7.ebuild
  The code in src_unpack() is replacing the Setup.hs with a default copy
  and then adding 'extra-libraries: sqlite3' to the .cabal file. Pretty
  straightforward. This does assume that you have sqlite3 installed
  in the
  default global location.
 
  You may also like to consider alternatives like HDBC-sqlite3.
 
  Duncan
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutable arrays

2008-02-02 Thread Henning Thielemann

On Sat, 2 Feb 2008, [ISO-8859-7] Jeff ö wrote:

 Hello,

 I'm trying to write code that will take a mutable 2D array and normalize it
 by dividing all elements by the largest element.

Are you sure you need the arrays to be mutable? Maybe it's fast enough to
do the copying - it's significantly easier anyway. If all operations run
over the whole array, like the normalization, then it's not much a matter
speed, but only a matter of memory. That is you need the double amount of
memory, because the data can be processed and copied forth and back. You
can even reduce this further, if you can come up with an optimizer fusion
framework.

With immutable arrays you can easily implement
  let xm = maximum (Array.elems arr)
  in  fmap (/xm) arr

Ok, better use the strict maximum' proposed by others in this thread.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] highlighting-kate - syntax highlighting library

2008-02-02 Thread John MacFarlane
Hello all,

I've been working on a source code syntax highlighting library. It is
now somewhat usable, and help would be welcome in testing it further, so
I'm making it publicly available:

darcs get http://johnmacfarlane.net/repos/highlighting-kate

Currently, the following languages are supported:

AdaAsp  AwkBash Bibtex
C  CmakeColdfusion Commonlisp   Cpp
CssDDiff   Djangotemplate   Doxygen
DtdErlang   FortranHaskell  Html
Java   Javadoc  Javascript Json Latex
LexLiterateHaskell  LuaMakefile Matlab
Mediawiki  Nasm Objectivec Objectivecpp Ocaml
Pascal Perl PhpPostscript   Prolog
Python Ruby Scala  Scheme   Sgml
SqlSqlMysql SqlPostgresql  Tcl  Texinfo
XmlXslt Yacc

The parsers for individual languages are automatically generated
from Kate syntax definitions.  The xml files have been included
in the repository, together with the program that converts them to
Haskell modules.  There's also a standalone program, Highlight, that
you can use to test the highlighting. (See README for instructions.)

Bug reports and patches are welcome.  Note that I don't want to make
any manual modifications to the generated modules in
Text/Highlighting/Kate/Syntax. Changes should be made either in the
source xml files or in the program ParseSyntaxFiles.hs that generates
these modules.

John

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


[Haskell-cafe] weird behavior with FFI

2008-02-02 Thread Tim Newsham

I am working on haskell bindings to C functions using FFI.  I have
a callback function that returns IO ().  When I pass in the callback
function:
foo = printf foo

it crashes (is there an easy way to debug this exception using ghc6.8.2?)
bot: SilcClient_d1al: uncaught exception

however, if I pass in the callback function:
foo = do
printf foo
return ()

it does not crash.  Is this a bug in my bindings?  In ghc/ffi?
Full code is at:
   http://www.thenewsh.com/%7Enewsham/silcbot.tgz

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring from State monad to ST monad, for STUArray

2008-02-02 Thread Denis Bueno
Thanks for all the responses.  I have never used monad transformers
before, but StateT is welcome and really cool.  I didn't even think to
look them up.

I have a follow up question.  I eventually get to a point where I have
a value of type (ST s (Maybe (STUArray s Int Int))), and I need
somehow to get rid of the Maybe, so I can call runSTUArray on it.  The
function containing this value returns a pure type:

 data Solution = Sat (UArray Int Int) | Unsat deriving (Eq)

I've included the function body below, along with a few comments that
hopefully make my problem clear enough.  Let me know if there's any
more detail needed:

 solve :: StdGen - Cnf - Solution
 solve rnd cnf =
-- To solve, we simply take baby steps toward the solution using solveStep,
-- starting with the empty assignment.
Sat . runSTUArray $
do solution - -- this block, as you can see,
   -- is the (ST s (STUArray s Int Int)) value
  evalStateT (stepToSolution $ do
initialAssignment - lift (newArray (1, numVars cnf) 0)
solveStep initialAssignment)
  SC{cnf=cnf, dm=Map.empty, dl=[], bad=Set.empty, rnd=rnd}
   case solution of -- `solution' is the (Maybe (STUArray s Int Int)) value
 Nothing - error unsat
 Just m - return m

Using `error' in the Nothing case is exactly what I'd like to avoid.
How should I improve this?


On Feb 2, 2008 2:57 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
 You can also do something like the following:

 newtype StateST st s a = StateST { internalRunStateST :: ReaderT
 (STRef st s) (ST st) a }

 instance MonadState s (StateST s st) where
 get = ask = readSTRef
 put s = ask = \ref - writeSTRef ref s

 runStateST :: StateST st s a - s - ST st a
 runStateST m s = do
 ref - newSTRef s
 runReaderT (internalRunStateST m) ref

   -- ryan



 On Feb 2, 2008 9:05 AM, Derek Elkins [EMAIL PROTECTED] wrote:
  On Sat, 2008-02-02 at 12:33 -0500, Denis Bueno wrote:
   Is it possible to use the ST monad as a (drop-in) replacement for the
   State monad in the following situation?  If not, is there a best
   practice for refactoring?
  
   I have a bunch of functions that return state actions:
  
   type MyState = ...
  
   foo1 :: T1 - State MyState a
   foo2 :: T2 - State MyState a
   ...
   foon :: Tn - State MyState a
  
   And I'd like to refactor this to use the ST monad, mechanically, if
   possible.  All uses of the MyState inside State are single-threaded.
  
   In my application, MyState is a record with 5 or so fields.  One of
   those fields uses a list to keep track of some information, and I'd
   like to change that to STUArray, because it changes my bottleneck
   operations from O(n) to O(1).  This, of course, requires having the ST
   monad around, in order to achieve the proper time complexity.
  
   Is there an easy way to do this?  In the future, should I *start out*
   with the ST monad if I suspect I'll need to use an imperative data
   structure for efficiency reasons?  I started out with State because
   I'm modeling a transition system, so it seemed natural.
  
   Any advice is appreciated.
 
  %s/State MyState/MyMonad s/g
 
  type MyState s = ... s ...
 
  type MyMonad s = StateT (MyState s) (ST s)
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 




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


Re: [Haskell-cafe] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Magnus Therning
Duncan Coutts wrote:
[..]
 Just so I'm sure I understand...

Sure thing.

 Or are you just trying to link some C code statically into a haskell
 program, but it just so happens that this C code relies on being built
 with MS's C compiler rather than gcc.

Yes, this is exactly it.  I mean, I could probably hack the incomplete
mingw header files to add the functions I need, but I thought it'd be
much easier to just use Microsoft's development environment.

 Perhaps you could clarify what it is you're trying to do (the end goal,
 just just the minutia) so we can see what feature it is that Cabal is
 missing that would help your situation. When we figure that out we can
 file a feature request so it is not forgotten.

The end goal is to sneak Haskell into the work place ;-)

What I'd really like to see is the ability to “drive” development
completely from Haskell.  With that I mean to, just as on Linux, have a
single cabal file that compiles the C code containing the wrappers while
still having access to a complete development environment.  On Windows
that means compiling C/C++ with MS's tool set.

I hope that clarifies what goes on in my muddy mind a bit...

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus.therning@gmail.com
http://therning.org/magnus

What if I don't want to obey the laws? Do they throw me in jail with
the other bad monads?
 -- Daveman



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] weird behavior with FFI

2008-02-02 Thread Tim Newsham

Am Samstag, 2. Februar 2008 schrieb Tim Newsham:

I am working on haskell bindings to C functions using FFI.  I have
a callback function that returns IO ().  When I pass in the callback
function:



I suspect this has to do with printf returning 'undefined' if you use it
with an IO type. Something in the code looks at the result and crashes.
Your second version is equivalent to printf foo = \_ - return (),
i.e. it never evaluates printf's result but returns () instead.
Fixing the first version would require some changes to Text.Printf,
restricting the 'a' in PrintfType (IO a).


But the callback function is already of type IO () as mentioned above.


HTH, Lukas


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Refactoring from State monad to ST monad, for STUArray

2008-02-02 Thread Daniel Fischer
Am Samstag, 2. Februar 2008 23:17 schrieb Denis Bueno:
 Thanks for all the responses.  I have never used monad transformers
 before, but StateT is welcome and really cool.  I didn't even think to
 look them up.

 I have a follow up question.  I eventually get to a point where I have
 a value of type (ST s (Maybe (STUArray s Int Int))), and I need
 somehow to get rid of the Maybe, so I can call runSTUArray on it.  The

 function containing this value returns a pure type:
  data Solution = Sat (UArray Int Int) | Unsat deriving (Eq)

 I've included the function body below, along with a few comments that
 hopefully make my problem clear enough.  Let me know if there's any

 more detail needed:
  solve :: StdGen - Cnf - Solution
  solve rnd cnf =
 -- To solve, we simply take baby steps toward the solution using
  solveStep, -- starting with the empty assignment.
 Sat . runSTUArray $
 do solution - -- this block, as you can see,
-- is the (ST s (STUArray s Int Int)) value
   evalStateT (stepToSolution $ do
 initialAssignment - lift (newArray (1, numVars
  cnf) 0) solveStep initialAssignment)
   SC{cnf=cnf, dm=Map.empty, dl=[], bad=Set.empty, rnd=rnd}
case solution of -- `solution' is the (Maybe (STUArray s Int Int))
  value Nothing - error unsat
  Just m - return m

 Using `error' in the Nothing case is exactly what I'd like to avoid.
 How should I improve this?

Would

solve rnd cnf =
case evalStateT ... of
Nothing - Unsat
Just st - Sat $ runSTUArray st

work? Might need some explicit 'forall s.' or not typecheck at all, didn't 
test.

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


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-02 Thread Antoine Latter
I'm not a fan of parameterizing the Stream class over the monad parameter `m':

 class Stream s m t | s - t where
uncons :: s - m (Maybe (t,s))

which leads to instance declarations like so:

 instance Monad m = Stream [tok] m tok where
 uncons [] = return $ Nothing
 uncons (t:ts) = return $ Just (t,ts)

I looked through the sources and I didn't see anywhere where this
parameterization gained anything.  As a proof of this I did a
mechanical re-write removing the class parameter, and the library
still seems to work.

-Antoine

On Feb 1, 2008 11:15 PM, Derek Elkins [EMAIL PROTECTED] wrote:
 [Now with 100% more correct darcs get URLs.]

 I'm currently getting Paolo Martini's Google Summer of Code project, an
 updated version of Parsec, into a releasable state, and I will be
 maintaining it for at least a while.

 Paolo's major additions are:
 * The Parser monad has been generalized into a Parser monad
   transformer
 * The parsers have been generalized to work over a stream of any
   type, in particular, with bytestrings.

 I have made a few minor additions as well:
 * There is Haddock documentation for almost all functions
 * The Parser monad now has Applicative/Alternative instances

 Currently, I am looking for people to give it a go reporting any bugs in
 the library or documentation, troubles building it, or changes/features
 they would like.  I'm also interested in performance information.

 Most old Parsec code should be relatively easy but not trivial to port.
 There is a darcs repository on code.haskell.org.  If nothing comes up,
 I'll put a package on Hackage in about a week or so.

 To get the code:
 darcs get http://code.haskell.org/parsec3

 To build it, the standard cabal commands should work:
 http://haskell.org/haskellwiki/Cabal/How_to_install_a_Cabal_package

 Alternatively, you can use the cabal-install application:
 http://hackage.haskell.org/trac/hackage/wiki/CabalInstall

 The documentation can be generated also via the normal cabal routine, or
 via cabal-install.

 The Text.Parsec modules should be preferred to the
 Text.ParserCombinators.Parsec modules.


 ___
 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] Circular enums

2008-02-02 Thread Ben Butler-Cole

Hello

I'm 
trying 
to 
define 
functions 
that 
allow 
you 
to 
traverse 
a 
bounded 
enumeration, 
wrapping 
at 
the 
start 
and 
the 
end.

My implementation looks like this:

next, 
prev 
:: 
(Enum 
a, 
Bounded 
a) 
= 
a 
- 
a
next 
= 
turn 
1
prev 
= 
turn 
(-1)

turn 
:: 
(Enum 
a, 
Bounded 
a) 
= 
Int 
- 
a 
- 
a
turn 
n 
e 
= 
toEnum 
(add 
(fromEnum 
(maxBound::a) 
+ 
1) 
(fromEnum 
e) 
n)
  
  
where
  
  
  
add 
mod 
x 
y 
= 
(x 
+ 
y 
+ 
mod) 
`rem` 
mod

Which fails to type check under GHC with this error:

No instance for (Bounded a)
  arising from use of `maxBound' at Hbot.hs:6:34-41
Probable fix: add (Bounded a) to the expected type of an expression
In the expression: maxBound :: a
In the first argument of `fromEnum', namely `(maxBound :: a)'
In the first argument of `(+)', namely `fromEnum (maxBound :: a)'

My (clearly flawed) understanding of the signature I've specified for 'turn' 
means *exactly* that a is Bounded.

Can anyone enlighten me as to where my understanding is going awry and how 
(whether) I can achieve what I'm trying to do.

Thank you 
Ben


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


[Haskell-cafe] Circular enums - resend

2008-02-02 Thread Ben Butler-Cole
[Resending 
with 
formatting 
fixed.]

Hello

I'm 
trying 
to 
define 
functions 
that 
allow 
you 
to 
traverse 
a 
bounded 
enumeration, 
wrapping 
at 
the 
start 
and 
the 
end.

My 
implementation 
looks 
like 
this:

  
  
next, 
prev 
:: 
(Enum 
a, 
Bounded 
a) 
= 
a 
- 
a
  
  
next 
= 
turn 
1
  
  
prev 
= 
turn 
(-1)
  
  
  
  
turn 
:: 
(Enum 
a, 
Bounded 
a) 
= 
Int 
- 
a 
- 
a
  
  
turn 
n 
e 
= 
toEnum 
(add 
(fromEnum 
(maxBound::a) 
+ 
1) 
(fromEnum 
e) 
n)
  
  
  
  
where
  
  
  
  
  
add 
mod 
x 
y 
= 
(x 
+ 
y 
+ 
mod) 
`rem` 
mod

Which 
fails 
to 
type 
check 
under 
GHC 
with 
this 
error:

  
  
No 
instance 
for 
(Bounded 
a)
  
  
  
arising 
from 
use 
of 
`maxBound' 
at 
Hbot.hs:6:34-41
  
  
Probable 
fix: 
add 
(Bounded 
a) 
to 
the 
expected 
type 
of 
an 
expression
  
  
In 
the 
expression: 
maxBound 
:: 
a
  
  
In 
the 
first 
argument 
of 
`fromEnum', 
namely 
`(maxBound 
:: 
a)'
  
  
In 
the 
first 
argument 
of 
`(+)', 
namely 
`fromEnum 
(maxBound 
:: 
a)'

My 
(clearly 
flawed) 
understanding 
of 
the 
signature 
I've 
specified 
for 
'turn' 
means 
*exactly* 
that 
a 
is 
Bounded.

Can 
anyone 
enlighten 
me 
as 
to 
where 
my 
understanding 
is 
going 
awry 
and 
how 
(whether) 
I 
can 
achieve 
what 
I'm 
trying 
to 
do.

Thank 
you
Ben





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


Re: [Haskell-cafe] Circular enums

2008-02-02 Thread Brandon S. Allbery KF8NH


On Feb 2, 2008, at 18:41 , Ben Butler-Cole wrote:


No instance for (Bounded a)
  arising from use of `maxBound' at Hbot.hs:6:34-41
(...)
My (clearly flawed) understanding of the signature I've specified  
for 'turn' means *exactly* that a is Bounded.


The problem is that the scope of a is the type signature; it does  
*not* extend to the definition.


You can try omitting the type on maxBound and minBound, or you can  
enable the scoped type variables extension ( http://www.haskell.org/ 
ghc/docs/latest/html/users_guide/other-type-extensions.html#scoped- 
type-variables ).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Circular enums

2008-02-02 Thread Ben Butler-Cole
On 
Feb 
2, 
2008, 
at 
18:41 
, I
wrote:

  
  
 
No 
instance 
for 
(Bounded 
a)
  
  
  
 
arising 
from 
use 
of 
`maxBound' 
at 
Hbot.hs:6:34-41
 
(...)
 
My 
(clearly 
flawed) 
understanding 
of 
the 
signature 
I've 
specified  
 
for 
'turn' 
means 
*exactly* 
that 
a 
is 
Bounded.

Brandon Allbery replied:

 The 
problem 
is 
that 
the 
scope 
of 
a 
is 
the 
type 
signature; 
it 
does  
 *not* 
extend 
to 
the 
definition.

 You 
can 
try 
omitting 
the 
type 
on 
maxBound 
and 
minBound, 
or 
you
 can enable 
the 
scoped 
type 
variables 
extension

Thank you. This compiles fine with the Glasgow extensions turned on as long as 
the type in the function signature is universally quantified:

turn :: forall a. (Enum a, Bounded a) = Int - a - a
turn n e = toEnum (add (fromEnum (maxBound::a) + 1) (fromEnum e) n)
where
  add mod x y = (x + y + mod) `rem` mod




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


[Haskell-cafe] strange GHC assembler failure

2008-02-02 Thread Tim Newsham

I'm getting a weird build error:
[ 9 of 95] Compiling Plugin.Pl.Common ( Plugin/Pl/Common.hs, 
dist/build/lambdabot/lambdabot-tmp/Plugin/Pl/Common.o )

/tmp/ghc52608_0/ghc52608_0.s: Assembler messages:

/tmp/ghc52608_0/ghc52608_0.s:36:0:  Error: unassigned file number 1
[... more of these ...]

I narrowed this down -- this happens when I add my new library
silc-client to the Build-depends: line in the cabal file even
if none of its code is referenced.  Removing the dependency makes
the error go away.  The module I'm referencing is a new one I'm
still working on and it makes use of FFI and references external
headers and libraries.
(I put a copy at http://www.thenewsh.com/~newsham/silc-client.tgz
if it helps anyone debug..  this is not release-quality code
though).

Any idea what is going on here?

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-02 Thread Philippa Cowderoy
On Sat, 2 Feb 2008, Antoine Latter wrote:

 I'm not a fan of parameterizing the Stream class over the monad 
 parameter `m':
snip
 I looked through the sources and I didn't see anywhere where this
 parameterization gained anything.  As a proof of this I did a
 mechanical re-write removing the class parameter, and the library
 still seems to work.
 

AngloHaskell attendees may remember the quickie I did on handling the 
layout rule via a parsing monad transformer - removing this would stop me 
from generating the input stream in a particular monad and break the trick 
behind it.

The idea was to use a lexing monad which the parser would be stacked on 
top of, such that the parser could communicate with the lexer and delayout 
function. Then when the parser failed at a point where a closing brace 
would allow parsing to continue, it could backtrack in the stream, tell 
the lexer that it failed the first time and ask for the character again - 
and if the layout rule allows it at that point, the returned character 
would this time be a closing brace.

-- 
[EMAIL PROTECTED]

Performance anxiety leads to premature optimisation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal, GHC, FFI and Visual Studio on Windows

2008-02-02 Thread Duncan Coutts

On Sat, 2008-02-02 at 22:33 +, Magnus Therning wrote:
 Duncan Coutts wrote:
 [..]
  Just so I'm sure I understand...
 
 Sure thing.
 
  Or are you just trying to link some C code statically into a haskell
  program, but it just so happens that this C code relies on being built
  with MS's C compiler rather than gcc.
 
 Yes, this is exactly it.  I mean, I could probably hack the incomplete
 mingw header files to add the functions I need, but I thought it'd be
 much easier to just use Microsoft's development environment.
 
  Perhaps you could clarify what it is you're trying to do (the end goal,
  just just the minutia) so we can see what feature it is that Cabal is
  missing that would help your situation. When we figure that out we can
  file a feature request so it is not forgotten.
 
 The end goal is to sneak Haskell into the work place ;-)
 
 What I'd really like to see is the ability to “drive” development
 completely from Haskell.  With that I mean to, just as on Linux, have a
 single cabal file that compiles the C code containing the wrappers while
 still having access to a complete development environment.  On Windows
 that means compiling C/C++ with MS's tool set.
 
 I hope that clarifies what goes on in my muddy mind a bit...

Ok, so you could create a separate component to produce the .dll / .a
from the C code but you'd prefer the convenience of being able to just:
c-sources: blah.c
and have them included in the project, but built using the MS C
compiler.

So I think we should file a feature request about building C sources
using gcc/ms-c directly rather than going via ghc as that would give us
the flexibility to use alternative C compilers.

Perhaps you'd like to file it, otherwise I can.
http://hackage.haskell.org/trac/hackage/

Duncan

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


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-02 Thread Antoine Latter
On Feb 2, 2008 5:28 PM, Antoine Latter [EMAIL PROTECTED] wrote:
 I'm not a fan of parameterizing the Stream class over the monad parameter 
 `m':

  class Stream s m t | s - t where
 uncons :: s - m (Maybe (t,s))

 which leads to instance declarations like so:

  instance Monad m = Stream [tok] m tok where
  uncons [] = return $ Nothing
  uncons (t:ts) = return $ Just (t,ts)


To expand on this point, side-effect instances of Stream don't play
nice with the backtracking in Text.Parsec.Prim.try:

 import Text.Parsec
 import Text.Parsec.Prim
 import System.IO
 import Control.Monad

 type Parser a = (Stream s m Char) = ParsecT s u m a

This particular instance was suggested by Derek.

 instance Stream Handle IO Char where
uncons hdl = do
b - hIsEOF hdl
if b then return Nothing
 else liftM (\c - Just (c,hdl)) getChar

 testParser :: Parser String
 testParser = try (string hello1) | string hello2

 test1 = runPT testParser () stdin stdin = print
 test2 = hGetLine stdin = print . runP testParser () stdin

test1 uses the  (Stream Handle IO Char) instance, test2 uses the
(Monad m = Stream [a] m a) instance.

For input hello2, test2 produces a valid parse while test1 does not.

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


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-02 Thread Philippa Cowderoy
On Sat, 2 Feb 2008, Antoine Latter wrote:

 To expand on this point, side-effect instances of Stream don't play
 nice with the backtracking in Text.Parsec.Prim.try:
 
  import Text.Parsec
  import Text.Parsec.Prim
  import System.IO
  import Control.Monad
 
  type Parser a = (Stream s m Char) = ParsecT s u m a
 
 This particular instance was suggested by Derek.
 

snip

We've been kicking this around on IRC a little, it took me a moment to 
remember the problem. Basically the problem isn't parsec/try playing badly 
with the stream - it's the stream playing badly with parsec/try. You need 
to keep track of where in the file you are and either cache it in an IORef 
or use seek to jump about appropriately. At the moment, Derek's instance 
doesn't know where it is in the stream so Parsec's backtracking is 
invisible to the underlying monad. That caching is the source of the 
potential leak I mentioned to you, because Parsec doesn't currently tell 
the stream when it's committed up to a given point and anything preceding 
it can be dropped safely.

We'll tell the list a nice story about this over the coming week. For now, 
it's nearly 3am here and I should get to bed!

-- 
[EMAIL PROTECTED]

The task of the academic is not to scale great
intellectual mountains, but to flatten them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-02 Thread Derek Elkins
On Sat, 2008-02-02 at 20:43 -0600, Antoine Latter wrote:
 On Feb 2, 2008 5:28 PM, Antoine Latter [EMAIL PROTECTED] wrote:
  I'm not a fan of parameterizing the Stream class over the monad parameter 
  `m':
 
   class Stream s m t | s - t where
  uncons :: s - m (Maybe (t,s))
 
  which leads to instance declarations like so:
 
   instance Monad m = Stream [tok] m tok where
   uncons [] = return $ Nothing
   uncons (t:ts) = return $ Just (t,ts)
 
 
 To expand on this point, side-effect instances of Stream don't play
 nice with the backtracking in Text.Parsec.Prim.try:
 
  import Text.Parsec
  import Text.Parsec.Prim
  import System.IO
  import Control.Monad
 
  type Parser a = (Stream s m Char) = ParsecT s u m a
 
 This particular instance was suggested by Derek.
 
  instance Stream Handle IO Char where
 uncons hdl = do
 b - hIsEOF hdl
 if b then return Nothing
  else liftM (\c - Just (c,hdl)) getChar
 
  testParser :: Parser String
  testParser = try (string hello1) | string hello2
 
  test1 = runPT testParser () stdin stdin = print
  test2 = hGetLine stdin = print . runP testParser () stdin
 
 test1 uses the  (Stream Handle IO Char) instance, test2 uses the
 (Monad m = Stream [a] m a) instance.
 
 For input hello2, test2 produces a valid parse while test1 does not.

Note that instance has a typo in it (which I fixed before testing this
myself): getChar should be (hGetChar hdl) (though that makes no
difference when you pass in stdin)

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


[Haskell-cafe] ANN: Hlist 0.1 on Hackage

2008-02-02 Thread gwern0
Hey everyone:

I'd like to make a short announcement that with the permission of its 
maintainer, I've uploaded HList v0.1 to Hackage. You can find the Hackage page 
here: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HList-0.1. 
'cabal install HList' should also work.

HList for those who don't know is a sort of OO Haskell package which permits 
heterogeneous lists; you can find out more at 
http://homepages.cwi.nl/~ralf/HList/. (The Darcs repository is at 
http://darcs.haskell.org/HList.)

What changes have been made to the darcs repo? Well, they are mostly updates 
and cleanups -  I've updated build-depends for GHC 6.8.x; largely moved from 
-fglasgow-exts to LANGUAGE pragmas; put the modules in a proper module 
namespace; fixed up Haddock generation; removed some unused files, and other 
things of that nature.

--
gwern
Covert data bank Armani Larson Missiles Dick CTP SO13 AUTODIN


pgpXMNyRA7zZg.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe