[Haskell-cafe] Re: Forall and type synonyms in GHC 7.0

2010-11-01 Thread Bas van Dijk
On Mon, Nov 1, 2010 at 4:30 AM, Mario Blažević mblaze...@stilo.com wrote:
     Before uploading a new version of my project on Hackage, I decided to
 future-proof it against GHC 7.0. I ran into several compile errors caused by
 the changes in let generalization, but these were easy to fix by adding
 extra type annotations. But then I ran into another problem that I can't fix
 so easily. Here is its trimmed-down reproduction:

 {-# LANGUAGE RankNTypes #-}

 module Test where

 data Component c = Component {with :: c}

 pair1 :: (Bool - c1 - c2 - c3) - Component c1 - Component c2 -
 Component c3
 pair1 combinator (Component c1) (Component c2) = Component (combinator
 True c1 c2)

 type PairBinder m = forall x y r. (x - y - m r) - m x - m y - m r

 pair2 :: Monad m = (PairBinder m - c1 - c2 - c3) - Component c1 -
 Component c2 - Component c3
 pair2 combinator = pair1 (combinator . chooseBinder)

 chooseBinder :: Monad m = Bool - PairBinder m
 chooseBinder right = if right then rightBinder else leftBinder

 leftBinder :: Monad m = PairBinder m
 leftBinder f mx my = do {x - mx; y - my; f x y}

 rightBinder :: Monad m = PairBinder m
 rightBinder f mx my = do {y - my; x - mx; f x y}

    The general idea here, if you're intrigued, is that pair1 belongs to a
 generic module that packages things it knows nothing about into Components.
 The remaining definitions belong to a client of the generic module, and
 pair2 is a specialization of pair1 to components that have something to do
 with monads.

    Now this little test compiles fine with GHC 6.12.1, but GHC
 7.0.0.20101029 reports the following error in the pair2 definition:

 TestForall.lhs:13:42:
     Couldn't match expected type `forall x y r.
   (x - y - m r) - m x - m y - m r'
     with actual type `(x - y - m1 r) - m1 x - m1 y - m1 r'
     Expected type: Bool - PairBinder m
   Actual type: Bool - (x - y - m1 r) - m1 x - m1 y - m1 r
     In the second argument of `(.)', namely `chooseBinder'
     In the first argument of `pair1', namely
   `(combinator . chooseBinder)'

     I've tried adding extra type annotations without making any progress. At
 this point I'm beginning to suspect I ran into a bug in GHC 7.0, but I can't
 find it in GHC Trac; the only ticket that looks similar is #4347, but that
 one works for me. Is this a bug? If not, how do I make my code compile?


 ___
 Glasgow-haskell-users mailing list
 glasgow-haskell-us...@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



I had the exact same problem in my regional-pointers package in the
withArray function:

withArray ∷ (Storable α, MonadCatchIO pr)
  ⇒ [α]
  → (∀ s. RegionalPtr α (RegionT s pr) → RegionT s pr β)
  → pr β

 I had to replace the original:

withArray vals = withArrayLen vals ∘ const

with:

withArray vals f = withArrayLen vals $ \_ → f

where:

withArrayLen ∷ (Storable α, MonadCatchIO pr)
⇒ [α]
→ (∀ s. Int → RegionalPtr α (RegionT s pr) → RegionT s pr β)
→ pr β

So unfortunately you gave to inline the function composition:

pair2 combinator = pair1 $ \b - combinator (chooseBinder b)

Note that in the other thread I'm describing a similar problem in my
usb-safe package. Where in essence the problem is that the following
won't type check:

foo :: (forall s. ST s a) - a
foo st = ($) runST st

but the following will:

foo :: (forall s. ST s a) - a
foo st = runST st

and surprisingly the following will also type check:

foo :: (forall s. ST s a) - a
foo st = runST $ st

Regards,

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


Re: [Haskell-cafe] Reference for technique wanted

2010-11-01 Thread Stephen Tetley
On 31 October 2010 23:05, Gregory Collins g...@gregorycollins.net wrote:

 They're called difference lists:

Andy Gill and Graham Hutton's first worker wrapper paper calls then
Hughes lists.

This seems more apt to me than difference lists as difference lists
(in the Haskell formulation at least*) don't seem to have any
connection to a notion difference.

Best wishes

Stephen

* It seems from other commentators on the thread that Haskell Hughes
lists are actually different from Prolog difference lists anyway.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: network-2.2.3, merger with network-bytestring

2010-11-01 Thread Neil Davies

Chris

What you are observing is the effects of the delay on the operation of  
the TCP stacks and the way your 'sleep' works.


You are introducing delay (the sleep time is a 'minimum' and then at  
least one o/s jiffy) - that represents one limit. The other limit is  
delay/bandwidth product of the connection hiding of this effect is  
dependent on the window size negotiated.


How accurate do you need this control of throughput? To get really  
accurate rates we had to write our own specialist rate regulated  
thread library which accounts for any scheduling delay and can even  
spin if you want low delay variance in the packet dispatch times.


Neil

On 31 Oct 2010, at 17:56, Christopher Done wrote:


On 31 October 2010 16:14, Johan Tibell johan.tib...@gmail.com wrote:

This version marks the end of the network-bytestring package, which
has now been merged into the network package. This means that
efficient and correct networking using ByteStrings is available as
part of the standard network package.

As part of the merger, two new modules have been added:
Network.Socket.ByteString and Network.Socket.ByteString.lAzy


Huzzah! I updated my little throttler program to use ByteString.[1]

One thing I'm curious about, that maybe you probably know off the top
of your head, is that when I'm limiting the speed, I was merely
recv'ing and send'ing at 1024 bytes a pop[2], however, when I did this
at, say, ~500KB/s, Firefox is really slow at receiving it, whereas
when I set it 4096 it's much faster/more accurate to the speed I
intend. Chrome doesn't seem to care.

I think the difference is that Firefox is single threaded
(select/poll-based?) and has to switch between various jobs while
receiving every tiny block that I'm sending. Chrome probably has the
receiver in a separate process.

So it seems like, short of balancing the package size (at powers of 2)
and the delay to get some ideal throughput, it's easiest and probably
realistically equivalent to set it to 4096 and just rely on an
accurate delay? What do you think? Just curious. This is something I
think I'll look into in the future, I really don't have a good feel
for typical network latency and throughput. It's not a big deal right
now as 56k slow is all I need to test my web app.

[1]: 
http://github.com/chrisdone/throttle/commit/97e03bfc64adc074c9d1f19c2605cb496576c593
[2]: 
http://github.com/chrisdone/throttle/commit/30dc1d970a7c0d43c1b6dc33da9deecf30808114
___
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] Re: Parsing workflow

2010-11-01 Thread Heinrich Apfelmus

Malcolm Wallace wrote:

Nils Schweinsberg wrote:


Vo Minh Thu wrote:

 So you have to either factorize you parsers or use
the 'try'.


This is exactly what gives me headaches. It's hard to tell where you 
need try/lookAhead and where you don't need them. And I don't really 
feel comfortable wrapping everything into try blocks...


Have you considered using a different set of parser combinators, a set 
that is actually composable, and does not require the mysterious try?  
I would recommend polyparse (because I wrote it), but uuparse would also 
be a fine choice.


I second that, the semantics of Parsec are quite tricky. It's worth 
learning them properly if you insist on using Parsec. If you don't want 
to do that, it's easier to use a different library.



The two defining properties of Parsec's alternative  |  combinator are:

1) If a parser  p  consumes a character, then it will take precedence 
over its alternatives   p | q = p  .


2) Parsers that are in sequence with an alternative don't have any 
influence on which alternative is chosen.


   (p | q) = k  =   p = k  if  p  succeeds
q = k  if  p  does not succeed

   but  p = k  might not succeed
   even if  p  does succeed and  q = k  would succeed.


I found the following rule of thumbs helpful:

* Try to use alternatives  p | q  only when  p  and  q  recognize 
different first characters.
* Don't do recursion yourself, use premade combinators like  many1  etc. 
instead.
*  lookAhead  is very useful for avoiding capturing input in the second 
argument of  manyTill



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Reference for technique wanted

2010-11-01 Thread Claus Reinke

To simplify, the difference in persistence between the two
representations is enough to consider them very different
as it makes a dramatic difference in interface.


Interesting discussion. I still think it is the same idea,
namely to represent not-yet-known list tails by variables,
embedded into two different kinds of languages.

   \rest-start++rest
   [start|rest]\rest-- '\' is an infix constructor

The differences arise from the different handling of
variables and scoping in those languages:

- functional languages: explicit, local scopes, variables
   are bound by injecting values from outside the scope
   (applying the binding construct to values); scoped
   expressions can be copied, allowing multiple
   instantiations of variables

- logic languages: implicit, global scopes, variables
   are bound by finding possible values inside the scope
   (unifying bound variables); outside of non-determinism/
   sets-of-solutions handling, only non-scoped terms can
   be copied, allowing single instantiation only

If current functional language implementations had not
abandoned support for reducing under binders, one could
float out the binder for a difference list, and get limitations
closer to those of logic languages (though binding to values
would then become much more unwieldy).

If logic languages allowed local binders in terms, one could
copy difference lists more easily (though substitution and
unification would then involve binders).

So, yes, the realization of the idea is different, as are the
language frameworks, and the junk in the representations,
but the idea is the same.

Btw, functional language implementations not reducing
under binders also implies that functional difference list
operations are not shared to the same extent as logic
difference list operations are - copying a closure copies
un-evaluated expressions, to be re-evaluated every
time the closure is opened with different variable bindings,
so the functional representation is not as efficient as the
logical one, in most implementations.

I can't confirm the reference, but several authors point
to this for an early description

[CT77] Clark, K.L.; Tärnlund, S,Å:
A First Order Theory of Data and Programs.
In: Inf. Proc. (B. Gilchrist, ed.), North Holland, pp. 939-944, 1977.

To close the circle: I understand that difference lists in
Prolog might have been a declarative translation of
in-place updating in Lisp lists:-)

Claus



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


Re: [Haskell-cafe] commutativity

2010-11-01 Thread Patrick Browne
On 31/10/2010 16:55, Brent Yorgey wrote:
 Note that the first parameter to commutative shadows the previous
 definition of com, I don't know if that's what you intended.


Does the following avoid the shadowing?

infixl 5 `op`
op :: Int - Int - Int
x `op` y  = (x + y)
commutative op1 = \a b -  (a `op` b) == (b `op` a)



This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] commutativity

2010-11-01 Thread Roel van Dijk
Yes, that would prevent the shadowing. But now you are ignoring the
argument op1. Choosing a name that is more different from 'op' might
be helpful. You can even invent your own operator as an argument to
your commutative function:

  commutative (⊕) = \a b - (a ⊕ b) == (b ⊕ a)

On Mon, Nov 1, 2010 at 11:15 AM, Patrick Browne patrick.bro...@dit.ie wrote:
 Does the following avoid the shadowing?

 infixl 5 `op`
 op :: Int - Int - Int
 x `op` y  = (x + y)
 commutative op1 = \a b -  (a `op` b) == (b `op` a)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Regex lib doesn't load

2010-11-01 Thread Dan Bensen
Hi Haskellers.  I'm trying to read a text file using GHCi on Haskell Platform 
2010.2.0.0.  The import line in my program is import Text.Regex.   When I run 
:main it says unknown symbol `_regerror' and  unable to load package 
`regex-posix-0.94.2'.  Any clues on how fix this problem?  Please let me know 
if there's a better place to ask about it.

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


Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Sjoerd Visscher
Hi,

There's nothing wrong with your type families. The problem is that the compiler 
doesn't know that the m and rsc of eval are the same as m and rsc of runLoader. 
(Also you had a small bug in the type of eval)

You need the ScopedTypeVariables extension, with a forall on runLoader to tell 
GHC that they should be scoped:

runLoader :: forall m rsc a. (Monad m, Resource rsc) = CfgOf (IdOf rsc) - 
RscLoader rsc m a - m a
runLoader cfg loader = viewT loader = eval M.empty
  where
eval :: (Monad m, Resource rsc) =
 M.Map (IdOf rsc) rsc
 - ProgramViewT (EDSL (IdOf rsc)) m a
 - m a
eval _(Return x) = return x
eval rscs (instr := k) = case instr of
  Load id - do let loc = retrieveLoc cfg id
  -- open and load from loc will go here
  viewT (k ()) = eval rscs
  -- -- -- Other cases yet to come...

greetings,
Sjoerd


On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:

 Hello,
 
 I'm trying to make a simple monad (built on operational's ProgramT) for 
 resource loading.
 I have classes featuring type families :
 
 {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
 
 -- | A ResourceId is something that identifies a resource.
 -- It should be unique for one resource, and should be used to find the 
 location (the path) of the resource,
 -- possibly by using a configuration datatype
 class (Ord id) = ResourceId id where
   type LocOf id
   type CfgOf id
   retrieveLoc :: CfgOf id - id - LocOf id
 
 -- | Class describing a resource of type @rsc@
 class (ResourceId (IdOf rsc)) = Resource rsc where
   type IdOf rsc
   load   :: LocOf (IdOf rsc) - IO (Maybe rsc)
 -- ^ Called when a resource needs to be loaded
   unload :: rsc - IO ()
 -- ^ Idem for unloading
 
 -- | Then, the operations that the loader can perform
 data EDSL id a where
   Load :: id - EDSL id ()
   IsLoaded :: id - EDSL id Bool
   Unload   :: id - EDSL id ()
 
 -- | The loader monad itself
 type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
 
 -- | And finally, how to run a loader
 runLoader :: (Monad m, Resource rsc) = CfgOf (IdOf rsc) - RscLoader rsc m a 
 - m a
 runLoader cfg loader = viewT loader = eval M.empty
   where
 eval :: (Monad m, Resource rsc) =
  M.Map (IdOf rsc) rsc
  - ProgramViewT (EDSL rsc) m a
  - m a
 eval _(Return x) = return x
 eval rscs (instr := k) = case instr of
   Load id - do let loc = retrieveLoc cfg id
   -- open and load from loc will go here
   viewT (k ()) = eval rscs
   -- -- -- Other cases yet to come...
 
 
 
 Well, there is no way I can get it type-check. I think I must be misusing the 
 type families (I tried with multi-param typeclasses and functional 
 dependencies, but it ends up to be the same kind of nightmare...).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] Regex lib doesn't load

2010-11-01 Thread Ivan Lazar Miljenovic
On 1 November 2010 23:36, Dan Bensen danben...@att.net wrote:
 Hi Haskellers.  I'm trying to read a text file using GHCi on Haskell
 Platform 2010.2.0.0.  The import line in my program is import Text.Regex.
   When I run :main it says unknown symbol `_regerror' and  unable to load
 package `regex-posix-0.94.2'.  Any clues on how fix this problem?  Please
 let me know if there's a better place to ask about it.

I'm going to randomly guess that you're using Windows, and that these
previous reports of similar behaviour have the same problem as you do:

http://www.mail-archive.com/haskell-cafe@haskell.org/msg51707.html
http://www.mail-archive.com/haskell-platf...@projects.haskell.org/msg01153.html

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Red links in the new haskell theme

2010-11-01 Thread Nick Bowler
On 2010-10-30 08:11 -0700, Mark Lentczner wrote:
 1) HTML supports the concept of alternate style sheets. If present,
 then the idea was that browsers would give the user the choice,
 somewhere, to choose among them. While Firefox does this (View  Page
 Style),

The implementation in Firefox is such that the style sheet resets to the
default if you reload the page or follow any link.  This makes the
feature completely useless in practice.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Regex lib doesn't load

2010-11-01 Thread Stephen Tetley
See this conclusion of this thread - installing the latest version
from Hackage seems to be the solution:

http://www.haskell.org/pipermail/haskell-cafe/2010-August/082141.html

Note that although regex-posix is a binding to a C library, because
the library and headers are delivered with the Platform you should be
able to upgrade without needing MinGW (MinGW is otherwise usually
needed for C library bindings on Windows).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Finding the contents of haskell platform?

2010-11-01 Thread Magnus Therning
I know there's a .cabal file for the latest version of HP somewhere,
but I can't coerce Google into finding me a link that actually works.
Furthermore, the following page:

http://hackage.haskell.org/platform/contents.html

does list all the contents, but to my big surprise it doesn't link to
the specific versions of the packages for HP, instead it links to the
latest version found on Hackage.

Would someone with the power to make changes on the HP pages *please*
make it as easy as possible to find the *exact* specification of what
HP contains?  Please, pretty please with sugar on top.

No, a changelog entry
(http://hackage.haskell.org/platform/changelog.html) is not very
helpful (why the HP front page links to it I can't understand).

Going via the Haskell wiki
(http://www.haskell.org/haskellwiki/Haskell_Platform#What.27s_in_the_platform)
to find a link to the .cabal
(http://code.haskell.org/haskell-platform/haskell-platform.cabal) is
not that user friendly.  It's even worse that the latter link doesn't
seem to work at all at the moment.

(The short irritated tone in this email accurately shows my
desperation with the situation: I thought I would be able to find this
information with only 5 minutes to spare before my next meeting.)

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Finding the contents of haskell platform?

2010-11-01 Thread Don Stewart
magnus:
 I know there's a .cabal file for the latest version of HP somewhere,
 but I can't coerce Google into finding me a link that actually works.
 Furthermore, the following page:
 
 http://hackage.haskell.org/platform/contents.html
 
 does list all the contents, but to my big surprise it doesn't link to
 the specific versions of the packages for HP, instead it links to the
 latest version found on Hackage.
 
 Would someone with the power to make changes on the HP pages *please*
 make it as easy as possible to find the *exact* specification of what
 HP contains?  Please, pretty please with sugar on top.
 
 No, a changelog entry
 (http://hackage.haskell.org/platform/changelog.html) is not very
 helpful (why the HP front page links to it I can't understand).
 
 Going via the Haskell wiki
 (http://www.haskell.org/haskellwiki/Haskell_Platform#What.27s_in_the_platform)
 to find a link to the .cabal
 (http://code.haskell.org/haskell-platform/haskell-platform.cabal) is
 not that user friendly.  It's even worse that the latter link doesn't
 seem to work at all at the moment.
 
 (The short irritated tone in this email accurately shows my
 desperation with the situation: I thought I would be able to find this
 information with only 5 minutes to spare before my next meeting.)
 

Currently, the versions are specified in the .cabal file.
A script is used to generate the changelog page (diffcabal, iirc).

I'll generate a spec page from the .cabal file this week sometime.

-- Don

P.S. better sent to the haskell-platform@ list


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


[Haskell-cafe] Re: Forall and type synonyms in GHC 7.0

2010-11-01 Thread Mario Blažević



I had the exact same problem in my regional-pointers package in the
withArray function:

withArray ∷ (Storable α, MonadCatchIO pr)
   ⇒ [α]
   → (∀ s. RegionalPtr α (RegionT s pr) → RegionT s pr β)
   → pr β

  I had to replace the original:

withArray vals = withArrayLen vals ∘ const

with:

withArray vals f = withArrayLen vals $ \_ → f

where:

withArrayLen ∷ (Storable α, MonadCatchIO pr)
 ⇒ [α]
 → (∀ s. Int → RegionalPtr α (RegionT s pr) → RegionT s pr β)
 → pr β

So unfortunately you gave to inline the function composition:

pair2 combinator = pair1 $ \b -  combinator (chooseBinder b)



	This worked for me, thank you! I was worried I'd have to make a 
sweeping change to the module interfaces. I find this solution rather 
surprising, but as long as it's localized I don't mind.




Note that in the other thread I'm describing a similar problem in my
usb-safe package. Where in essence the problem is that the following
won't type check:

foo :: (forall s. ST s a) -  a
foo st = ($) runST st

but the following will:

foo :: (forall s. ST s a) -  a
foo st = runST st

and surprisingly the following will also type check:

foo :: (forall s. ST s a) -  a
foo st = runST $ st



	Yes, I hadn't seen that thread until this morning. The same issue with 
impredicative types appears to cause my problem and both problems you've 
encountered. I wonder what percentage of Hackage libraries will be 
affected by the change.

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


Re: [Haskell-cafe] Edit Hackage

2010-11-01 Thread Claus Reinke



Stack Overflow and Reddit are at least improvements over the traditional
web forums, starting to acquire some of the features Usenet had twenty
years ago.  Much like Planet-style meta-blogs and RSS syndication makes
it liveable to follow blogs.


Very much this. I mourn Usenet's potential as much as anyone, but life
goes on.


Agreed, in principle. However, the quality of discussions on Reddit
makes me want to run away more often than not - it is already worse
than Usenet was in its last throws (yes, I know it is living an 
afterlive;-). One thing we learned from Usenet is that trying to 
add to a thread gone bad is very unlikely to make it any better, 
and too many Reddit threads go bad so quickly that I've never 
felt like even trying to improve the signal/noise ratio. Just my 
own impression, of course (and perhaps the Haskell Reddit

doesn't suffer quite as much).

Also, while both Reddit and Stack Overflow can be read without
Javascript, both require Javascript for posting (can't even log in
to Reddit without, and have to edit half-blind in Stack Overflow
without). Community-edited sites like these are the last ones on
which I'd want to be forced to enable Javascript.

Moving from a few Haskell mailing lists to many lists, to added
IRC channels, to added blogs and RSS-feeds and aggregators,
and added sites like Reddit and Stack Overflow does give more
options, but makes it rather harder to follow everthing (in the
beginning, feeds and aggregators give you the feeling that
you're more up to date than ever, but at some point your feed
handler overflows your number of hours per day:-).

Which means that it is also getting more and more difficult to
reach people as easily as before (do you ask on haskell-cafe,
haskell-beginners, reddit, or SO? do you announce on haskell,
haskell-cafe, or reddit? do you survey on haskell, haskell-cafe,
google, or reddit? do you answer queries on the wiki, on -cafe,
on -beginners, on reddit, on SO, or where? and so on..). Some
people try to crosspost items to their favourite sites, in the
hope of finding them again, in a single place. So many social
sites now compete with each other that blog entries come
with one-click-forward-this-there buttons.

So, I agree with Don that you're missing things if you only
follow the -cafe, and I agree with others that the -cafe is the
most important forum for me. Overall, I'm not too happy
with the way things are diverging, though..

Apart from the Usenet-mailing list move, it also reminds
me of the command line-GUI movement - some people
are quite happy with tools that at least remind them of
command line control (such as most mail readers or
programmer's editors), while others want web and guis
that do not remind them of something they've never seen
or put to good use (the command line prompt).

Or perhaps, it is just a tick easier to get started on web
forums - you can read without subscribing, you can
subscribe without committing yourself (throwaway
accounts on reddit, for instance) or installing tools (if
I recall correctly, my last Windows notebook no longer
came with pre-installed email client..).


As you say, most email archives leave something to be desired. As far
as I know, the best way to find anything in old -cafe threads is to do
a google search with
site:http://www.haskell.org/pipermail/haskell-cafe/;, and there's no
good way to get an overview. Especially as topic drift leads to
subject lines being uninformative (I mean, Edit Hackage? What?).


I have the feeling that the existence of 4-5 archives for some
Haskell lists means that the Google ranking will be spread
among them, giving each a weaker ranking than one would
hope for (it certainly didn't help that some time ago, haskell.org
had robots banned from its mailing list archives for a while).

Btw, does anyone know why searching with list:haskell-cafe
does not help much, even though every single posting to this
list has a List-Archive: heading pointing to the pipermail
archive?

Claus


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


Re: [Haskell-cafe] Finding the contents of haskell platform?

2010-11-01 Thread Magnus Therning
On Mon, Nov 1, 2010 at 14:47, Don Stewart d...@galois.com wrote:
 magnus:
 I know there's a .cabal file for the latest version of HP somewhere,
 but I can't coerce Google into finding me a link that actually works.
 Furthermore, the following page:

 http://hackage.haskell.org/platform/contents.html

 does list all the contents, but to my big surprise it doesn't link to
 the specific versions of the packages for HP, instead it links to the
 latest version found on Hackage.

 Would someone with the power to make changes on the HP pages *please*
 make it as easy as possible to find the *exact* specification of what
 HP contains?  Please, pretty please with sugar on top.

 No, a changelog entry
 (http://hackage.haskell.org/platform/changelog.html) is not very
 helpful (why the HP front page links to it I can't understand).

 Going via the Haskell wiki
 (http://www.haskell.org/haskellwiki/Haskell_Platform#What.27s_in_the_platform)
 to find a link to the .cabal
 (http://code.haskell.org/haskell-platform/haskell-platform.cabal) is
 not that user friendly.  It's even worse that the latter link doesn't
 seem to work at all at the moment.

 (The short irritated tone in this email accurately shows my
 desperation with the situation: I thought I would be able to find this
 information with only 5 minutes to spare before my next meeting.)


 Currently, the versions are specified in the .cabal file.
 A script is used to generate the changelog page (diffcabal, iirc).

 I'll generate a spec page from the .cabal file this week sometime.

Ah, excellent.  Sorry for the rather rant-y email before.  I've now
been to the meeting and managed to calm down a bit :-)

 P.S. better sent to the haskell-platform@ list

Yes, of course.  I'm now trying to fix that by cross-posting, let's
hope I won't get too many angry emails about that ;-)

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANNAUNCE] ghcjs-0.1.0 Haskell to Javascript compiler

2010-11-01 Thread Martijn Schrage

On 29-10-10 22:20, Aaron Gray wrote:
On 27 October 2010 13:30, Martijn Schrage mart...@oblomov.com 
mailto:mart...@oblomov.com wrote:


On 21-10-10 01:01, Victor Nazarov wrote:


This example creates a text field that turns red if it contains
any non-digit characters. It is on-line at
http://tryout.oblomov.com/ghcjs/ghcjs.html  (Note: I only tested
it on Firefox on a Mac)

All used files are in a zip file at
http://tryout.oblomov.com/ghcjs/ghcjs.zip (validate is in Test.hs,
the JS monad in JS.hs, and the JavaScript for execHaskell in util.js)


What browser are you using, IE8, IE9, FF and Chrome on Windows throw 
up errors, both locally and to your above code.
That's weird, since http://tryout.oblomov.com/ghcjs/ghcjs.html works 
fine for me with Firefox both on Mac and Windows (XP  7). There is only 
a small bug that causes a key event to get lost when the Haskell 
JavaScript modules are loaded.


What error messages do you get from Firefox?

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


[Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
Hello.

I'd like to have a template haskell function that take some constraints and
a class name and write an empty class from those and relative empty instance
to simulate typeclass synonyms.

As I've never written TH and couldn't find a easily adaptable code around, I
ask here for the code, or some hints on how to arrive there.

Thanks

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


Re: [Haskell-cafe] commutativity

2010-11-01 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 10/30/10 06:55 , Patrick Browne wrote:
 -- Question 1
 -- commutative com 1 3
 -- This also gives true. Is it because of commutative equation or
 because of the plus operation?

Haskell doesn't know about commutativity; you got true because (+) happens
to be commutative.  There was a discussion about this recently on the list.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkzO8MMACgkQIn7hlCsL25XC2ACgulNd5A+Gf33lplW3HOmhPLlZ
u3EAoMsrbEkMQuU1yR/VaG5XqvNdhS5+
=jMQe
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] install GHC 7.0.1 RC on OS X?

2010-11-01 Thread Edward Amsden
I'd like to install the GHC 7.0.1 RC on my mac (Snow Leopard, x86_64),
but I don't want it to run over my current GHC 6.12.2 install.

If I use the .pkg installer, it doesn't allow me to select the
destination, and I worry that it will overwrite my 6.12.2 install.

If I try to build from source, that requires me to use my current GHC,
which (as I understand) would build for 32 bit.

What other options do I have, or am I misunderstanding something?
--
Edward Amsden
Undergraduate
Computer Science
Rochester Institute of Technology
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Christopher Done
On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com wrote:
 I'd like to have a template haskell function that take some constraints and
 a class name and write an empty class from those and relative empty instance
 to simulate typeclass synonyms.

 As I've never written TH and couldn't find a easily adaptable code around, I
 ask here for the code, or some hints on how to arrive there.

I took Justin Bailey's haskelldb-th library as a TH example to work
from and rewrote one TH function to try my hand at it, it's quite easy
to follow with a simple example:

http://hpaste.org/paste/41035/demo

Maybe this is enough example to get you going. The rest you can find
syntax parts from the TH Haddock documentation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: network-2.2.3, merger with network-bytestring

2010-11-01 Thread Christopher Done
On 1 November 2010 09:55, Neil Davies semanticphilosop...@gmail.com wrote:
 How accurate do you need this control of throughput? To get really accurate
 rates we had to write our own specialist rate regulated thread library which
 accounts for any scheduling delay and can even spin if you want low delay
 variance in the packet dispatch times.

I don't need particular accuracy, about as slow as dial-up and
about as slow as broadband are good enough for my purposes (merely
testing a GMail-like AJAXy web app) and I've got that. But I was
curious about how one might get accurate rates if you needed. What
project did you need such accuracy for? I imagine a real-time system.
What did you write the thread library in? C? Links?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Gábor Lehel
On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
chrisd...@googlemail.com wrote:
 On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com wrote:
 I'd like to have a template haskell function that take some constraints and
 a class name and write an empty class from those and relative empty instance
 to simulate typeclass synonyms.

 As I've never written TH and couldn't find a easily adaptable code around, I
 ask here for the code, or some hints on how to arrive there.

 I took Justin Bailey's haskelldb-th library as a TH example to work
 from and rewrote one TH function to try my hand at it, it's quite easy
 to follow with a simple example:

 http://hpaste.org/paste/41035/demo

 Maybe this is enough example to get you going. The rest you can find
 syntax parts from the TH Haddock documentation.

A useful FYI: the API docs are (almost) completely devoid of comments,
but if you click to see the source, it does have some additional
information in comments there, just not Haddock-formatted.


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




-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
Thanks. I annotated the function
http://hpaste.org/paste/41035/test_simpleclasssynonym
It seems to produce the right code.

How should I use the Parents synonym in my functions?

This is a noob question I suppose.

paolino


2010/11/1 Gábor Lehel illiss...@gmail.com

 On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
 chrisd...@googlemail.com wrote:
  On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com wrote:
  I'd like to have a template haskell function that take some constraints
 and
  a class name and write an empty class from those and relative empty
 instance
  to simulate typeclass synonyms.
 
  As I've never written TH and couldn't find a easily adaptable code
 around, I
  ask here for the code, or some hints on how to arrive there.
 
  I took Justin Bailey's haskelldb-th library as a TH example to work
  from and rewrote one TH function to try my hand at it, it's quite easy
  to follow with a simple example:
 
  http://hpaste.org/paste/41035/demo
 
  Maybe this is enough example to get you going. The rest you can find
  syntax parts from the TH Haddock documentation.

 A useful FYI: the API docs are (almost) completely devoid of comments,
 but if you click to see the source, it does have some additional
 information in comments there, just not Haddock-formatted.


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



 --
 Work is punishment for failing to procrastinate effectively.

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


[Haskell-cafe] Generating random tuples

2010-11-01 Thread Jacek Generowicz
I'm toying with generating random objects (for example tuples) and  
started wondering what pearls of wisdom Cafe might have on the matter.  
Two obvious points (relating to my toy code, shown below) are


1) The meaning of the limits required by randomR is not obvious for  
types such as tuples (you could come up with some definition, but it  
wouldn't be unique: how would you allow for different ones?[*]; you  
might decide that having such limits is nonsensical and not want to  
provide a randomR: would you then leave it undefinded?).


[*] I guess this is related to issues such as Num being both a sum and  
and product monoid.


2) I'm sure there are at least half a dozen prettier definitions of  
random.


But I suspect that the juicy bits will be in offerings about issues  
that I haven't even dreamed about.


Presumably QuickCheck's test-data generation mechanism would be  
interesting to look at in this context. Is there a gentle explanation  
of how it works somewhere?




Here's my initial effort:

import Control.Monad
import System.Random

main :: IO (Int, Int)
main = randomIO

instance (Random a, Random b) = Random (a, b) where
randomR = undefined
random g0 = let (i1,g1) = random g0
(i2,g2) = random g1
in ((i1,i2), g1)

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


Re: [Haskell-cafe] install GHC 7.0.1 RC on OS X?

2010-11-01 Thread Antoine Latter
On Mon, Nov 1, 2010 at 12:07 PM, Edward Amsden eca7...@cs.rit.edu wrote:
 I'd like to install the GHC 7.0.1 RC on my mac (Snow Leopard, x86_64),
 but I don't want it to run over my current GHC 6.12.2 install.

 If I use the .pkg installer, it doesn't allow me to select the
 destination, and I worry that it will overwrite my 6.12.2 install.

 If I try to build from source, that requires me to use my current GHC,
 which (as I understand) would build for 32 bit.

 What other options do I have, or am I misunderstanding something?

Does GHC 7 support 64 bit? For some reason I had thought it was still 32 bit.

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


Re: [Haskell-cafe] Generating random tuples

2010-11-01 Thread Daniel Fischer
On Monday 01 November 2010 19:18:33, Jacek Generowicz wrote:
 I'm toying with generating random objects (for example tuples) and
 started wondering what pearls of wisdom Cafe might have on the matter.
 Two obvious points (relating to my toy code, shown below) are

 1) The meaning of the limits required by randomR is not obvious for
 types such as tuples

But there's a pretty natural one, much like the Ix instance for tuples:

randomR ((x1,y1),(x2,y2)) g0 = ((x,y),g2)
  where
(x,g1) = randomR (x1,x2) g0
(y,g2) = randomR (y1,y2) g1

Of course, if there is an Ord instance, it would be tempting to use the 
limits as bounds for that, i.e.

randomR (p1,p2) g

should produce a pair p with p1 = p = p2, but that's not particularly 
nice to implement (in particular, if you don't want skewed sample 
distributions).

 (you could come up with some definition, but it
 wouldn't be unique: how would you allow for different ones?[*];

newtype

 you
 might decide that having such limits is nonsensical and not want to
 provide a randomR: would you then leave it undefinded?).

Yes.


 [*] I guess this is related to issues such as Num being both a sum and
 and product monoid.

 2) I'm sure there are at least half a dozen prettier definitions of
 random.

 But I suspect that the juicy bits will be in offerings about issues
 that I haven't even dreamed about.

 Presumably QuickCheck's test-data generation mechanism would be
 interesting to look at in this context. Is there a gentle explanation
 of how it works somewhere?



 Here's my initial effort:

 import Control.Monad
 import System.Random

 main :: IO (Int, Int)
 main = randomIO

 instance (Random a, Random b) = Random (a, b) where
  randomR = undefined
  random g0 = let (i1,g1) = random g0
  (i2,g2) = random g1
  in ((i1,i2), g1)

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


[Haskell-cafe] Haskellers browse users form

2010-11-01 Thread Yitzchak Gale
I'm using Safari on Snow Leopard.

On the Browse Users page on Haskellers,
there are little buttons that look like number spinners
on the two numerical fields, like Using Haskell since...

When I press one of those, the number
-1.7976931348623157e+308 appears in the field.

That must be Lennart.

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


Re: [Haskell-cafe] Generating random tuples

2010-11-01 Thread Nick Bowler
On 2010-11-01 19:18 +0100, Jacek Generowicz wrote:
 I'm toying with generating random objects (for example tuples) and  
 started wondering what pearls of wisdom Cafe might have on the matter.  
 Two obvious points (relating to my toy code, shown below) are
 
 1) The meaning of the limits required by randomR is not obvious for  
 types such as tuples (you could come up with some definition, but it  
 wouldn't be unique: how would you allow for different ones?[*]; you  
 might decide that having such limits is nonsensical and not want to  
 provide a randomR: would you then leave it undefinded?).

Indeed, the Random class has a fairly narrow everything fits on the
real line view of the world: not only is the talk about closed
intervals ambiguous in general, but so is the talk about uniform
distributions on those intervals.  That being said, there is an Ord
instance for tuples (a lexicographic ordering) and for this case I think
it would make the most sense to use that: select an element from the set
{ x : lo = x = hi }

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generating random tuples

2010-11-01 Thread Daniel Fischer
On Monday 01 November 2010 19:55:22, Nick Bowler wrote:
 On 2010-11-01 19:18 +0100, Jacek Generowicz wrote:
  I'm toying with generating random objects (for example tuples) and
  started wondering what pearls of wisdom Cafe might have on the matter.
  Two obvious points (relating to my toy code, shown below) are
 
  1) The meaning of the limits required by randomR is not obvious for
  types such as tuples (you could come up with some definition, but it
  wouldn't be unique: how would you allow for different ones?[*]; you
  might decide that having such limits is nonsensical and not want to
  provide a randomR: would you then leave it undefinded?).

 Indeed, the Random class has a fairly narrow everything fits on the
 real line view of the world: not only is the talk about closed
 intervals ambiguous in general, but so is the talk about uniform
 distributions on those intervals.  That being said, there is an Ord
 instance for tuples (a lexicographic ordering) and for this case I think
 it would make the most sense to use that: select an element from the set
 { x : lo = x = hi }

Really bad for

lo, hi :: (Int,Integer)
lo = (0,0)
hi = (3,4)

the product (partial) order seems much better to me.

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


Re: [Haskell-cafe] Generating random tuples

2010-11-01 Thread Nick Bowler
On 2010-11-01 20:09 +0100, Daniel Fischer wrote:
 On Monday 01 November 2010 19:55:22, Nick Bowler wrote:
  That being said, there is an Ord instance for tuples (a
  lexicographic ordering) and for this case I think it would make the
  most sense to use that: select an element from the set
  { x : lo = x = hi }
 
 Really bad for
 
 lo, hi :: (Int,Integer)
 lo = (0,0)
 hi = (3,4)

Good point, that's not so hot.

 the product (partial) order seems much better to me.

Indeed it does.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Yves Parès
Yes, I did make a small mistake in the type of eval.
In fact, through the compiler messages, I guessed that it was a problem of
matching between the 'rsc' type variable of runLoader and the 'rsc' of eval.
I thought that this kind of matching was automatic in Haskell, well I was
wrong... Thanks !


2010/11/1 Sjoerd Visscher sjo...@w3future.com

 Hi,

 There's nothing wrong with your type families. The problem is that the
 compiler doesn't know that the m and rsc of eval are the same as m and rsc
 of runLoader. (Also you had a small bug in the type of eval)

 You need the ScopedTypeVariables extension, with a forall on runLoader to
 tell GHC that they should be scoped:

 runLoader :: forall m rsc a. (Monad m, Resource rsc) = CfgOf (IdOf rsc) -
 RscLoader rsc m a - m a
 runLoader cfg loader = viewT loader = eval M.empty
  where
eval :: (Monad m, Resource rsc) =
 M.Map (IdOf rsc) rsc
  - ProgramViewT (EDSL (IdOf rsc)) m a
  - m a
eval _(Return x) = return x
eval rscs (instr := k) = case instr of
  Load id - do let loc = retrieveLoc cfg id
  -- open and load from loc will go here
  viewT (k ()) = eval rscs
  -- -- -- Other cases yet to come...

 greetings,
 Sjoerd


 On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:

  Hello,
 
  I'm trying to make a simple monad (built on operational's ProgramT) for
 resource loading.
  I have classes featuring type families :
 
  {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
 
  -- | A ResourceId is something that identifies a resource.
  -- It should be unique for one resource, and should be used to find the
 location (the path) of the resource,
  -- possibly by using a configuration datatype
  class (Ord id) = ResourceId id where
type LocOf id
type CfgOf id
retrieveLoc :: CfgOf id - id - LocOf id
 
  -- | Class describing a resource of type @rsc@
  class (ResourceId (IdOf rsc)) = Resource rsc where
type IdOf rsc
load   :: LocOf (IdOf rsc) - IO (Maybe rsc)
  -- ^ Called when a resource needs to be loaded
unload :: rsc - IO ()
  -- ^ Idem for unloading
 
  -- | Then, the operations that the loader can perform
  data EDSL id a where
Load :: id - EDSL id ()
IsLoaded :: id - EDSL id Bool
Unload   :: id - EDSL id ()
 
  -- | The loader monad itself
  type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
 
  -- | And finally, how to run a loader
  runLoader :: (Monad m, Resource rsc) = CfgOf (IdOf rsc) - RscLoader rsc
 m a - m a
  runLoader cfg loader = viewT loader = eval M.empty
where
  eval :: (Monad m, Resource rsc) =
   M.Map (IdOf rsc) rsc
   - ProgramViewT (EDSL rsc) m a
   - m a
  eval _(Return x) = return x
  eval rscs (instr := k) = case instr of
Load id - do let loc = retrieveLoc cfg id
-- open and load from loc will go here
viewT (k ()) = eval rscs
-- -- -- Other cases yet to come...
 
 
 
  Well, there is no way I can get it type-check. I think I must be misusing
 the type families (I tried with multi-param typeclasses and functional
 dependencies, but it ends up to be the same kind of nightmare...).
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

 --
 Sjoerd Visscher
 sjo...@w3future.com




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


Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Steffen Schuldenzucker
Hi Yves,

On 11/01/2010 09:44 PM, Yves Parès wrote:
 Yes, I did make a small mistake in the type of eval.
 In fact, through the compiler messages, I guessed that it was a problem of
 matching between the 'rsc' type variable of runLoader and the 'rsc' of eval.
 I thought that this kind of matching was automatic in Haskell, well I was
 wrong... Thanks !

Just out of curiosity: Does it work if you omit eval's type signature?

-- Steffen

 
 
 2010/11/1 Sjoerd Visscher sjo...@w3future.com mailto:sjo...@w3future.com
 
 Hi,
 
 There's nothing wrong with your type families. The problem is that the
 compiler doesn't know that the m and rsc of eval are the same as m and rsc
 of runLoader. (Also you had a small bug in the type of eval)
 
 You need the ScopedTypeVariables extension, with a forall on runLoader to
 tell GHC that they should be scoped:
 
 runLoader :: forall m rsc a. (Monad m, Resource rsc) = CfgOf (IdOf rsc)
 - RscLoader rsc m a - m a
 runLoader cfg loader = viewT loader = eval M.empty
  where
eval :: (Monad m, Resource rsc) =
 M.Map (IdOf rsc) rsc
 - ProgramViewT (EDSL (IdOf rsc)) m a
 - m a
eval _(Return x) = return x
eval rscs (instr := k) = case instr of
  Load id - do let loc = retrieveLoc cfg id
  -- open and load from loc will go here
  viewT (k ()) = eval rscs
  -- -- -- Other cases yet to come...
 
 greetings,
 Sjoerd
 
 
 On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:
 
  Hello,
 
  I'm trying to make a simple monad (built on operational's ProgramT) for
 resource loading.
  I have classes featuring type families :
 
  {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
 
  -- | A ResourceId is something that identifies a resource.
  -- It should be unique for one resource, and should be used to find the
 location (the path) of the resource,
  -- possibly by using a configuration datatype
  class (Ord id) = ResourceId id where
type LocOf id
type CfgOf id
retrieveLoc :: CfgOf id - id - LocOf id
 
  -- | Class describing a resource of type @rsc@
  class (ResourceId (IdOf rsc)) = Resource rsc where
type IdOf rsc
load   :: LocOf (IdOf rsc) - IO (Maybe rsc)
  -- ^ Called when a resource needs to be loaded
unload :: rsc - IO ()
  -- ^ Idem for unloading
 
  -- | Then, the operations that the loader can perform
  data EDSL id a where
Load :: id - EDSL id ()
IsLoaded :: id - EDSL id Bool
Unload   :: id - EDSL id ()
 
  -- | The loader monad itself
  type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
 
  -- | And finally, how to run a loader
  runLoader :: (Monad m, Resource rsc) = CfgOf (IdOf rsc) - RscLoader
 rsc m a - m a
  runLoader cfg loader = viewT loader = eval M.empty
where
  eval :: (Monad m, Resource rsc) =
   M.Map (IdOf rsc) rsc
   - ProgramViewT (EDSL rsc) m a
   - m a
  eval _(Return x) = return x
  eval rscs (instr := k) = case instr of
Load id - do let loc = retrieveLoc cfg id
-- open and load from loc will go here
viewT (k ()) = eval rscs
-- -- -- Other cases yet to come...
 
 
 
  Well, there is no way I can get it type-check. I think I must be
 misusing the type families (I tried with multi-param typeclasses and
 functional dependencies, but it ends up to be the same kind of 
 nightmare...).
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 --
 Sjoerd Visscher
 sjo...@w3future.com mailto:sjo...@w3future.com
 
 
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Yves Parès
 Just out of curiosity: Does it work if you omit eval's type signature?

In fact you can't omit it since EDSL is a GADT.
I don't know why there is this restriction, but it is written in
operational's documentation:
http://hackage.haskell.org/packages/archive/operational/0.2.0.1/doc/html/Control-Monad-Operational.html
(At the very bottom of the page)


But there still must be something I don't get :
I tried to merge the two classes ResourceId and Resource in only one
Resource class, which leads to a few changes in runLoader :

{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs, ScopedTypeVariables #-}

import qualified Data.Map as M
import Control.Monad.Operational

-- | A ResourceId is something that identifies a resource.
-- It should be unique for one resource, and should be used to find the
location (the path) of the resource,
-- possibly by using a configuration datatype
--class (Ord id) = ResourceId id where

-- | Class describing a resource of type @rsc@
class (Ord (IdOf rsc)) = Resource rsc where
  type IdOf rsc
  type LocOf rsc
  type CfgOf rsc
  retrieveLoc :: CfgOf rsc - IdOf rsc - LocOf rsc
  load   :: LocOf rsc - IO (Maybe rsc)
-- ^ Called when a resource needs to be loaded
  unload :: rsc - IO ()
-- ^ Idem for unloading

-- | Then, the operations that the loader can perform
data EDSL id a where
  Load :: id - EDSL id ()
  IsLoaded :: id - EDSL id Bool
  Unload   :: id - EDSL id ()

-- | The loader monad itself
type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a

-- | And finally, how to run a loader
runLoader :: forall m rsc a. (Monad m, Resource rsc)
  = CfgOf rsc - RscLoader rsc m a - m a
runLoader cfg loader = viewT loader = eval M.empty
  where
eval :: (Monad m, Resource rsc)
 = M.Map (IdOf rsc) rsc
 - ProgramViewT (EDSL (IdOf rsc)) m a
 - m a
eval _(Return x) = return x
eval rscs (instr := k) = case instr of
*  Load id - do let loc = retrieveLoc cfg id*
-- open and load from loc will go here
viewT (k ()) = eval rscs
  -- -- -- Other cases yet to come...


This leads to new errors with 'IdOf rsc' and 'CfgOf rsc' :

GameBasics/Resources.hs:46:42:
Couldn't match expected type `CfgOf rsc'
   against inferred type `CfgOf rsc1'
  NB: `CfgOf' is a type function, and may not be injective
In the first argument of `retrieveLoc', namely `cfg'
In the expression: retrieveLoc cfg id
In the definition of `loc': loc = retrieveLoc cfg id

GameBasics/Resources.hs:46:46:
Couldn't match expected type `IdOf rsc'
   against inferred type `IdOf rsc1'
  NB: `IdOf' is a type function, and may not be injective
In the second argument of `retrieveLoc', namely `id'
In the expression: retrieveLoc cfg id
In the definition of `loc': loc = retrieveLoc cfg id

Seems like the compiler still has a 'rsc1' type despite the scoped type
variable 'rsc'.


2010/11/1 Yves Parès limestr...@gmail.com

 Yes, I did make a small mistake in the type of eval.
 In fact, through the compiler messages, I guessed that it was a problem of
 matching between the 'rsc' type variable of runLoader and the 'rsc' of eval.
 I thought that this kind of matching was automatic in Haskell, well I was
 wrong... Thanks !


 2010/11/1 Sjoerd Visscher sjo...@w3future.com

 Hi,

 There's nothing wrong with your type families. The problem is that the
 compiler doesn't know that the m and rsc of eval are the same as m and rsc
 of runLoader. (Also you had a small bug in the type of eval)

 You need the ScopedTypeVariables extension, with a forall on runLoader to
 tell GHC that they should be scoped:

 runLoader :: forall m rsc a. (Monad m, Resource rsc) = CfgOf (IdOf rsc)
 - RscLoader rsc m a - m a
 runLoader cfg loader = viewT loader = eval M.empty
  where
eval :: (Monad m, Resource rsc) =
 M.Map (IdOf rsc) rsc
  - ProgramViewT (EDSL (IdOf rsc)) m a
  - m a
eval _(Return x) = return x
eval rscs (instr := k) = case instr of
  Load id - do let loc = retrieveLoc cfg id
  -- open and load from loc will go here
  viewT (k ()) = eval rscs
  -- -- -- Other cases yet to come...

 greetings,
 Sjoerd


 On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:

  Hello,
 
  I'm trying to make a simple monad (built on operational's ProgramT) for
 resource loading.
  I have classes featuring type families :
 
  {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
 
  -- | A ResourceId is something that identifies a resource.
  -- It should be unique for one resource, and should be used to find the
 location (the path) of the resource,
  -- possibly by using a configuration datatype
  class (Ord id) = ResourceId id where
type LocOf id
type CfgOf id
retrieveLoc :: CfgOf id - id - LocOf id
 
  -- | Class describing a resource of type @rsc@
  class (ResourceId (IdOf rsc)) = Resource rsc where
type IdOf 

Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
I think I've got something nice in the end.

http://hpaste.org/41042/classsynonymhs

example:

class  (ParteDi (Servizio a) s
,Read a
,Eq a
, Show a
, Integer `ParteDi` s
) = SClass s a

$(classSynonym ''SClass)

ghci :i SClass command is printing some strange type variables but it
compiles

paolino

2010/11/1 Gábor Lehel illiss...@gmail.com

 On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done
 chrisd...@googlemail.com wrote:
  On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com wrote:
  I'd like to have a template haskell function that take some constraints
 and
  a class name and write an empty class from those and relative empty
 instance
  to simulate typeclass synonyms.
 
  As I've never written TH and couldn't find a easily adaptable code
 around, I
  ask here for the code, or some hints on how to arrive there.
 
  I took Justin Bailey's haskelldb-th library as a TH example to work
  from and rewrote one TH function to try my hand at it, it's quite easy
  to follow with a simple example:
 
  http://hpaste.org/paste/41035/demo
 
  Maybe this is enough example to get you going. The rest you can find
  syntax parts from the TH Haddock documentation.

 A useful FYI: the API docs are (almost) completely devoid of comments,
 but if you click to see the source, it does have some additional
 information in comments there, just not Haddock-formatted.


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



 --
 Work is punishment for failing to procrastinate effectively.

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


Re: [Haskell-cafe] Parsing workflow

2010-11-01 Thread Andrew Coppin

On 31/10/2010 04:15 PM, Nils Schweinsberg wrote:
This is exactly what gives me headaches. It's hard to tell where you 
need try/lookAhead and where you don't need them. And I don't really 
feel comfortable wrapping everything into try blocks...


I vaguely recall somebody mentioning a parser library on Hackage where 
try is the default behaviour and you turn it off explicitly, rather 
than turning it on explicitly. Apparently this is much more intuitive. 
But unfortunately I can't remember what the hell the library was...


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


[Haskell-cafe] Mysterious fact

2010-11-01 Thread Andrew Coppin

The other day, I accidentally came up with this:

|{-# LANGUAGE RankNTypes #-}

type  Either  x y=  forall r.  (x -  r) -  (y -  r) -  r

left :: x -  Either  x y
left x f g=  f x

right :: y -  Either  x y
right y f g=  g y

|

This is one example; it seems that just about any algebraic type can be 
encoded this way. I presume that somebody else has thought of this 
before. Does it have a name?


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


Re: [Haskell-cafe] Mysterious fact

2010-11-01 Thread Jeremy Shaw

Looks a lot like Church encoding to me:

http://en.wikipedia.org/wiki/Church_encoding

It was first discovered by the guy who invented lambda calculus :p

- jeremy

On Nov 1, 2010, at 5:28 PM, Andrew Coppin wrote:


The other day, I accidentally came up with this:

{-# LANGUAGE RankNTypes #-}

type Either x y = forall r. (x - r) - (y - r) - r

left :: x - Either x y
left x f g = f x

right :: y - Either x y
right y f g = g y

This is one example; it seems that just about any algebraic type can  
be encoded this way. I presume that somebody else has thought of  
this before. Does it have a name?


___
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] Mysterious fact

2010-11-01 Thread Henning Thielemann


On Mon, 1 Nov 2010, Andrew Coppin wrote:


The other day, I accidentally came up with this:

{-# LANGUAGE RankNTypes #-}

type Either x y = forall r. (x - r) - (y - r) - r

left :: x - Either x y
left x f g = f x

right :: y - Either x y
right y f g = g y

This is one example; it seems that just about any algebraic type can be encoded 
this
way. I presume that somebody else has thought of this before. Does it have a 
name?


http://www.haskell.org/haskellwiki/Functions_not_data_structures

The article could be more informative. This was asked several times in 
Haskell-Cafe, thus it should certainly be Category:FAQ - but with what 
title?

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


Re: [Haskell-cafe] Parsing workflow

2010-11-01 Thread Ozgur Akgun
On 1 November 2010 22:18, Andrew Coppin andrewcop...@btinternet.com wrote:

 I vaguely recall somebody mentioning a parser library on Hackage where
 try is the default behaviour and you turn it off explicitly, rather than
 turning it on explicitly. Apparently this is much more intuitive. But
 unfortunately I can't remember what the hell the library was...


polyparse, is it?

from http://code.haskell.org/~malcolm/polyparse/docs/index.html#what

 If you have only ever used the parsec combinators before, then you might be

pleasantly surprised by polyparse: all of the same functionality is
 available,

but it removes the confusion that all too commonly arises from a failure to

use parsec's try combinator correctly. Ambiguous grammars often fail to be

compositional in parsec, and it can be a black art guessing where to
 introduce

a try to fix it. In contrast, polyparsers are by default fully
 compositional.

It is possible to improve their efficiency (and the accuracy of error

messages) by inserting commits (which are the dual of try), but it is not

necessary for writing a correct parser, and furthermore, it is usually
 obvious

where it can be beneficial to add a commit.


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


Re: [Haskell-cafe] Mysterious fact

2010-11-01 Thread Dan Doel
On Monday 01 November 2010 6:40:30 pm Jeremy Shaw wrote:
 Looks a lot like Church encoding to me:
 
 http://en.wikipedia.org/wiki/Church_encoding
 
 It was first discovered by the guy who invented lambda calculus :p

Also, if you're interested in this, you can read Proofs and Types by Girard 
(not an easy read). In it, (I think) he notes, and probably proves, that you 
can encode any inductive type in System F (which is relatively close to 
Haskell with rank-n types) by this method (that is, it has the right types; of 
course it works in the untyped lambda calculus, too, but not in, say, the 
simply typed lambda calculus).

You can also encode coinductive types:

  nu F = exists s. s * (s - F s)

  exists s. T[s] = forall r. (forall s. T[s] - r) - r

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


Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Antoine Latter
2010/11/1 Paolino paolo.verone...@gmail.com:
 I think I've got something nice in the end.

 http://hpaste.org/41042/classsynonymhs

 example:

 class  (    ParteDi (Servizio a) s
         ,    Read a
         ,    Eq a
         ,     Show a
         ,     Integer `ParteDi` s
         ) ⇒ SClass s a

 $(classSynonym ''SClass)

 ghci :i SClass command is printing some strange type variables but it
 compiles


Template Haskell might be overkill for this. In the past, I've done:

 class (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b
 instance (Eq b, Show b, MyClass b, MyOtherClass b) = MySynonym b

I think this requires a couple of GHC extensions, but TemplateHaskell
is an extension as well. Maybe there are pitfalls with this approach.

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


[Haskell-cafe] windows network programming

2010-11-01 Thread Michael Litchard
I took a quick look on hackage for an interface to windows networking
function calls, and didn't find anything that worked. I may have
overlooked something. What's the state of windows network programming?
Any recommendations for a good package?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] windows network programming

2010-11-01 Thread Antoine Latter
Have you tried the 'network' package on Hackage? I had thought it was
cross-platform. I do not do much development on Windows.
On Nov 1, 2010 6:45 PM, Michael Litchard mich...@schmong.org wrote:
 I took a quick look on hackage for an interface to windows networking
 function calls, and didn't find anything that worked. I may have
 overlooked something. What's the state of windows network programming?
 Any recommendations for a good package?
 ___
 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] windows network programming

2010-11-01 Thread Paulo Tanimoto
On Mon, Nov 1, 2010 at 7:04 PM, Antoine Latter aslat...@gmail.com wrote:
 Have you tried the 'network' package on Hackage? I had thought it was
 cross-platform. I do not do much development on Windows.

 On Nov 1, 2010 6:45 PM, Michael Litchard mich...@schmong.org wrote:
 I took a quick look on hackage for an interface to windows networking
 function calls, and didn't find anything that worked. I may have
 overlooked something. What's the state of windows network programming?
 Any recommendations for a good package?

Yes, I think it is cross-platform and it ships with Haskell Platform
(so you don't have to compile by yourself).

http://hackage.haskell.org/platform/contents.html

Michael, also note that the newest version on Hackage merges network
and network-bytestring.

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

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


[Haskell-cafe] Is Curry alive?

2010-11-01 Thread Gregory Crosswhite

 Hey everyone,

This is a little off-topic, but I just ran into a problem which might 
benefit from being attacked by a logic language, so I've been looking 
for a good one to try out --- and hopefully one that has a very 
efficient implementation since I want to iterate through billions and 
possibly trillions of nondeterministically generated solutions.  I was 
thinking about using Curry, but it looks to me like the language is dead 
and hasn't seen much activity for a few years.  Does anyone know about 
whether there is still much going on over there?  Or, alternatively, do 
you have any suggestions regarding other logic language/implementations 
I should check out?  I've also been looking at Prolog but I am having 
trouble seeing whether I can process N non-deterministic solutions in 
O(1) space (rather than first generating a O(N) size list), and I 
checked out Mercury but the documentation for it is a bit sparse.


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


Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Ryan Ingram
This one is easy:

 -- | Class describing a resource of type @rsc@
 class (Ord (IdOf rsc)) = Resource rsc where
   type IdOf rsc
   type LocOf rsc
   type CfgOf rsc
   retrieveLoc :: CfgOf rsc - IdOf rsc - LocOf rsc
   load   :: LocOf rsc - IO (Maybe rsc)
 -- ^ Called when a resource needs to be loaded
   unload :: rsc - IO ()
 -- ^ Idem for unloading

Consider this:

instance Resource () where
   type IdOf () = Int
   type LocOf () = String
   type CfgOf () = ()
   retrieveLoc () n = Unit_ ++ show n
   load = undefined
   unload = undefined

instance Resource Int where
   type IdOf () = Int
   type LocOf () = String
   type CfgOf () = ()
   retrieveLoc () n = Int_  ++ show n
   load = undefined
   unload = undefined

foo = retrieveLoc :: () - Int - String  -- which retrieveLoc is called here?

The problem, in case you haven't surmised it, is that retrieveLoc is
ambiguous; you can never call it!  There's no way to know which
instance you might be referring to.  You can work around it by making
one of the type families into a data family (which is injective; you
know that if CfgOf x = CfgOf y, then x = y).  Or you can add a proxy
parameter to retrieveLoc:

 data Proxy a = Proxy
 retrieveLoc :: Proxy rsc - CfgOf rsc - IdOf rsc - LocOf rsc

now:

 foo = retrieveLoc (Proxy :: Proxy ())

and ghc can correctly infer foo's type as
 foo :: () - Int - String

and foo will call the retrieveLoc from the () instance.

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


Re: [Haskell-cafe] Is Curry alive?

2010-11-01 Thread Richard O'Keefe

On 2/11/2010, at 1:27 PM, Gregory Crosswhite wrote:

 Hey everyone,
 
 This is a little off-topic, but I just ran into a problem which might benefit 
 from being attacked by a logic language,

Why not describe the problem?

 so I've been looking for a good one to try out --- and hopefully one that has 
 a very efficient implementation since I want to iterate through billions and 
 possibly trillions of nondeterministically generated solutions.

I think about the practical success of Model Checking, and wonder whether it
might be better NOT to iterate through so many.

 I've also been looking at Prolog but I am having trouble seeing whether I can 
 process N non-deterministic solutions in O(1) space (rather than first 
 generating a O(N) size list),

The point of backtracking search is that you need only space for the current
candidate solution, not for all solutions visited so far.  So much so that the
Iterative Deepening family of search algorithms cheerfully *revisit* graph nodes
in order to save time over all.

 and I checked out Mercury but the documentation for it is a bit sparse.
Packl
The Mercury documentation I downloaded in March comes to 773 pages.

faq.pdf   6 pages
library.pdf 470 pages
reference_manual.pdf150 pages
transition_guide.pdf 10 pages (Mercury for Prolog programmers)
user_guide.pdf  137 pages

Packing the tutorial into a single HTML file gives another 19 pages.
Ralph Beckett's tutorial adds another 53 pages of PDF.

So that's 845 pages all up.  sparse?



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


[Haskell-cafe] Is let special?

2010-11-01 Thread Günther Schmidt

Hi all,

is there something special about let? I don't mean only its use in 
haskell, but in the general context of programming languages.


I've been given a few hints over time when I asked question concerning 
DSLs but regretfully didn't follow them up.


Günther

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


Re: [Haskell-cafe] Is let special?

2010-11-01 Thread Ivan Lazar Miljenovic
2010/11/2 Günther Schmidt gue.schm...@web.de:
 Hi all,

 is there something special about let? I don't mean only its use in
 haskell, but in the general context of programming languages.

It means whatever the language specification/definition/implementation
says it means.  It's usually used for some kind of name binding
however (there might be some language theory definition of let, but I
wouldn't know).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Curry alive?

2010-11-01 Thread Gregory Crosswhite

 On 11/01/2010 06:19 PM, Richard O'Keefe wrote:

On 2/11/2010, at 1:27 PM, Gregory Crosswhite wrote:


Hey everyone,

This is a little off-topic, but I just ran into a problem which might benefit 
from being attacked by a logic language,

Why not describe the problem?



My goal is to exhaustively search through a space in order to categorize 
all of the elements in that space.  This space is combinatorial, so I am 
looking for a good domain specific language for letting me break up the 
space into a bunch of generators which can be combined combinatorically 
to generate the list of elements in the space.  What makes the 
generators non-trivial is that I am choosing them carefully in order to 
eliminate many symmetries of the problem that effectively result in 
equivalent/redundant elements of the search space, and a consequence of 
this is that some generators depend on the results of other generators.  
The combinatorics of the problem are such that there are about a billion 
elements in the space if I try tackling a small version of my problem, 
and a trillion if I try tackling a slightly larger version of my problem.


(More background:  The elements in this space are choices of quantum 
measurement operators which are used to implement a quantum 
error-correcting code, and I am interested in knowing if the code is 
good or not.  My goal is to systematically search through all codes 
with a small (= 5-6) number of qubits in order to be able to classify 
all of the possible of error-correcting codes one can implement using 
that many qubits.)


It is worth mentioning that the function I am applying to these elements 
to compute the desired properties is very fast.  I have had benchmarks 
showing the ability for this function to scan through up to ~ 500,000 
elements a second (It helps that it is written in C++ :-) ).


Actually, the more that I think about my problem the more that I'm 
thinking I should just stick with the List monad.  This gives me a way 
to create generators that can rely on the results of other generators 
and put them all together using the List monad, taking advantage of 
Haskell's laziness to iterate in O(1) space.  Which does raise the 
question: when is it better to use a logic programming language instead 
of the list monad?



so I've been looking for a good one to try out --- and hopefully one that has a 
very efficient implementation since I want to iterate through billions and 
possibly trillions of nondeterministically generated solutions.

I think about the practical success of Model Checking, and wonder whether it
might be better NOT to iterate through so many.



What exactly do you mean by Model Checking?

Anyway, there might be more clever ways to eliminate possibilities from 
my space (other than the ones I have already) but the advantage of 
having a computer search all of it is that it can scan through all of 
the millions and even billions of possibilities in a stupid brute-force 
fashion in less time than it takes for me to come up with a clever way 
to analyze the space using theoretical analysis.  :-)



I've also been looking at Prolog but I am having trouble seeing whether I can 
process N non-deterministic solutions in O(1) space (rather than first 
generating a O(N) size list),

The point of backtracking search is that you need only space for the current
candidate solution, not for all solutions visited so far.  So much so that the
Iterative Deepening family of search algorithms cheerfully *revisit* graph nodes
in order to save time over all.



Yes, exactly, but my point is that in Prolog I am having trouble 
figuring out if there is a way to iterate over all of the solutions 
generated non-deterministically in O(1) space because all of the library 
functions which run an accumulator over a generated set of results seem 
to operate by first generating the full list and then accumulating over 
it which takes O(n) space, which is wasteful since as you point out it 
should only take O(1) space to do this.  However, it is also possible 
that I misunderstand the semantics of how Prolog works and so things 
which look like O(n) to me are actually O(1) --- similar to laziness in 
Haskell.




and I checked out Mercury but the documentation for it is a bit sparse.

Packl
The Mercury documentation I downloaded in March comes to 773 pages.

faq.pdf   6 pages
library.pdf 470 pages
reference_manual.pdf150 pages
transition_guide.pdf 10 pages (Mercury for Prolog programmers)
user_guide.pdf  137 pages

Packing the tutorial into a single HTML file gives another 19 pages.
Ralph Beckett's tutorial adds another 53 pages of PDF.

So that's 845 pages all up.  sparse?



a bit sparse?


Yes, because although there is a tutorial with the trivial stuff, and a 
references for people who already know what they are doing, there is not 
much intermediate-level documentation for someone who understands the 
basic ideas behind the language 

Re: [Haskell-cafe] Reference for technique wanted

2010-11-01 Thread Richard O'Keefe

On 1/11/2010, at 10:37 PM, Claus Reinke wrote:
 
 Interesting discussion. I still think it is the same idea,
 namely to represent not-yet-known list tails by variables,
 embedded into two different kinds of languages.
 
   \rest-start++rest
   [start|rest]\rest-- '\' is an infix constructor

Savvy Prolog programmers wouldn't *DREAM* of
using an infix constructor here.  The art of doing list
differences well in Prolog is to think of a list difference
as a RELATIONSHIP between TWO terms, not as a single data
structure.  (The same is true for the queue example I mentioned.
Keeping the length, the front, and the back as separate arguments
gives usefully better performance.)

 
 The differences arise from the different handling of
 variables and scoping in those languages:
 
 - functional languages: explicit, local scopes, variables
   are bound by injecting values from outside the scope
   (applying the binding construct to values); scoped
   expressions can be copied, allowing multiple
   instantiations of variables
 
 - logic languages: implicit, global scopes, variables
   are bound by finding possible values inside the scope

Eh?  The scope of *identifiers* is strictly LOCAL in Prolog.
Logic *variables* don't *have* scope.

 So, yes, the realization of the idea is different, as are the
 language frameworks, and the junk in the representations,
 but the idea is the same.

In an extremely vague and not obviously useful sense.
This is rather like saying that association lists and hash
tables are both implementations of the finite map idea,
so we might as well call them by the same name.

The algorithmic and observability properties of the two approaches
are very different.

Since there already is a DList implementation for Haskell,
I decided to write one for SML.  It was very frustrating,
because while everything is possible, almost nothing is easy.
Many of the functions degenerated into

fun foo x ... = fromList (List.foo (toList x) ...)

and this included head and tail.  Afterwards, looking at
Data.DList to find out what clever trick I had missed, I was
glumly pleased to find out there wasn't one:  head and tail are
O(size of list) in Data.DList too.

The bottom line for anything that's supposed to make concatenation
fast is that it ought to be able to make singleton and ++ fast.
So I tried a test case.

datatype tree = LEAF of int | FORK of (tree * tree);

For SML/NJ I used a full binary tree of depth 22;
for MLton  I used a full binary tree of depth 25.

SML/NJ MLton
 0.899 0.244boring old plain list
 5.481 1.244build a raum using raums
 8.186 1.380build a raum then convert it to a list
12.581 4.449build a dlist using dlists
16.209 5.096build a dlist then convert it to a list

Times were measured on an Intel Core 2 Duo Mac running
Mac OS X 10.6.4, SSML/NJ v110.70 [built: Wed Jun 17 16:24:00 2009]
MLton MLTONVERSION (built Mon Jun 15 11:10:01 CDT 2009 on fenrir.uchicago.edu)

Building a list using dlists is 16 (SML/NJ) or 20 (MLton) times
slower than using a plain list.

Caveat:  because raums handle reverse in O(1) time as well as
concatenation, for a fair comparison I made dlists do the same,
so
type 'x dlist = bool - 'x list - 'x list

fun fromList xs flag tail =
if flag then xs @ tail else List.revAppend(xs, tail)


fun list_flatten t = 
let fun flat (LEAF x) ys = x :: ys
  | flat (FORK(a,b)) ys = flat a (flat b ys)
 in flat t []
end

fun raum_flat (LEAF x)= Raum.singleton x
  | raum_flat (FORK(a,b)) = Raum.cat (raum_flat a) (raum_flat b)

fun raum_flatten t = Raum.toList (raum_flat t)

fun dlist_flat (LEAF x)= DList.singleton x
  | dlist_flat (FORK(a,b)) = DList.cat (dlist_flat a) (dlist_flat b)

fun dlist_flatten t = DList.toList (dlist_flat t)

 To close the circle: I understand that difference lists in
 Prolog might have been a declarative translation of
 in-place updating in Lisp lists:-)

It seems unlikely.  Prolog was born as a grammar formalism
(metamorphosis grammars) and the idea of a non-terminal as
a relation between a (starting point, end point) pair owes
nothing to Lisp.

I mean, do you call parser combinators in Haskell a
declarative translation of in-place updating in Lisp lists?
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is let special?

2010-11-01 Thread Richard O'Keefe
As syntax, let goes back at least to ISWIM.
As for there being something special, Milner's algorithm for
type checking/inference in SML had to treat let specially.


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


[Haskell-cafe] Re: Haskellers browse users form

2010-11-01 Thread Michael Snoyman
Alright, I've brushed up on my HTML5 form fields a bit and added
appropriate min, max and step attributes for those fields, as well as
the Haskeller since field in the profile. Let me know if you still
have any problems with it.

Thanks,
Michael

On Mon, Nov 1, 2010 at 8:47 PM, Yitzchak Gale g...@sefer.org wrote:
 I'm using Safari on Snow Leopard.

 On the Browse Users page on Haskellers,
 there are little buttons that look like number spinners
 on the two numerical fields, like Using Haskell since...

 When I press one of those, the number
 -1.7976931348623157e+308 appears in the field.

 That must be Lennart.

 Thanks,
 Yitz

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