Re: How to best add logging/debugging code?

2003-11-17 Thread Johannes Waldmann
Ben Escoto wrote:
Hi all, does anyone have any tips on how to insert debugging or
logging statements through a program?  Here are two possibilities:
another thing I found quite useful is
to add a component  { .. , info :: Doc } to my data types,
and then set its value at each function call:
f x y = ( ... ) { info = parens $ fsep [ text f, info x, info y ] }

( I figure this is sort of part of what
some tools can do automatically? )
that way you always know who built what.
and it's cheap - if you don't use this information,
then it's never created (due to laziness).
best regards,
--
-- Johannes Waldmann,  Tel/Fax: (0341) 3076 6479 / 6480 --
-- http://www.imn.htwk-leipzig.de/~waldmann/ -
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: How to best add logging/debugging code?

2003-11-17 Thread ketil+haskell
Johannes Waldmann [EMAIL PROTECTED] writes:

 f x y = ( ... ) { info = parens $ fsep [ text f, info x, info y ] }

Cool!

 that way you always know who built what.
 and it's cheap - if you don't use this information,
 then it's never created (due to laziness).

Uh..is that really true?  I would think it would keep a lot of data
from being garbage collected?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Implementation of while loop

2003-11-17 Thread Abraham Egnor
While while can be implemented in haskell, I would strongly suggest you
look at using the many higher-order functions available (foldl/foldr, map,
filter, etc.) - they're much more in line with the spirit of the language,
and will lend themselves to much clearer expressions once you get the hang
of them.

What sort of thing do you want to do in your while loop?  Is it a pure
processing function, or an IO-related one?

Abe

[EMAIL PROTECTED] writes:
Hi,does any one knows how to implement while-do loop or nested while-do
loop?
I'm in a situation that I need to implement  nested while do loop with
some if-
then-else condition in my code,but I have no idea about it.Thanks.

Ray




This mail sent through www.mywaterloo.ca
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell




___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


ANN: H98 FFI Addendum 1.0, Release Candidate 16

2003-11-17 Thread Manuel M T Chakravarty
Dear Haskell Folks,

Release Candidate 16 of the H98 FFI Addendum 1.0 is now
available from

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

Since the last version of the Addendum announced on
[EMAIL PROTECTED], namely RC12, the FFI Task Force
decided on a slight generalisation of the interface to
finalizers as well as the addition of some support for
string marshalling for characters sets beyond ASCII.  A
detailed change log is at the end of this message.

I'd like to propose RC16 as the final form of Version 1.0 of
the FFI Addendum.  If you find any problems with this
version, please raise them within the next two weeks.

Cheers,
Manuel

-=-

Changes since RC15:
* 6.3: Footnote regarding __STDC_ISO_10646__ added to text introducing
   `CWString'.

Changes since RC14:
* 6.2: CWChar - CWchar
* 6.3: - CWChar - CWchar
   - Stated explicitly that memory allocated by `newCString' and friends
 can be deallocated by `MarshalAlloc.free'
   - Improved documentation

Changes since RC13:
* 5.3: Fixed typo
* 5.7: Fixed a mistake in the type of `peekByteOff' and `pokeByteOff' (the
   type variable constrained by `Storable' must be different from the
   parameter of the `Ptr')
* 6.3: Improved documentation

Changes since RC12:
* Acks : Added John Meacham
* 4.1.5: Bug fix courtesy of Wolfgang Thaller
* 5.5  : Added `FinalizerEnvPtr', `newForeignPtrEnv', and
 `addForeignPtrFinalizerEnv'
* 6.3  : Added John Meacham proposal for `wchar_t' support as well localised
 string marshalling; in particular, this adds `CWString' and
 `CWStringLen' as well as the `CWString' and the `CAString' family
 of marshalling routines.  In addition, `charIsRepresentable' was
 added. 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Subsumption in partially ordered sets

2003-11-17 Thread Graham Klyne
I have a need for an algorithm to perform subsumption on partially 
ordered sets of values.  That is, given a selection of values from a 
partially ordered set, remove all values from the collection that are less 
than some other member of the collection.

Below is some code I have written, which works, but I'm not sure that it's 
especially efficient or elegant.  Are there any published Haskell libraries 
that contain something like this?

#g
--
(The implementation here is based on values of type (Eq a) = [Maybe a], 
where the partial ordering is defined by function 'pcompare'.  Function 
dropSubsumed (and helpers) is the subsumption calculation.  testds1, 
testds2, testds3, testds4, testds5 are test cases, and all should be True.)

[[
-- Type for result of partial order comparison (PNR is no-relationship)
data PartOrdering = PLT | PEQ | PGT | PNR deriving (Eq, Show)
--  Drop tuples from the supplied list that are subsumed by
--  more specific ones.
--
dropSubsumed :: (Eq a) = [[Maybe a]] - [[Maybe a]]
dropSubsumed []  = []
dropSubsumed [a] = [a]
dropSubsumed (a1:as) = dropSubsumed1 a1 as
dropSubsumed1 a1 []   = [a1]
dropSubsumed1 a1 (a2:a2s) = case pcompare a1 a2 of
PEQ - dropSubsumed1 a1 a2s
PGT - dropSubsumed1 a1 a2s
PLT - dropSubsumed1 a2 a2s
PNR - dropSubsumed2 [] a1 $ dropSubsumed1 a2 a2s
--  Merge new head element into list from which subsumed elements
--  have already been removed.  The extra (first) parameter is used
--  to construct a result in which the order of remaining elements
--  is preserved with respect to the original list.
dropSubsumed2 a1s a []  = a : revConcat a1s []
dropSubsumed2 a1s a ar@(a2:a2s) = case pcompare a a2 of
PEQ - a : revConcat a1s a2s
PGT - a : revConcat a1s a2s
PLT - revConcat a1s ar
PNR - dropSubsumed2 (a2:a1s) a a2s
revConcat :: [a] - [a] - [a]
revConcat [] a2s = a2s
revConcat (a1:a1s) a2s = revConcat a1s (a1:a2s)
--  Perform subsumption calculation between a pair of tuples
--  A tuple with more information subsumes a one with less but
--  consistent information.
--
pcompare :: (Eq a) = [Maybe a] - [Maybe a] - PartOrdering
pcompare a1s a2s = pcompare1 a1s a2s PEQ
pcompare1 [][]po = po
pcompare1 (Just _:a1s)  (Nothing:a2s) po =
if (po == PEQ) || (po==PGT) then pcompare1 a1s a2s PGT else PNR
pcompare1 (Nothing:a1s) (Just _:a2s)  po =
if (po == PEQ) || (po==PLT) then pcompare1 a1s a2s PLT else PNR
pcompare1 (a1:a1s) (a2:a2s)   po =
if a1 == a2 then pcompare1 a1s a2s po else PNR
pcompare1 __  _  = PNR
testds1 = ds1a == ds1b
ds1a = dropSubsumed
[ [Just 'a',Just 'b',Just 'c']
, [Just 'a',Just 'b',Nothing ]
, [Just 'a',Nothing ,Just 'c']
, [Just 'a',Nothing ,Nothing ]
, [Nothing ,Just 'b',Just 'c']
, [Nothing ,Just 'b',Nothing ]
, [Nothing ,Nothing ,Just 'c']
, [Nothing ,Nothing ,Nothing ]
]
ds1b =
[ [Just 'a',Just 'b',Just 'c']
]
testds2 = ds2a == ds2b
ds2a = dropSubsumed
[ [Just 'a',Just 'b',Nothing ]
, [Just 'a',Nothing ,Just 'c']
, [Just 'a',Nothing ,Nothing ]
, [Nothing ,Just 'b',Just 'c']
, [Nothing ,Just 'b',Nothing ]
, [Nothing ,Nothing ,Just 'c']
, [Nothing ,Nothing ,Nothing ]
]
ds2b =
[ [Just 'a',Just 'b',Nothing ]
, [Just 'a',Nothing ,Just 'c']
, [Nothing ,Just 'b',Just 'c']
]
testds3 = ds3a == ds3b
ds3a = dropSubsumed
[ [Just a1,Just b1,Just c1]
, [Just a2,Just b2,Nothing  ]
, [Just a3,Nothing  ,Just c3]
, [Just a4,Nothing  ,Nothing  ]
, [Nothing  ,Just b5,Just c5]
, [Nothing  ,Just b6,Nothing  ]
, [Nothing  ,Nothing  ,Just c7]
, [Nothing  ,Nothing  ,Nothing  ]
]
ds3b =
[ [Just a1,Just b1,Just c1]
, [Just a2,Just b2,Nothing  ]
, [Just a3,Nothing  ,Just c3]
, [Just a4,Nothing  ,Nothing  ]
, [Nothing  ,Just b5,Just c5]
, [Nothing  ,Just b6,Nothing  ]
, [Nothing  ,Nothing  ,Just c7]
]
testds4 = ds4a == ds4b
ds4a = dropSubsumed
[ [Just 1, Just 1 ]
, [Just 2, Nothing]
, [Nothing,Just 3 ]
, [Nothing,Nothing]
]
ds4b =
[ [Just 1, Just 1 ]
, [Just 2, Nothing]
, [Nothing,Just 3 ]
]
-- Check handling of equal values
testds5 = ds5a == ds5b
ds5a = dropSubsumed
[ [Just 1, Just 1 ]
, [Just 2, Nothing]
, [Nothing,Just 3 ]
, [Nothing,Nothing]
, [Just 1, Just 1 ]
, [Just 2, Nothing]
, [Nothing,Just 3 ]
]
ds5b =
[ [Just 1, Just 1 ]
, [Just 2, Nothing]
, [Nothing,Just 3 ]
]
]]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Subsumption in partially ordered sets

2003-11-17 Thread Tom Pledger
Graham Klyne writes:
 :
 | Below is some code I have written, which works, but I'm not sure
 | that it's especially efficient or elegant.  Are there any published
 | Haskell libraries that contain something like this?

Hi.

Partially ordered sets are in cahoots with lattices, so you may be
interested in http://www.cse.ogi.edu/~mpj/pubs/lattices.html .

And here's some off-the-cuff feedback...

How about using Maybe Ordering, instead of a new data type?
(As in http://www.mail-archive.com/[EMAIL PROTECTED]/msg05635.html)

Instead of hard-wiring Maybe into the element type in dropSubsumed,
how about passing in a partial comparison function?

dropSubsumedBy :: (a - a - Maybe Ordering) - [a] - [a]

- Tom

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Subsumption in partially ordered sets

2003-11-17 Thread rvollmert-lists
 I have a need for an algorithm to perform subsumption on partially
 ordered sets of values. That is, given a selection of values from a
 partially ordered set, remove all values from the collection that
 are less than some other member of the collection.

That is, you want the maxima, right?

The following seems to work, though I don't know how efficient it is.

maxima :: (Eq a) = [[Maybe a]] - [[Maybe a]]
maxima es = maxima' [] es
where maxima' ms [] = ms
  maxima' ms (e:es) = maxima' (add ms e) es
  add [] e = [e]
  add (m:ms) e = case pcompare m e of PNR - m:(add ms e)
  PGT - m:ms
  PLT - add ms e
  PEQ - m:ms

Cheers
Robert
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


There is flexible exception handling in Haskell?

2003-11-17 Thread 7253146
Hi all. I am porting to Haskell a small zlib-based library for .zip files (I 
have not seen any released package for it, although it should very useful). The 
matters come when I try to address exceptional conditions: all the library 
functions return a integer code with OK/SOMEERROR meaning. The most natural way 
to carry the exceptional situations should be raise IO exceptions, but here 
comes the problem: how can I define new Exception codes, instead of raising 
userError all the time? I think it makes sense for a library to raise 
specialized exceptions, instead of userErrors.

There is such a mechanism? Can someone help?

Thanks.



-
Este mensaje lo ha enviado un Alumno de la Universidad de Malaga.
http://www.alumnos.uma.es/


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


There is flexible exception handling in Haskell?

2003-11-17 Thread 7253146
Hi all. I am porting to Haskell a small zlib-based library for .zip files (I 
have not seen any released package for it, although it should very useful). The 
matters come when I try to address exceptional conditions: all the library 
functions return a integer code with OK/SOMEERROR meaning. The most natural way 
to carry the exceptional situations should be raise IO exceptions, but here 
comes the problem: how can I define new Exception codes, instead of raising 
userError all the time? I think it makes sense for a library to raise 
specialized exceptions, instead of userErrors.

There is such a mechanism? Can someone help?

Thanks.



-
Este mensaje lo ha enviado un Alumno de la Universidad de Malaga.
http://www.alumnos.uma.es/


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: There is flexible exception handling in Haskell?

2003-11-17 Thread Bernard James POPE
 Hi all. I am porting to Haskell a small zlib-based library for .zip files (I 
 have not seen any released package for it, although it should very useful). The 
 matters come when I try to address exceptional conditions: all the library 
 functions return a integer code with OK/SOMEERROR meaning. The most natural way 
 to carry the exceptional situations should be raise IO exceptions, 

Sometimes you can just encode your exceptional values in some type. It tends to
be more declarative than throwing/catching exceptions:

   data Result = Ok Int | ThisError | ThatError String | SomeError Int ...

And you library functions can be:

   fun :: Foo - Bar - IO Result

drop the IO type if you don't need it.
  
 but here 
 comes the problem: how can I define new Exception codes, instead of raising 
 userError all the time? I think it makes sense for a library to raise 
 specialized exceptions, instead of userErrors.
 There is such a mechanism? Can someone help?

If the encoding doesn't somehow suit your needs then you could try GHC's 
exception extensions, which provide a much richer exception facility than
plain Haskell 98

Have a look at the module Control.Exception in the user docs. 

I think that very modern versions of Hugs support some of this extension too.

Cheers,
Bernie.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe