[Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread Casey Hawthorne
How does one delare a 2D STUArray in Haskell?

I see the following from a diffusion program segment:



module Diffusion where

import Data.Array
import Data.List (sortBy)

type VFieldElem = Float
type VField = Array (Int,Int) VFieldElem

snip

zeros = listArray ((1,1),(imax,jmax)) (repeat 0)



From Real World Haskell to declare a 1D array (I changed some of the
value names) there is the following:

import Data.Array.ST (STUArray)
import Data.Array.Unboxed (UArray)
import Data.Word (Word32)


data PlayingField1D a = PF1D {
pf1DState  :: (a - [Word32])
, pf1DArray :: UArray Word32 Bool
}


data MutPlayingField1D s a = MPF1D {
  mpf1DState :: (a - [Word32])
, mutpf1DArray :: STUArray s Word32 Bool
}


But I cannot see how to declare a 2D array.

Although, it is not strictly necessary, pun intended, since one can
reframe the 1D array as 2D array by using row/column mapping
functions.




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


Re: [Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread minh thu
2009/9/25 Casey Hawthorne cas...@istar.ca:
 How does one delare a 2D STUArray in Haskell?

Hi,

STUArray, like other arrays is parametrized by the type of the index,
the i in STUArray s i e [1]. That i is should be an instance of
Ix which is a class of the types that can be used as indices. If you
want to use 2D indices, that's fine as pairs (of types that are
themselves in Ix) are instances of Ix.

In your code, (Int,Int) (2d) and Word32 (1d) are the indice types. So

STUArray s (Word32,Word32) Bool

would be the 2d version of an array indiced by Word32 (that is, an
array indiced by pairs of Word32).

Cheers,
Thu

[1] 
http://hackage.haskell.org/packages/archive/array/0.2.0.0/doc/html/Data-Array-ST.html#t%3ASTUArray
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread Casey Hawthorne
Well that makes sense, but for a learner, how is he/she supposed to
know that 'i' could be '(i,i)' or for that matter a tuple of n of
those i's?

STUArray s i e

Could you also have a tuple of states?

Obviosly, 'e' could be a tuple, for instance  (Int,Char)

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


Re: [Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread minh thu
2009/9/25 Casey Hawthorne cas...@istar.ca:
 Well that makes sense, but for a learner, how is he/she supposed to
 know that 'i' could be '(i,i)' or for that matter a tuple of n of
 those i's?

 STUArray s i e

 Could you also have a tuple of states?

 Obviosly, 'e' could be a tuple, for instance  (Int,Char)

Well, 'i' is just a type variable, just like 'a' and 'b' are type
variables in the function type

map :: (a - b) - [a] - [b]

I guess you know that you can map a suitable function on a list of
pairs, right ?

Type variable mean you can use whatever type you want, including
pairs, lists, or whatever.

So you can have list of whaterver you want, and use whatever you want
as indices in arrays BUT!

But the whatever you want can be constrained a bit: here, the
constraint is that the type of the indices must be in Ix, this is what
the Ix i = means.

For instance, we said we can put whatever you want in a list. But ask
GHCi what is the type of

inc = map (+1) :

Prelude :t map (+1)
map (+1) :: (Num a) = [a] - [a]

You see that you can use inc on list of whatever you want (the a)
*provided* the a is in Num, the Num a = part of the type
signature.

Now, you have to look if the type you want to use for your indices is in Ix.
Look at [1] and you see that

(Ix a, Ix b) = Ix ((,) a b)

is an Instance of Ix.

(The right part can be read as (a,b) instead of (,) a b).

So a pair is in Ix provided its elements are in Ix too.

[1] 
http://hackage.haskell.org/packages/archive/base/4.0.0.0/doc/html/GHC-Arr.html#t%3AIx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread minh thu
2009/9/25 minh thu not...@gmail.com:
 2009/9/25 Casey Hawthorne cas...@istar.ca:
 Well that makes sense, but for a learner, how is he/she supposed to
 know that 'i' could be '(i,i)' or for that matter a tuple of n of
 those i's?

 STUArray s i e

 Could you also have a tuple of states?

 Obviosly, 'e' could be a tuple, for instance  (Int,Char)

 Well, 'i' is just a type variable, just like 'a' and 'b' are type
 variables in the function type

 map :: (a - b) - [a] - [b]

 I guess you know that you can map a suitable function on a list of
 pairs, right ?

 Type variable mean you can use whatever type you want, including
 pairs, lists, or whatever.

 So you can have list of whaterver you want, and use whatever you want
 as indices in arrays BUT!

 But the whatever you want can be constrained a bit: here, the
 constraint is that the type of the indices must be in Ix, this is what
 the Ix i = means.

 For instance, we said we can put whatever you want in a list. But ask
 GHCi what is the type of

 inc = map (+1) :

 Prelude :t map (+1)
 map (+1) :: (Num a) = [a] - [a]

 You see that you can use inc on list of whatever you want (the a)
 *provided* the a is in Num, the Num a = part of the type
 signature.

 Now, you have to look if the type you want to use for your indices is in Ix.
 Look at [1] and you see that

 (Ix a, Ix b) = Ix ((,) a b)

 is an Instance of Ix.

 (The right part can be read as (a,b) instead of (,) a b).

 So a pair is in Ix provided its elements are in Ix too.

 [1] 
 http://hackage.haskell.org/packages/archive/base/4.0.0.0/doc/html/GHC-Arr.html#t%3AIx


Forget to say this:

You don't have a pair of indices or a pair of states: you have an
index which is a pair, and you can have a state which is a pair.

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


RE: [Haskell-cafe] Haddock and literate Haskell: annotations must bemarked as source?

2009-09-25 Thread Bayley, Alistair
 From: haskell-cafe-boun...@haskell.org 
 [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Andy Gimblett
 Sent: 24 September 2009 20:19
 
 On 24 Sep 2009, at 20:10, Duncan Coutts wrote:
 
  On Thu, 2009-09-24 at 19:48 +0100, Andy Gimblett wrote:
 
  That's great news for me, except: that's what I tried 
 first, and I've
  just tried it again and it still doesn't seem to work for me.   
  Perhaps
  I am doing something wrong...?
 
  You're quite right, it got broken with the move to haddock2. The  
  code in
  Cabal-1.6 skips the pre-processing when using haddock2, assuming  
  haddock
  will handle it. In the current Cabal development version it works
  properly and I get the right output for your example.
 
 Ah, righto.  In that case, I won't shy away from LHS, and I'll be  
 patient for the next Cabal release, or maybe even check out the  
 development version.  :-)


Doh. I forgot that little detail. You need cabal  1.6.0.2, which unfortunately 
is the last released version. The current development one should do it (very 
easy to install with cabal :-).

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

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


Re: [Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread Daniel Fischer
Am Freitag 25 September 2009 09:22:25 schrieb Casey Hawthorne:
 Well that makes sense, but for a learner, how is he/she supposed to
 know that 'i' could be '(i,i)' or for that matter a tuple of n of
 those i's?

minh thu already explained this very well.


 STUArray s i e

 Could you also have a tuple of states?

You can't choose the state 's', the documentation says
The strict state-transformer monad. A computation of type ST s a transforms an 
internal 
state indexed by s, and returns a value of type a. The s parameter is either

* an uninstantiated type variable (inside invocations of runST), or
* RealWorld (inside invocations of Control.Monad.ST.stToIO). 

Without evil hackery (or stToIO), you can only use ST actions/ST(U)Arrays via

runST :: (forall s. ST s a) - a

or

runST(U)Array :: Ix i = (forall s. ST s (ST(U)Array s i e)) - (U)Array i e

which have rank 2 types (universally qualified type as type of argument 
[result]),
the 'forall s' within the parentheses says it has to work whatever type the rts 
chooses 
(actually none), so if you write

myFancyArray :: forall s1, s2. ST (s1,s2) (STUArray (s1,s2) Int Int)

you can't use it.


 Obviosly, 'e' could be a tuple, for instance  (Int,Char)

Not for STUArrays, but for STArrays, there's no problem.


 --
 Regards,
 Casey

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


Re[2]: [Haskell-cafe] How does one delare a 2D STUArray in Haskell?

2009-09-25 Thread Bulat Ziganshin
Hello Casey,

Friday, September 25, 2009, 11:22:25 AM, you wrote:

 Well that makes sense, but for a learner, how is he/she supposed to
 know that 'i' could be '(i,i)' or for that matter a tuple of n of
 those i's?

look at Ix class instances: 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-Arr.html#v%3ArangeSize



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Proof in Haskell

2009-09-25 Thread pat browne
Hi,
Below is a function that returns a mirror of a tree, originally from:

http://www.nijoruj.org/~as/2009/04/20/A-little-fun.html

where it was used to demonstrate the use of Haskabelle(1) which converts
Haskell programs to the Isabelle theorem prover. Isabelle was used to
show that the Haskell implementation of mirror is a model for the axiom:

 mirror (mirror x) = x

My question is this:
Is there any way to achieve such a proof in Haskell itself?
GHC appears to reject equations such has
mirror (mirror x) = x
mirror (mirror(Node x y z)) = Node x y z


Regards,
Pat


=CODE=
module BTree where

data Tree a = Tip
| Node (Tree a) a (Tree a)

mirror ::  Tree a - Tree a
mirror (Node x y z) = Node (mirror z) y (mirror x)
mirror Tip = Tip

(1)Thanks to John Ramsdell for the link to Haskabelle:
http://www.cl.cam.ac.uk/research/hvg/Isabelle/haskabelle.html).

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


Re: [Haskell-cafe] Proof in Haskell

2009-09-25 Thread Eugene Kirpichov
It is not possible at the value level, because Haskell does not
support dependent types and thus cannot express the type of the
proposition forall a . forall x:Tree a, mirror (mirror x) = x, and
therefore a proof term also cannot be constructed.

However, if you manage to express those trees at type level, probably
with typeclasses and type families, you might have some success.

2009/9/25 pat browne patrick.bro...@comp.dit.ie:
 Hi,
 Below is a function that returns a mirror of a tree, originally from:

 http://www.nijoruj.org/~as/2009/04/20/A-little-fun.html

 where it was used to demonstrate the use of Haskabelle(1) which converts
 Haskell programs to the Isabelle theorem prover. Isabelle was used to
 show that the Haskell implementation of mirror is a model for the axiom:

  mirror (mirror x) = x

 My question is this:
 Is there any way to achieve such a proof in Haskell itself?
 GHC appears to reject equations such has
 mirror (mirror x) = x
 mirror (mirror(Node x y z)) = Node x y z


 Regards,
 Pat


 =CODE=
 module BTree where

 data Tree a = Tip
            | Node (Tree a) a (Tree a)

 mirror ::  Tree a - Tree a
 mirror (Node x y z) = Node (mirror z) y (mirror x)
 mirror Tip = Tip

 (1)Thanks to John Ramsdell for the link to Haskabelle:
 http://www.cl.cam.ac.uk/research/hvg/Isabelle/haskabelle.html).

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




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Peter Verswyvelen
Haskell's records are a bit annoying, and type-classes often group together
too many methods, which means you make early decisions about future unknown
requirements, and IMO you always get it wrong :-)
After having read an email in the cafe about the Noop language  Self
language, I realized that what I really would like to have is strong duck
typing on records (or is it called structural subtyping? or
prototype-based-objects? or something like that)
For example (silly example full of inaccuracies, but you get the picture):

class HasPosition a where
  position :: a - Point
  withPosition :: Point - a - a

class HasVelocity a where
  velocity :: a - Vector
  withVelocity :: Vector - a - a

which we really should write as

field HasPosition :: Point
field HasVelocity :: Vector

And then

record IsKinetic :: HasPosition HasVelocity

suppose we write a function like

kineticEulerStep dt k = withPosition (position k .+^ dt *^ velocity k) k

kineticEulerStep will work on any type a that HasPosition and HasVelocity,
and would get inferred signature

kineticEulerStep :: IsKinetic a = Float - a - a

which is identical to

kineticEulerStep :: (HasPosition a, HasVelocity a) = Float - a - a

So basically kineticEulerStep accepts anything that HasPosition and
HasVelocity, whatever it is.

So if it walks like a duck and ..., then it is a duck, but statically
known...

We could also do

field HasForce :: Vector
field HasMass :: Float

record IsDynamic :: IsKinetic HasForce HasMass

acceleration d = force d ^/ mass d
withAcceleration a d = withForce (a ^* mass d) d

dynamicEulerStep dt d = withVelocity (velocity d ^+^ dt *^ acceleration d)

Of course you would also need type families to be really correct since
Vector, Point, etc should also be parametrized.

And really kineticEulerStep might also work on something that HasVelocity
and HasAcceleration (since the code in dynamicEulerStep is almost the same
as kineticEulerStep), so better abstraction might be needed.

I'm not sure what kind of overhead a system like this would have in Haskell,
since I suspect the many dictionaries are often not optimized away.

I think for Haskell prime, something like this was
suggestedhttp://repetae.net/recent/out/classalias.html,
but is was rejected?

Languages like OCaml and haXe http://haxe.org/manual/2_types also provide
a similar feature?

I would like to collect ways of doing this in Haskell, without boilerplate,
and preferably without runtime overhead.

I remember reading OOHaskell a while time ago, and while I didn't understand
a lot of it, I recall it also was doing a similar thing, but since the
compiler lacks native support, the error messages you get most likely make
it impossible to figure out what is going wrong. I think Grapefruit's
Records, HList, Data.Accessor, etc.. might also work.

Any guidelines and comments regarding strong duck typing/structural
subtyping are very welcome, since the lack of this is the only reason why I
would prefer a dynamic language over a static one.

Thanks a lot,
Peter Verswyvelen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: epoll bindings 0.2

2009-09-25 Thread Toralf Wittner
Hi, I am pleased to announce the release of epoll bindings 0.2 available from:

http://hackage.haskell.org/package/epoll

Epoll is an I/O event notification facility for Linux similar to poll
but with good scaling characteristics. This release adds a buffer
abstraction on top of the existing low-level bindings, so client code
can write and read to buffers without having to deal directly with the
underlying epoll event handling.

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


Re: [Haskell-cafe] Proof in Haskell

2009-09-25 Thread Paul Johnson
One alternative approach is to use QuickCheck to test many trees and 
look for counter-examples.  You can also use SmallCheck to do an 
exhaustive check up to a chosen size of tree.


To do this with QuickCheck you would write a function such as

   prop_mirror :: Node a - Bool
   prop_mirror x = (mirror (mirror x)) == x

You would also need to define an instance of Arbitrary for Node to 
create random values of the Node type.  Then you can call:


   quickCheck prop_mirror

and it will call the prop_mirror function with 100 random test cases.  
Not the formal proof you wanted, but still very effective at finding bugs.




On 25/09/09 12:14, pat browne wrote:

Hi,
Below is a function that returns a mirror of a tree, originally from:

http://www.nijoruj.org/~as/2009/04/20/A-little-fun.html

where it was used to demonstrate the use of Haskabelle(1) which converts
Haskell programs to the Isabelle theorem prover. Isabelle was used to
show that the Haskell implementation of mirror is a model for the axiom:

  mirror (mirror x) = x

My question is this:
Is there any way to achieve such a proof in Haskell itself?
GHC appears to reject equations such has
mirror (mirror x) = x
mirror (mirror(Node x y z)) = Node x y z


Regards,
Pat


=CODE=
module BTree where

data Tree a = Tip
 | Node (Tree a) a (Tree a)

mirror ::  Tree a -  Tree a
mirror (Node x y z) = Node (mirror z) y (mirror x)
mirror Tip = Tip

(1)Thanks to John Ramsdell for the link to Haskabelle:
http://www.cl.cam.ac.uk/research/hvg/Isabelle/haskabelle.html).

___
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] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Job Vranish
Short answer: There is no good way of doing what you want.
This is actually one of my biggest annoyances with haskell (right up there
with disallowing infinite types). They are many techniques that work better
or worse depending on the application, but non are very satisfactory IMO.
Your typeclass solution(or some variant of) is pretty much your best option.
If you're careful about how you define your datatype and classes you can
avoid the type families and such, but the whole point is to not have to be
careful.
If your types are fixed (which is usually true as long as you're not using
existentials) you might be able to get away with using
-XDisambiguateFieldRecords

If you want anything better you're probably going to have to use some form
of preprocessor (like OHaskell).


Supposedly OCaml has an OO feature that does this but I haven't tried it
out.

I would suspect that the reason why haskell doesn't provide duck typeing on
record fields is that analisys for optimizations is much more complicated
(as it currently stands, records are nothing but sugar on top of algeraic
datatypes).
You can end up with all sorts of weird things with duck typeing on record
fields, like unnamed datatypes. For example:

(using class constraint style to inidicate a record field restriction for
lack of a better syntax)
setPosition :: (position a) =Vector - a - a
setPosition v x = x { position = v }

translate :: (position a) =Vector - a - a
translate v x = x { position = v + (position x) }

getPosition :: (position a) = a - Vector
getPosition x = position x

result :: Vector
result = getPosition $ translate someVector $ setPosition someOtherVector

The type variable 'a' in these functions is never fixed to a specific type,
and it actually doesn't need to be. The compiler would just have to invent a
suitable one (a type with only the field 'position' of type Vector).

Maybe someday haskell will finially implement good, clean, duck typeable,
record functionality. I will be waiting...

- Job


On Fri, Sep 25, 2009 at 9:54 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Haskell's records are a bit annoying, and type-classes often group together
 too many methods, which means you make early decisions about future unknown
 requirements, and IMO you always get it wrong :-)
 After having read an email in the cafe about the Noop language  Self
 language, I realized that what I really would like to have is strong duck
 typing on records (or is it called structural subtyping? or
 prototype-based-objects? or something like that)
 For example (silly example full of inaccuracies, but you get the picture):

 class HasPosition a where
   position :: a - Point
   withPosition :: Point - a - a

 class HasVelocity a where
   velocity :: a - Vector
   withVelocity :: Vector - a - a

 which we really should write as

 field HasPosition :: Point
 field HasVelocity :: Vector

 And then

 record IsKinetic :: HasPosition HasVelocity

 suppose we write a function like

 kineticEulerStep dt k = withPosition (position k .+^ dt *^ velocity k) k

 kineticEulerStep will work on any type a that HasPosition and HasVelocity,
 and would get inferred signature

 kineticEulerStep :: IsKinetic a = Float - a - a

 which is identical to

 kineticEulerStep :: (HasPosition a, HasVelocity a) = Float - a - a

 So basically kineticEulerStep accepts anything that HasPosition and
 HasVelocity, whatever it is.

 So if it walks like a duck and ..., then it is a duck, but statically
 known...

 We could also do

 field HasForce :: Vector
 field HasMass :: Float

 record IsDynamic :: IsKinetic HasForce HasMass

 acceleration d = force d ^/ mass d
 withAcceleration a d = withForce (a ^* mass d) d

 dynamicEulerStep dt d = withVelocity (velocity d ^+^ dt *^ acceleration d)

 Of course you would also need type families to be really correct since
 Vector, Point, etc should also be parametrized.

 And really kineticEulerStep might also work on something that HasVelocity
 and HasAcceleration (since the code in dynamicEulerStep is almost the same
 as kineticEulerStep), so better abstraction might be needed.

 I'm not sure what kind of overhead a system like this would have in
 Haskell, since I suspect the many dictionaries are often not optimized away.

 I think for Haskell prime, something like this was 
 suggestedhttp://repetae.net/recent/out/classalias.html,
 but is was rejected?

 Languages like OCaml and haXe http://haxe.org/manual/2_types also
 provide a similar feature?

 I would like to collect ways of doing this in Haskell, without boilerplate,
 and preferably without runtime overhead.

 I remember reading OOHaskell a while time ago, and while I didn't
 understand a lot of it, I recall it also was doing a similar thing, but
 since the compiler lacks native support, the error messages you get most
 likely make it impossible to figure out what is going wrong. I think
 Grapefruit's Records, HList, Data.Accessor, etc.. might also work.

 Any guidelines and comments regarding 

[Haskell-cafe] mapping large structures into memory

2009-09-25 Thread Warren Harris
I've dabbled in haskell, but am by no means an expert. I was hoping  
someone here could help me settle this debate so that we can more  
seriously consider haskell for a next version of an application we're  
building


I would like to understand better what its capabilities are for  
directly mapping and managing memory. For instance, I would like mmap  
many large files into memory and mutate their internals directly...  
without needing to reallocate them (or chunks of them) in the haskell  
heap, and without resorting to a byte-array and byte-offset  
representation. Furthermore, I might also like to map intrinsic  
haskell data structures into this mmap'd memory such that standard  
library functions can manipulate them (perhaps in a purely functional  
way, e.g. treating them as haskell arrays of smaller foreign  
structures).


I understand that the foreign function interface has the ability to  
marshall/unmarshall C structs, but I'm unsure of the memory  
implications of using this mechanism. Our application has a very large  
footprint, and reallocating some or all of these mapped files is a non- 
starter. Thanks,


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


Re: [Haskell-cafe] mapping large structures into memory

2009-09-25 Thread Don Stewart
warrensomebody:
 I've dabbled in haskell, but am by no means an expert. I was hoping  
 someone here could help me settle this debate so that we can more  
 seriously consider haskell for a next version of an application we're  
 building

 I would like to understand better what its capabilities are for directly 
 mapping and managing memory. For instance, I would like mmap many large 
 files into memory and mutate their internals directly... without needing 
 to reallocate them (or chunks of them) in the haskell heap, and without 
 resorting to a byte-array and byte-offset representation. Furthermore, I 
 might also like to map intrinsic haskell data structures into this mmap'd 
 memory such that standard library functions can manipulate them (perhaps 
 in a purely functional way, e.g. treating them as haskell arrays of 
 smaller foreign structures).

 I understand that the foreign function interface has the ability to  
 marshall/unmarshall C structs, but I'm unsure of the memory implications 
 of using this mechanism. Our application has a very large footprint, and 
 reallocating some or all of these mapped files is a non-starter. Thanks,

It is entirely possible to use mmap to map structures into memory.
Thanks to the foreign function interface, there are well-defined
semantics for calling to and from C.

The key questions would be:

 * what is the type and representation of the data you wish to map
 * what operations on them

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


Re: [Haskell-cafe] mapping large structures into memory

2009-09-25 Thread Warren Harris


On Sep 25, 2009, at 12:14 PM, Don Stewart wrote:



It is entirely possible to use mmap to map structures into memory.
Thanks to the foreign function interface, there are well-defined
semantics for calling to and from C.

The key questions would be:

* what is the type and representation of the data you wish to map
* what operations on them


Right... my question relates more to how well the intrinsic type  
system integrates with foreign/mapped structures. For instance, I  
wouldn't want to create my own foreign arrays, and have to replicate  
all sorts of library code that only works on haskell's intrinsic arrays.


I'm assuming here that all this mapped data is self-contained, and  
doesn't point to heap-allocated structures, although that's a related  
question -- is it possible to inform the gc about heap pointers stored  
(temporarily) in these structures (and later identify them in order to  
swizzle them out when flushing the mapped file to disk).


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


Re: [Haskell-cafe] mapping large structures into memory

2009-09-25 Thread Don Stewart
warrensomebody:

 On Sep 25, 2009, at 12:14 PM, Don Stewart wrote:


 It is entirely possible to use mmap to map structures into memory.
 Thanks to the foreign function interface, there are well-defined
 semantics for calling to and from C.

 The key questions would be:

 * what is the type and representation of the data you wish to map
 * what operations on them

 Right... my question relates more to how well the intrinsic type system 
 integrates with foreign/mapped structures. For instance, I wouldn't want 
 to create my own foreign arrays, and have to replicate all sorts of 
 library code that only works on haskell's intrinsic arrays.

Well, nothing is really 'intrinsic', but the fundamental distinction are
unpinned GC-managed memory,  and pinned memory.

The 'arrays' package illustrates GC-managed memory, while
Data.ByteString or the 'carray' or 'hmatrix' library illustrate pinned
memory manipulatable with foreign operations.

For your mmapped data, you'll need to assign (coerce) the pointers to
that data to a type that describes pinned memory.
 
 I'm assuming here that all this mapped data is self-contained, and  
 doesn't point to heap-allocated structures, although that's a related  
 question -- is it possible to inform the gc about heap pointers stored  
 (temporarily) in these structures (and later identify them in order to  
 swizzle them out when flushing the mapped file to disk).

You can associated a ForeignPtr with mmapped data, and have the GC unmap
the data for you once references go out of scope.

Simple example:

- Data.ByteString

A fast Haskell type that can be allocated and manipulated by C or Haskell.

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


Re: [Haskell-cafe] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Alp Mestan
On Fri, Sep 25, 2009 at 8:14 PM, Job Vranish jvran...@gmail.com wrote:

 Supposedly OCaml has an OO feature that does this but I haven't tried it
 out.


Indeed, OCaml has stuctural polymorphism, it's a wonderful feature.

*# let f myobj = myobj#foo Hi !;;
val f :  foo : string - 'a; ..  - 'a = fun*

IIRC, there has been work on Template Haskell for structural polymorphism.

-- 
Alp Mestan
http://blog.mestan.fr/
http://alp.developpez.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Casey Hawthorne
On Fri, 25 Sep 2009 23:25:21 +0200, you wrote:

On Fri, Sep 25, 2009 at 8:14 PM, Job Vranish jvran...@gmail.com wrote:

 Supposedly OCaml has an OO feature that does this but I haven't tried it
 out.


Indeed, OCaml has stuctural polymorphism, it's a wonderful feature.

*# let f myobj = myobj#foo Hi !;;
val f :  foo : string - 'a; ..  - 'a = fun*

IIRC, there has been work on Template Haskell for structural polymorphism.

Structural subtyping/polymorphism:

Pros:
- an object can be coerced to any compatible type, the types do not
have to be specified ahead of time, that is at compile time.

Cons:
- may be overly permissive; some coercions might not make sense
semantically.

I wonder how Haskell will minimize the cons, since it is strongly
typed.

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


[Haskell-cafe] Re: Beginning of a meta-Haskell [was: An issue with the ``finally tagless'' tradition]

2009-09-25 Thread Brad Larsen
Oleg,

On Thu, Sep 24, 2009 at 1:54 AM,  o...@okmij.org wrote:

 The topic of an extensible, modular interpreter in the tagless final
 style has come up before. A bit more than a year ago, on a flight from
 Frankfurt to San Francisco I wrote two interpreters for a trivial
 subset of Haskell or ML (PCF actually), just big enough for Power,
 Fibonacci and other classic functions. The following code is a
 fragment of meta-Haskell. It defines the object language and two
 interpreters: one is the typed meta-circular interpreter, and the
 other is a non-too-pretty printer. We can write the expression once:

 power =
   fix $ \self -
   lam $ \x - lam $ \n -
     if_ (n = 0) 1
         (x * ((self $$ x) $$ (n - 1)))

 and interpret it several times, as an integer

 -- testpw :: Int
 testpw = (unR power) (unR 2) ((unR 7)::Int)
 -- 128

 or as a string

 -- testpwc :: P.String
 testpwc = showQC power

 {-
  (let self0 = (\\t1 - (\\t2 - (if (t2 = 0) then 1 else (t1 * ((self0  t1) 
  (t2 - 1)) in self0)
 -}

 The code follows. It is essentially Haskell98, with the exception of
 multi-parameter type classes (but no functional dependencies, let
 alone overlapping instances).

 {-# LANGUAGE NoMonomorphismRestriction, NoImplicitPrelude #-}
 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

 -- A trivial introduction to `meta-Haskell', just enough to give a taste
 -- Please see the tests at the end of the file

 module Intro where

 import qualified Prelude as P
 import Prelude (Monad(..), (.), putStrLn, IO, Integer, Int, ($), (++),
                (=), Bool(..))
 import Control.Monad (ap)
 import qualified Control.Monad.State as S

 -- Definition of our object language
 -- Unlike that in the tagless final paper, the definition here is spread
 -- across several type classes for modularity

 class QNum repr a where
    (+) :: repr a - repr a - repr a
    (-) :: repr a - repr a - repr a
    (*) :: repr a - repr a - repr a
    negate :: repr a - repr a
    fromInteger :: Integer - repr a
 infixl 6 +, -
 infixl 7 *

 class QBool repr where
    true, false :: repr Bool
    if_ :: repr Bool - repr w - repr w - repr w

 class QBool repr = QLeq repr a where
    (=) :: repr a - repr a - repr Bool
 infix 4 =

 -- Higher-order fragment of the language

 class QHO repr  where
    lam  :: (repr a - repr r) - repr (a - r)
    ($$) :: repr (a - r) - (repr a - repr r)
    fix  :: (repr a - repr a) - repr a
 infixr 0 $$

 -- The first interpreter R -- which embeds the object language in
 -- Haskell. It is a meta-circular interpreter, and so is trivial.
 -- It still could be useful if we wish just to see the result
 -- of our expressions, quickly
 newtype R a = R{unR :: a}

 instance P.Num a = QNum R a where
    R x + R y = R $ x P.+ y
    R x - R y = R $ x P.- y
    R x * R y = R $ x P.* y
    negate      = R . P.negate . unR
    fromInteger = R . P.fromInteger

 instance QBool R where
    true  = R True
    false = R False
    if_ (R True)  x y = x
    if_ (R False) x y = y

 instance QLeq R Int where
    R x = R y = R $ x P.= y

 instance QHO R where
    lam f      = R $ unR . f . R
    R f $$ R x = R $ f x
    fix f      = f (fix f)

 -- The second interpreter: pretty-printer
 -- Actually, it is not pretty, but sufficient

 newtype S a = S{unS :: S.State Int P.String}

 instance QNum S a where
    S x + S y = S $ app_infix + x y
    S x - S y = S $ app_infix - x y
    S x * S y = S $ app_infix * x y
    negate (S x) = S $ (return $ \xc - (negate  ++ xc ++ )) `ap` x
    fromInteger = S . return . P.show

 app_infix op x y = do
  xc - x
  yc - y
  return $ ( ++ xc ++   ++ op ++   ++ yc ++ )

 instance QBool S where
    true  = S $ return True
    false = S $ return False
    if_ (S b) (S x) (S y) = S $ do
                                bc - b
                                xc - x
                                yc - y
                                return $ (if  ++ bc ++  then  ++ xc ++
                                          else  ++ yc ++ )
 instance QLeq S a where
    S x = S y = S $ app_infix = x y

 newName stem = do
  cnt - S.get
  S.put (P.succ cnt)
  return $ stem ++ P.show cnt

 instance QHO S where
  S x $$ S y = S $ app_infix  x y

  lam f = S $ do
             name - newName t
             let xc = name
             bc - unS . f . S $ return xc
             return $ (\\ ++ xc ++  -  ++ bc ++ )

  fix f = S $ do
             self - newName self
             let sc = self
             bc - unS . f . S $ return sc
             return $ (let  ++ self ++  =  ++ bc ++  in  ++ sc ++ )

 showQC :: S a - P.String
 showQC (S m) = S.evalState m (unR 0)

 -- 
 --   Tests

 -- Perhaps the first test should be the power function...
 -- The following code can be interpreted and compiled just as it is...

 power =
  fix $ \self -
  lam $ \x - lam $ \n -
    if_ (n = 0) 1
        (x * ((self $$ x) $$ (n - 1)))

 -- The interpreted result
 -- testpw :: 

Re: [Haskell-cafe] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Casey Hawthorne
On Fri, 25 Sep 2009 23:25:21 +0200, you wrote:

On Fri, Sep 25, 2009 at 8:14 PM, Job Vranish jvran...@gmail.com wrote:

 Supposedly OCaml has an OO feature that does this but I haven't tried it
 out.


Indeed, OCaml has stuctural polymorphism, it's a wonderful feature.

*# let f myobj = myobj#foo Hi !;;
val f :  foo : string - 'a; ..  - 'a = fun*

IIRC, there has been work on Template Haskell for structural polymorphism.

Structural subtyping/polymorphism:

Pros:
- an object can be coerced to any compatible type, the types do not
have to be specified ahead of time, that is at compile time.

Cons:
- may be overly permissive; some coercions might not make sense
semantically.

I wonder how Haskell will minimize the cons, since it is strongly
typed.


I forgot to add: that even if strong typing could be measured on sum
numerical scale, I don't know whether Haskell has a higher
measure/metric than OCaml, in the strong typing area.

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


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-25 Thread wren ng thornton

Brad Larsen wrote:

On Thu, Sep 24, 2009 at 8:36 PM, wren ng thornton w...@freegeek.org wrote:

The reason this is unsatisfying is [...] if you need to lift
more than one variable in the same class then it can be tricky to do the
encoding right. For instance, when converting Monad into this form (e.g. so
we can define an instance for Set) it is prudent to separate it into one
class for return and another for join/(=)/().


As you say :)



I have experimented some in the past day with this canonical technique
of lifting type variables into the class specification.  This is
somewhat successful; however, one problem is that when multiple
variables are lifted into the specification, ambiguity creeps in (and
over-generality?), in the absence of superclass constraints or
functional dependencies.
[...]
One can alleviate the ambiguity of Bar by splitting it into two
classes, similarly to splitting up Monad:
[...]
It's not clear to me that such a decomposition is always possible.
I'll keep experimenting with modular, tagless EDSLs...



I don't know that it will always work (though Oleg could say for sure). 
For simple classes like Monad and similar algebraic concepts, it works 
quite well; but then the maths are sort of designed that way. The more 
you move to large families of complexly interconnected methods, the more 
it seems likely it'll break down or require fundeps/typefamilies to 
resolve ambiguity cleanly.


Depending on exactly what your goal is re multiple interpretation, Ralf 
Hinze has some nice work on the lifting lemma for re-interpreting 
lambda-calculus syntax under different idioms:


http://www.comlab.ox.ac.uk/ralf.hinze/WG2.8//26/slides/ralf.pdf

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread wren ng thornton

Peter Verswyvelen wrote:

After having read an email in the cafe about the Noop language  Self
language, I realized that what I really would like to have is strong duck
typing on records (or is it called structural subtyping? or
prototype-based-objects? or something like that)


The common name for (one form of) what you're seeking is row polymorphism:

  http://www.cs.cmu.edu/~neelk/rows.pdf

This is implemented in OCaml but, like most OO features in functional 
languages, it is often ignored or forgotten about. As others've 
mentioned, there are some cases where row polymorphism is really nice, 
but it's not always semantically coherent.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Sebastian Sylvan
On Fri, Sep 25, 2009 at 10:55 PM, Casey Hawthorne cas...@istar.ca wrote:

 On Fri, 25 Sep 2009 23:25:21 +0200, you wrote:

 On Fri, Sep 25, 2009 at 8:14 PM, Job Vranish jvran...@gmail.com wrote:
 
  Supposedly OCaml has an OO feature that does this but I haven't tried it
  out.
 
 
 Indeed, OCaml has stuctural polymorphism, it's a wonderful feature.
 
 *# let f myobj = myobj#foo Hi !;;
 val f :  foo : string - 'a; ..  - 'a = fun*
 
 IIRC, there has been work on Template Haskell for structural polymorphism.

 Structural subtyping/polymorphism:

 Pros:
 - an object can be coerced to any compatible type, the types do not
 have to be specified ahead of time, that is at compile time.

 Cons:
 - may be overly permissive; some coercions might not make sense
 semantically.

 I wonder how Haskell will minimize the cons, since it is strongly
 typed.


I kind of think there's no real problem here. If you say that you can accept
any record with a given set of fields, then you have to make sure you make
no other assumptions. This is, in principle, no different from passing a
speed Double to a function that expects a mass Double (e.g. it may produce
garbage for negative values). In both cases a function that requires extra
invariants can enforce it by using a newtype that's constructed and
manipulated in a way which preserves the extra semantic rules.

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