[Haskell-cafe] Re: Editors for Haskell

2006-05-31 Thread Thomas Hallgren

Brian Hulley wrote:



Another thing which causes difficulty is the use of qualified operators, 
and the fact that the qualification syntax is in the context free 
grammar instead of being kept in the lexical syntax (where I think it 
belongs).


You are in luck, because according to the Haskell 98 Report, qualified 
names are in the lexical syntax!


http://www.haskell.org/onlinereport/syntax-iso.html

So, C.f is a qualified name, but C . f is composition of the Constructor 
C with the function f.


--
Thomas H

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


[Haskell-cafe] Filtering on data constructors with TH

2006-05-31 Thread Christophe Poucet

Dear,

After having read Bulat's mail regarding TH when I had mentioned my wish 
for Pretty, I decided to use TH for a much smaller project. That's why 
today I have created an automated derivation for data constructor 
filtering. As I started coding someone mentioned that something similar 
can be done with list comprehensions, so I'm not certain about the scope 
of usefulness, however personally I have found the need for this at 
times. Anyways, the code can be obtained from the darcs repo at

http://oasis.yi.org:8080/repos/haskell/filter

Suggestions, bugs, additions are always welcome :)

Here is an example:

{-# OPTIONS_GHC -fglasgow-exts -fth #-}
module Main where

import Filter 


data T = A Int String | B Integer | C deriving Show

data Plop a b = Foo a | Bar b deriving Show

$(deriveFilter ''T)
$(deriveFilter ''Plop)

main :: IO ()
main = do
 let l = [A 1 "s", B 2, C] 
 let l2 = [Foo 1, Bar "a", Foo 2, Bar "b"]
 print l 
 print $ filter isA l

 print l2
 print $ filter isFoo l2


Cheers
Christophe ([EMAIL PROTECTED])

--
Christophe Poucet
Ph.D. Student
Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
Website: http://notvincenz.com/  
IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – www.imec.be

*DISCLAIMER*
This e-mail and/or its attachments may contain confidential information. It is 
intended solely for the intended addressee(s).
Any use of the information contained herein by other persons is prohibited. 
IMEC vzw does not accept any liability for the contents of this e-mail and/or 
its attachments.
**

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


Re: [Haskell-cafe] Tips for converting Prolog to typeclasses?

2006-05-31 Thread Robert Dockins
On Wednesday 31 May 2006 08:22 pm, Greg Buchholz wrote:
> Lately, in my quest to get a better understanding of the typeclass
> system, I've been writing my typeclass instance declarations in Prolog
> first, then when I've debugged them, I port them over back over to
> Haskell.  The porting process involves a lot trial and error on my part
> trying to decide when to use functional dependencies and which compiler
> extension to enable ( -fallow-undecidable-instances,
> -fallow-overlapping-instances, etc.).  Which might be okay, but I still
> can produce things that won't compile, and I don't necessarily know if
> I'm making a fundamental mistake in a program, or if there's something
> trivial that I'm not doing quite right.
>
> For example, there was a question on haskell-cafe last week about
> creating an "apply" function.  My first solution (
> http://www.haskell.org//pipermail/haskell-cafe/2006-May/015905.html )
> was to use type classes and nested tuples for the collection of
> arguments.  This works fine.  But then I wanted to try to get closer to
> what the original poster wanted, namely to use regular homogenous lists
> to store the arguments.  So I thought I could reuse the class definition
> and just provide new instances for a list type, instead of the nested
> tuple type.  Here's the class definition...
>
> > class Apply a b c | a b -> c where
> > apply :: a -> b -> c
>
> ...So I wrote the following Prolog snippets which seemed like they might
> properly describe the situation I was looking for...
>
> :- op(1000,xfy,=>).  % use => instead of -> for arrow type
>
> app(A=>B,[A],C) :- app(B,[A],C).
> app(C,[A],C).
>
> ...which I translated into the following Haskell instances...
>
> > instance Apply b [a] c => Apply (a->b) [a] c where
> > apply f [] = error "Not enough arguments"
> > apply f (x:xs) = apply (f x) xs
> > instance Apply c [a] c where
> > apply f _ = f


To make this work, you're going to have to convince the compiler to accept 
"overlapping instances" and then make sure they don't overlap :) In the 
second instance, what you really want to say is "instance c [a] c, only where 
c is not an application of (->)".  As I recall, there is a way to express 
such type equality/unequality using typeclasses, but I don't remember how to 
do it offhand.


A quick google turns up this page, which appears to address most of the 
questions at hand:

http://okmij.org/ftp/Haskell/types.html


> ...and here's a test program...
>
> > g :: Int -> Int -> Int -> Int -> Int
> > g w x y z = w*x + y*z
> >
> > main = do print $ apply g [1..]
>
> ...but I haven't been able to get GHC to accept this yet.  So I'm
> wondering if there's an easy route to learning this stuff.  Some sort of
> comprehensive tutorial out there which I should be reading that
> describes what should be possible with Haskell's typeclasses plus GHC
> extenstions, and when and where to enable these extentions.  (Bonus
> points awarded if it explains things in terms of Prolog).  Or is this
> just one of those things that requires reading lots of papers on each
> extentsion and possibly the source code of the implementation?
>
> Thanks,
>
> Greg Buchholz
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Tips for converting Prolog to typeclasses?

2006-05-31 Thread Greg Buchholz
Lately, in my quest to get a better understanding of the typeclass
system, I've been writing my typeclass instance declarations in Prolog
first, then when I've debugged them, I port them over back over to
Haskell.  The porting process involves a lot trial and error on my part
trying to decide when to use functional dependencies and which compiler
extension to enable ( -fallow-undecidable-instances,
-fallow-overlapping-instances, etc.).  Which might be okay, but I still
can produce things that won't compile, and I don't necessarily know if
I'm making a fundamental mistake in a program, or if there's something
trivial that I'm not doing quite right.

For example, there was a question on haskell-cafe last week about
creating an "apply" function.  My first solution (
http://www.haskell.org//pipermail/haskell-cafe/2006-May/015905.html )
was to use type classes and nested tuples for the collection of
arguments.  This works fine.  But then I wanted to try to get closer to
what the original poster wanted, namely to use regular homogenous lists
to store the arguments.  So I thought I could reuse the class definition
and just provide new instances for a list type, instead of the nested
tuple type.  Here's the class definition...

> class Apply a b c | a b -> c where
> apply :: a -> b -> c

...So I wrote the following Prolog snippets which seemed like they might
properly describe the situation I was looking for...

:- op(1000,xfy,=>).  % use => instead of -> for arrow type
app(A=>B,[A],C) :- app(B,[A],C).
app(C,[A],C).

...which I translated into the following Haskell instances...
>
> instance Apply b [a] c => Apply (a->b) [a] c where
> apply f [] = error "Not enough arguments"
> apply f (x:xs) = apply (f x) xs
> instance Apply c [a] c where
> apply f _ = f

...and here's a test program...

> g :: Int -> Int -> Int -> Int -> Int 
> g w x y z = w*x + y*z 
>
> main = do print $ apply g [1..]

...but I haven't been able to get GHC to accept this yet.  So I'm
wondering if there's an easy route to learning this stuff.  Some sort of
comprehensive tutorial out there which I should be reading that
describes what should be possible with Haskell's typeclasses plus GHC
extenstions, and when and where to enable these extentions.  (Bonus
points awarded if it explains things in terms of Prolog).  Or is this
just one of those things that requires reading lots of papers on each
extentsion and possibly the source code of the implementation?

Thanks,

Greg Buchholz

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


Re: [Haskell-cafe] Re[2]: [Haskell] My summer of code project: HsJudy

2006-05-31 Thread Benjamin Franksen
On Wednesday 31 May 2006 17:12, Bulat Ziganshin wrote:
> 6. There is no class framework for container types other than this
> Data.Collections module, 

Edison?

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


Re[2]: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Bulat Ziganshin
Hello Jacques,

Wednesday, May 31, 2006, 8:07:29 PM, you wrote:

> I am completely biased in this regard:  I have spent several years
> maintaining ~800Kloc of legacy dynamically typed [commercial] code. A
> lot of this code has a life-span of roughly 20 years [ie once written,
> it takes an average of 20 years before it gets re-written].  That 
> experience has converted me to a static-type fan, as well as a fan of 
> designs that are for the "long term"; short-term convenience is 
> something that is great for short-lived code (< 5 years is short-lived
> to me ;-) ). 

my own programming experience say the same - strict typing
significantly simplify program writing by ensuring it's correctness. and
Haskell catch many problems as early as i compile code. but in this
case we will add more complexity for standard use of functions (when
just Ptr required) without any improvements in reliability just to
catch potential problems with unusual usage. moreover, there are also
encode/encodeLE/... functions that produce String - they also don't
need any special String types

why i include encoding type in function name? just to simplify usage,
all the 'encodePtr*' functions can be expressed via one encodePtrWith,
but i don't think that many peoples want to write this himself:

encodePtr   = encodePtrWith put_
encodePtrLE = encodePtrLEWith   put_
encodePtrBitAligned = encodePtrBitAlignedWith   put_
encodePtrBitAlignedLE   = encodePtrBitAlignedLEWith put_

encodePtrLEWith   write = encodePtrWith (\s a-> withByteAlignedLE s 
(`write` a))
encodePtrBitAlignedWith   write = encodePtrWith (\s a-> withBitAligneds 
(`write` a))
encodePtrBitAlignedLEWith write = encodePtrWith (\s a-> withBitAlignedLE  s 
(`write` a))


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Editors for Haskell

2006-05-31 Thread Brian Hulley

Doaitse Swierstra wrote:

On 2006 mei 30, at 17:33, Brian Hulley wrote:


But the buffer will nearly always be incomplete as you're editing it.

I was kind of hoping that the syntax of Haskell could be changed so
that for
any sequence of characters there would be a unique parse that had a
minimum
number of "gaps" inserted by the editor to create a complete parse
tree, and
moreover that this parse could be found by deterministic LL1
recursive descent.


If you use my parsercombinators, and are willing to work on the
grammar I think this can in principle be done. The combinators
automatically "correct" incorrect (i.e. in this case incomplete)
input, but:
 - you may really need some time to tune the grammar so the
corrections are what a user might expect (there are many hooks for
doing so, but it will takje some effort, since this s also a human
interface issue)
 - making a Haskell grammar that parsers top-down is not an easy
task, and making it LL1 is definitely impossible, but also not needed
if you use my combinators

[rearranged]

Not only the =>, but e.g. the commonality between patterns and
expressions makes left factorisation a not so simple task.


My idea was to use a coarse grammar for parsing, rather than H98 directly, 
so that the parser could "see" common errors like


  newtype T a = T a a -- only one value may be wrapped by a newtype

The coarse grammar can be LL1.
The purpose of using LL1 is to ensure that the fontification would remain 
stable whenever the user types text from left to right ie gaps get filled in 
rather than the parser deciding on wildly different parses. (Just as type 
inference has to be predictable enough for users to get a feeling for so 
does parsing I think.)
As John pointed out, code can be edited by going back and forward filling in 
gaps but in this case there is no issue of stability to worry about.


I'm also not at all keen on using higher levels of analysis (such as knowing 
whether SomeId referes to a tycon or class name) to drive the parsing. I'm 
really wanting something quite simple so that the editor doesn't become so 
"clever" that it becomes unpredictable and annoying.



 - we could in principle provide you with a complete parser for
Haskell using our combinators that was tested by replacing the GHC
parser with this parser, and that worked (contact [EMAIL PROTECTED] to
get a copy of his code)


Thanks for the pointer - I'll keep this possibility in mind.


 - did you think about how to handle the offside rule? If not, the
good news is that we have combinators for that too.



In my C implementation it turned out to be quite simple to handle, but also 
was something which prevented me from using a table-based approach (although 
at the time I'd only understood the rule as inserting an implicit } whenever 
the parse would otherwise get stuck).


The needs of incremental parsing also force some changes to Haskell syntax. 
For example, currently the layout rule is switched off by an opening {, but 
this is no use if you need to maintain invariants about the structure of the 
buffer eg that you can search back and forwards for the beginning of top 
level declarations by examining the leftmost column (a simpler solution 
would have been to use a symbol such as {} at the top of a module to 
indicate that the module as a whole doesn't use layout at all). Also, 
multi-line strings (being multi-line lexemes) are a real nusiance as well, 
and I don't think they look good in any case (unlines can always be used 
instead and looks much neater imho) - so probably in the first instance at 
least I won't bother trying to support these little-used quirks and with any 
luck they'll be killed off in future versions of Haskell... ;-)


Anyway, thanks (also to everyone else who replied) - there's lots of ideas 
for me to consider,


Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


[Haskell-cafe] Polymorphic Sudoku solver

2006-05-31 Thread Chris Kuklewicz
A while back there was a long thread about Sudoku solvers (some of which ended
up on http://haskell.org/haskellwiki/Sudoku ).  I contributed my brute-force
dancing links solver at the time, and mentioned that I had a by-logic solver
that, while a bit slow, was as good as most of those being discussed.

At the time the code for my solver was too ugly to post.  Attached is a cleaned
up version.

I have gone back and rewritten it, and come to the conclusion: There are only
two deduction algorithms: "subsets" and "blocks".  These subsume the other types
of propagation and deduction.  So I made this version as a "minimalist" example
instead of going for performance.

The "subsets" algorithm can be applied to all 6 permutations of row column and
value, as well as 1 special case of value and block indices.

The "blocks" algorithm can be applied 4 ways (in two flavors and to either
permutation of row/column or column/row).

There are newtypes for row, column, value, block index, and sub-block index.

The state is held in an array of type DiffArray (R,C,V) Bool

The actual computation is a series of concat/map/filter/group/sort
operations on the assocs's of the array.

The choice of which permutation is handled by leaning on the type system to
reify the type into appropriate view,shuffle, and unshuffle functions.

It should solve exactly the same number of puzzles as my older version, where "I
sent the 36628 line sudoku17 puzzle through it and it could solve 31322 of the
puzzles, leaving 5306 resistant."

-- 
Chris Kuklewicz


module Main (main) where

import Data.Ix(inRange,range)
import Data.Char(intToDigit,digitToInt)
import Deduce(deduce,lo,hi)

loC = intToDigit lo
hiC = intToDigit hi
unsetC = pred loC

main = do
  all <- getContents
  let puzzles = zip [1..] (map parseBoard (lines all))
  act (i,p) = do p' <- deduce p
 return (i,length p,length p')
  mapM_ (\ip -> act ip >>= print) puzzles
  
parseBoard :: String -> [(Int,Int,Int)]
parseBoard s = map toHint justSet
  where rcs = [ (r,c) | r <- range (lo,hi), c <- range (lo,hi) ]
isHint vC = inRange (loC,hiC) vC
justSet = filter (isHint . snd) (zip rcs s)
toHint ((r,c),vC) = (r,c,digitToInt vC)

{- By Chris Kuklewicz <[EMAIL PROTECTED]> -}

module Deduce (deduce,lo,hi) where

{- The exposed function deduce takes a list of (row,column,value)
   tuples that are the known parts of the solutions and returns a
   (hopefully longer) list in the same format.  The indices can be any
   enumerated type in the range (lo,hi).
-}

import Data.Array.Diff 
(assocs,(!),(//),ixmap,range,inRange,accumArray,DiffArray,Ix)
import Data.List(sortBy,groupBy,transpose,(\\))
import Control.Monad(liftM,guard)

default ()

-- Typesafe values for indices
-- This machinery allows for more type safety than if R,C,V,B,D were all Int or 
Char

type E = Int
newtype R = R E deriving (Eq,Ord,Ix,Enum,Show) -- Row index
newtype C = C E deriving (Eq,Ord,Ix,Enum,Show) -- Column index
newtype V = V E deriving (Eq,Ord,Ix,Enum,Show) -- Value index
newtype B = B E deriving (Eq,Ord,Ix,Enum,Show) -- 3x3 Block index
newtype D = D E deriving (Eq,Ord,Ix,Enum,Show) -- Inside 3x3 Block index

lo,hi :: (Enum a) => a
lo = toEnum 1
hi = toEnum 9

fullRange :: (Enum a,Ix a) => [a]
fullRange = range (lo,hi)

rcToBD (R r) (C c) = let (rq,rm) = quotRem (r-lo) 3
 (cq,cm) = quotRem (c-lo) 3
 b = lo + ( 3*rq + cq )
 d = lo + ( 3*rm + cm )
 in (B b, D d)

bdToRC (B b) (D d) = let (bq,bm) = quotRem (b-lo) 3
 (dq,dm) = quotRem (d-lo) 3
 r = lo + ( 3*bq + dq )
 c = lo + ( 3*bm + dm )
 in (R r, C c)

-- Typeclasses and Data for "shuffle" and "unshuffle"

class (Show x, Ix x, Enum x, Ord x) => IE x
instance IE R; instance IE C; instance IE V; instance IE B; instance IE D

data Perms a b c = Perms { shuffle'   :: (R,C,V) -> (a,b,c)
 , unshuffle' :: (a,b,c) -> (R,C,V) }

-- Reify the types "a b c" to a value of type Perms
class (IE a, IE b, IE c) => Perm a b c where perm :: Perms a b c
instance Perm R C V where perm = Perms id id
instance Perm R V C where perm = Perms (\ (r,c,v) -> (r,v,c)) (\ (r,v,c) -> 
(r,c,v))
instance Perm C V R where perm = Perms (\ (r,c,v) -> (c,v,r)) (\ (c,v,r) -> 
(r,c,v))
instance Perm C R V where perm = Perms (\ (r,c,v) -> (c,r,v)) (\ (c,r,v) -> 
(r,c,v))
instance Perm V R C where perm = Perms (\ (r,c,v) -> (v,r,c)) (\ (v,r,c) -> 
(r,c,v))
instance Perm V C R where perm = Perms (\ (r,c,v) -> (v,c,r)) (\ (v,c,r) -> 
(r,c,v))
-- Special cases
instance Perm B D V where perm = Perms (\ (r,c,v) -> let (b,d) = rcToBD r c in 
(b,d,v))
   (\ (b,d,v) -> let (r,c) = bdToRC b d in 
(r,c,v))
instance Perm V B D where perm = Perms (\ (r,c,v) -> let (b,d) = rcToBD r c in 
(v,b,d))
   (\ (

Re: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Jacques Carette

Bulat Ziganshin wrote:

i'm not against your idea, you absolutely right that this will be more
Haskell way, but can this be implemented without additional
complications for library users?
  
C is a language which pushes the boundaries of "no complications" (ie 
convenience) quite far (and yet claims to have types).  The beauty of 
Haskell is that you are forced to think before you lay down some code, 
to make sure what you write really is meaningful.


A Haskell API for a library /can/ likewise force its users to think 
about what they really need to do before they lay down some code.  Yes, 
that makes the use more complicated.  Convenience is a short-term gain, 
and going from 'convenient' languages (think Perl and Python here) to 
Haskell is quite the shock!  But think of the long-term gains of doing 
it correctly / the Haskell way.


I am completely biased in this regard:  I have spent several years 
maintaining ~800Kloc of legacy dynamically typed [commercial] code.  A 
lot of this code has a life-span of roughly 20 years [ie once written, 
it takes an average of 20 years before it gets re-written].  That 
experience has converted me to a static-type fan, as well as a fan of 
designs that are for the "long term"; short-term convenience is 
something that is great for short-lived code (< 5 years is short-lived 
to me ;-) ). 

I think the choice really boils down to the expected life-span of your 
library, as well as the expected size of the user base. 


Jacques (stepping off my soap-box now...)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Jacques Carette
I have no problems with marshalling/unmarshalling (and even with the 
implicit casting going on).  What I dislike is having a bunch of 
functions which are "the same" but with different names, where the 
difference boils down to enumerated types that end up being encoded in 
the function name.  Regardless of type safety.


Jacques

Tim Newsham wrote:
Am I the only one who finds this encoding-of-types in the _name_ of a 
function quite distateful?  There is no type safety being enforced 
here, no ensuring one will not be encoding a Ptr one way and decoding 
it another.  Why not use Haskell's type system to help you there?


When marshalling data you often don't want any type safety.  You often 
want to explicitely linearize data from one type and then unlinearize 
it into another type.  The net result is that of casting.  In fact, 
you can write a marshalling library with an interface based entirely 
on this concept:


http://www.lava.net/~newsham/x/Pkts5.lhs

The interface is, in essense, a glorified casting mechanism.  To 
marshall data you convert it to an array of bytes and to unmarshall 
data you unconvert it.



Jacques


Tim Newsham
http://www.lava.net/~newsham/

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


Re: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Tim Newsham
Am I the only one who finds this encoding-of-types in the _name_ of a 
function quite distateful?  There is no type safety being enforced here, no 
ensuring one will not be encoding a Ptr one way and decoding it another.  Why 
not use Haskell's type system to help you there?


When marshalling data you often don't want any type safety.  You often 
want to explicitely linearize data from one type and then unlinearize it 
into another type.  The net result is that of casting.  In fact, you can 
write a marshalling library with an interface based entirely on this 
concept:


http://www.lava.net/~newsham/x/Pkts5.lhs

The interface is, in essense, a glorified casting mechanism.  To marshall 
data you convert it to an array of bytes and to unmarshall data you 
unconvert it.



Jacques


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


[Haskell-cafe] Re[2]: [Haskell] My summer of code project: HsJudy

2006-05-31 Thread Bulat Ziganshin
(moved to haskell-cafe)

Hello Jean-Philippe,

Tuesday, May 30, 2006, 2:58:01 PM, you wrote:

>> you should also see to the Collections package:
>> darcs get --partial http://darcs.haskell.org/packages/collections/
>> although it contains only _immutable_ datastructures at this
>> moment. may be, you can codevelop with Bernardy interface for mutable
>> maps/sets

> I'm not sure there is significant overlap between what we're doing.
> I'd be delighted to cooperate if you think this is possible though.

well, what i think: while all the actual work will be performed by
Caio himself, we can help him (and to ourselves as possible future
users of this lib) by describing infrastructure in that he need to
insert his work and pointing to "adjancent" projects

so, Caio, now i write for you, better organizing my previous post:

1. In terms of Haskell, Judy is a library of _mutable_ collections of
_unboxed_ elements. i pointed you to the Array wiki page, where
differences between boxed and unboxed, mutable and immutable
datastructures are described

2. Collections is a library of _immutable_ datastructures, and
Jean-Philippe especially omitted any support for mutable
datastructures - because it's the whole story of it's own. So, you
don't need to write your work as part of the Collections library

3. Nevertheless, Collections has GREAT organization and it will be
very helpful to study it. in particular, see at the Data.Collections
module, what describes various classes into which all collections are
fitted, and hierarchy between them

4. Next, when you will search for the datatypes/classes whose
interface you can imitate, you will find only Data.HashTable - other
datatypes in standard libraries are either immutable (say, Map) or
need contiguous indexes (say, MArray). So you will need to create your
own interface and here you can borrow from the Collections lib. Just
see at the differences between IArray and MArray classes. They are
very close, only MArray class update arrays on-the-place and has
additional 'Monad m' on all it's return types. say,

class IArray a e where
  unsafeAt :: (Index i) => a i e -> i -> e

becomes

class MArray a e m where
  unsafeRead :: (Index i) => a i e -> i -> m e

You can do the same with Collections classes. instead of reinventing
the wheel, you can add letter 'M' to it :)

say,

class Monoid c => Map c k a | c -> k a where
insert :: k -> a -> c -> c
delete :: k -> c -> c
member :: k -> c -> Bool

would become

class (Monoid c, Monad m) => MapM c k a | c -> k a where
insertM :: k -> a -> c -> m ()
deleteM :: k -> c -> m ()
memberM :: k -> c -> m Bool


5. as i already said, then you should use StablePtr and any form of
hashing/seriazliation in order to map between boxed (Haskell) and
unboxed (C) values. and then you can develop series of Diff
transformers what emulates immutable collections via mutable ones (say
interface of class Map via the interface of class MapM), DiffArray can
serve as template here

6. There is no class framework for container types other than this
Data.Collections module, so implementing it's close imitation (with
monadic operations) will help future users to easily learn and use
both interfaces

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Bulat Ziganshin
Hello Jacques,

Wednesday, May 31, 2006, 5:33:39 PM, you wrote:

>> encodePtr :: (Binary a, Integral size) =>  a -> IO (ForeignPtr 
>> x, size)
>> encodePtrLE   :: (Binary a, Integral size) =>  a -> IO (ForeignPtr 
>> x, size)
>> encodePtrBitAligned   :: (Binary a, Integral size) =>  a -> IO (ForeignPtr 
>> x, size)
>> encodePtrBitAlignedLE :: (Binary a, Integral size) =>  a -> IO (ForeignPtr 
>> x, size)
>>
> Am I the only one who finds this encoding-of-types in the _name_ of a 
> function quite distateful?  There is no type safety being enforced here,
> no ensuring one will not be encoding a Ptr one way and decoding it 
> another.  Why not use Haskell's type system to help you there?

i misunderatood you when i wrote previous message. now that i can say:

you are right. but on practice this means more text typing and
coercion. especially when we go to ForeignPtrs. moreover, in most
cases, imho, data encoded by 'encodePtr*', will go to the FFI
libraries, so we can't use typechecking anyway

i'm not against your idea, you absolutely right that this will be more
Haskell way, but can this be implemented without additional
complications for library users?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Jacques Carette

You would need to define a type class
(Binary a) => EncodedPtr a b
where the 'a' is as you have it currently, and the b would be an 
enumerated type which tracks the memory representation.


I agree they are different concepts - that is why an EncodedPtr would 
require 2 type parameters.  Of course, this class would define 
encode/decode functions, but without the need for the name encoding (and 
additional safety).


Jacques

Bulat Ziganshin wrote:

Hello Jacques,

Wednesday, May 31, 2006, 5:33:39 PM, you wrote:

  

decodePtrBitAlignedLE :: (Binary a, Integral size) =>  Ptr x -> size -> IO a

  
Am I the only one who finds this encoding-of-types in the _name_ of a 
function quite distateful?  There is no type safety being enforced here,



can you please write code you suggested? i'm not sure that type "a"
should be encoded only to area pointed by "Ptr a" - binary encoding of
value and it's memory representation are different concepts, although
they are similar at the look


  

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


Re[2]: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Bulat Ziganshin
Hello Jacques,

Wednesday, May 31, 2006, 5:33:39 PM, you wrote:

>> decodePtrBitAlignedLE :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
>>
> Am I the only one who finds this encoding-of-types in the _name_ of a 
> function quite distateful?  There is no type safety being enforced here,

can you please write code you suggested? i'm not sure that type "a"
should be encoded only to area pointed by "Ptr a" - binary encoding of
value and it's memory representation are different concepts, although
they are similar at the look


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Jacques Carette

[See comments at bottom]

Bulat Ziganshin wrote:

Finally i've implemented the following (you then would use
'withForeignPtr' to work with contents of ForeignPtr):

-- -
-- Encode/decode contents of memory buffer

encodePtr :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtrLE   :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtrBitAligned   :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtrBitAlignedLE :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtr = encodePtr' openByteAligned
encodePtrLE   = encodePtr' openByteAlignedLE
encodePtrBitAligned   = encodePtr' openBitAligned
encodePtrBitAlignedLE = encodePtr' openBitAlignedLE

decodePtr :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
decodePtrLE   :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
decodePtrBitAligned   :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
decodePtrBitAlignedLE :: (Binary a, Integral size) =>  Ptr x -> size -> IO a

decodePtr = decodePtr' openByteAligned
decodePtrLE   = decodePtr' openByteAlignedLE
decodePtrBitAligned   = decodePtr' openBitAligned
decodePtrBitAlignedLE = decodePtr' openBitAlignedLE
  
Am I the only one who finds this encoding-of-types in the _name_ of a 
function quite distateful?  There is no type safety being enforced here, 
no ensuring one will not be encoding a Ptr one way and decoding it 
another.  Why not use Haskell's type system to help you there?


One could imagine putting encodePtr' and decodePtr' in a type class for 
example?  Or many other solutions. 

This is not meant to be a general critique of this habit of encoding 
types into function names, not of the particular instance above.  My 
interest in starting this thread is to discuss the solutions that work, 
and the situations where no solution currently seems to exist.


I believe there may be instances of encoding-types-in-names that are 
currently necessary in Haskell because the type system is not powerful 
enough to do anything else.  Using Typeable and a type-witness just 
moves the problem, it does not ``solve'' it.


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


Re[5]: [Haskell-cafe] Re: [Haskell] installing streams library

2006-05-31 Thread Bulat Ziganshin
Hello Bulat,

Sunday, May 28, 2006, 2:44:37 PM, you wrote:

>> type PtrLen a = (Ptr a, Int)
>> encodePtrLen :: (Binary a) => a -> (PtrLen a -> IO b) -> IO b
>> decodePtr :: (Binary a) => Ptr a -> IO a

Finally i've implemented the following (you then would use
'withForeignPtr' to work with contents of ForeignPtr):

-- -
-- Encode/decode contents of memory buffer

encodePtr :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtrLE   :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtrBitAligned   :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtrBitAlignedLE :: (Binary a, Integral size) =>  a -> IO (ForeignPtr x, 
size)
encodePtr = encodePtr' openByteAligned
encodePtrLE   = encodePtr' openByteAlignedLE
encodePtrBitAligned   = encodePtr' openBitAligned
encodePtrBitAlignedLE = encodePtr' openBitAlignedLE

decodePtr :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
decodePtrLE   :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
decodePtrBitAligned   :: (Binary a, Integral size) =>  Ptr x -> size -> IO a
decodePtrBitAlignedLE :: (Binary a, Integral size) =>  Ptr x -> size -> IO a

decodePtr = decodePtr' openByteAligned
decodePtrLE   = decodePtr' openByteAlignedLE
decodePtrBitAligned   = decodePtr' openBitAligned
decodePtrBitAlignedLE = decodePtr' openBitAlignedLE

-- Universal function what encodes data with any alignment
encodePtr' open thedata = do
h <- createMemBuf 512 >>= open
put_ h thedata
vFlush h
vRewind h
(buf,size) <- vReceiveBuf h READING -- FIXME: 
MemBuf-implementation specific
fptr <- newForeignPtr finalizerFree (castPtr buf)   -- FIXME: also 
MemBuf-implementation specific
return (fptr,size)

-- Universal function what decodes data written with any alignment
decodePtr' open ptr size = do
h <- openMemBuf ptr size >>= open
result <- get h
vClose h
return result



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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