Re: [Haskell-cafe] Thread scheduling

2010-06-11 Thread David Powell
On Fri, Jun 11, 2010 at 3:34 PM, Luke Palmer lrpal...@gmail.com wrote:

 Say, using System.Time.getClockTime.

 Luke

 On Thu, Jun 10, 2010 at 11:31 PM, Luke Palmer lrpal...@gmail.com wrote:
  On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin
  andrewcop...@btinternet.com wrote:
  Control.Concurrent provides the threadDelay function, which allows you
 to
  make the current thread sleep until T=now+X. However, I can't find any
 way
  of making the current thread sleep until T=X. In other words, I want to
  specify an absolute wakeup time, not a relative one.
 
  Modulo a small epsilon between the two actions, can't you just get the
  current time and subtract it from the target time?  threadDelay is
  allowed to delay for too long anyway, so doing it this way does not
  lose you any correctness.
 
  Luke
 


This is a slightly different issue, but isn't there a potential problem with
threadDelay?  I noticed that internally threadDelay uses gettimeofday() as
the absolute time source (on linux at least).   Isn't there potential
problem with this since wall-clock time isn't guaranteed to be monotonic
increasing?  On linux, I'd have thought the right thing to do would be to
use clock_gettime(CLOCK_MONOTONIC) although that is probably not very
portable.

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


[Haskell-cafe] CGI differences FastCGI

2010-06-11 Thread Jonas Fager
Hi.

This is probably I must be blind department

I have a very basic strip down echo cgi that runs with apache2.

When I try to modfi it to be a FastCGI instead and run it with spawn-fcgi
with nginx
It don't behave as expected.
I suppose that the line that don't get any data is mn -  getInputFPS file
when running under FastGCI.
So is the code wrong? or have I missed something with the setup?

I can run the example of fastcgi provided in
http://mult.ifario.us/p/wiring-haskell-into-a-fastcgi-web-server with no
problem.


Description:Ubuntu 10.04 LTS
2.6.32-22-generic-pae #36-Ubuntu SMP
The Glorious Glasgow Haskell Compilation System, version 6.12.1

+
import Control.Concurrent
import Network.CGI
-- import Network.FastCGI
import Text.Html
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString.Lazy.Char8 as BS8
import Control.Monad (liftM)
import Data.Maybe (fromJust)
import Char
import Data.List
import System.Time
import qualified Data.ByteString.Char8 as C
import Text.JSON.Generic
import Text.JSON

insertthis fb =  do
  let f = BS8.unpack  fb
  return (f)




fileForm = form ! [method post, enctype multipart/form-data]
  [textfield file, submit  Upload]



saveFile cont =
do r-liftIO $ insertthis  cont
   return $ paragraph  (Inserted  ++ (show r))

page t b = header  thetitle  t +++ body  b




test :: CGI CGIResult
test = do setHeader Content-Type text/html; charset=utf-8
  mn -  getInputFPS file
  h - maybe (return fileForm) saveFile mn
  output $  renderHtml $ page Upload h


main = runCGI $ handleErrors test

--main= runFastCGI $ handleErrors test

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


[Haskell-cafe] Re: Help with Bird problem 3.3.3

2010-06-11 Thread Heinrich Apfelmus
Günther Schmidt wrote:
 
 I'm just re-reading the book again, this time doing the exercises though :)
 
 Is there a site with solutions for the exercises?

Unless you count the haskell-cafe and beginners mailing lists as sites,
I don't know any sites which have the solutions. ;)


Problem 3.3.3: Construct a program for division from the specification

  (m * n) / n = m

and prove that it's correct.


Sketch of a solution: To define  a / n , the usual approach of
subtracting  n  from the first argument until something less than  n
remains will work. Correctness can then be proven by induction on  m .



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] Re: How to Show an Operation?

2010-06-11 Thread Daniel Fischer
On Friday 11 June 2010 07:47:03, Martin Drautzburg wrote:
 On Friday, 11. June 2010 00:12:03 Daniel Fischer wrote:

 Thanks Daniel.

  Upgrade. We're at 6.12 now!

 Did that. Everything is available now.

 I am still having trouble with the test function. First it seems I need
 braces, so I can mix == and *.
 test :: Num a
  = (a - a) - (a - a) - (a - a) - [String]
 test f g h = do
 [f', g', h'] - permutations [Named f f, Named g g, Named h h]
 guard $ namedPure 42 == (f' * g' * h' * namedPure 42)
 return $ show f' ++  .  ++ show g' ++  .  ++ show h'

 But this leads to

 Occurs check: cannot construct the infinite type:
   a = (a - a) - a1 - t
 When generalising the type(s) for `test'

Ah, yes, (*) is left associative (infixl 4, hence you also need the 
parentheses since (==) is infix 4; same fixity and different 
associativities don't mix), here it must be associated to the right,

namedPure 42 == (f' * (g' * (h' * namedPure 42)))

:(

If you'd want to use it a lot, define a right associative alias with higher 
fixity:

infixr 5 *

(*) = (*)


 This error message is still the maximum penalty for me (along with
 Corba marshall exception in J2EE and Missing right parenthesis in
 Oracle SQL)

 Then generally speaking, I have the feeling that this code does not
 allow namifying existing code either. In this respect it does not seem
 to do better than the apply method pattern discussed earlier in this
 thread.

You'd have to rewrite; either way.


 The problem it solves is very simple and therefore using (*) and
 namedPure isn't much of a drawback. But if I had tons of code to namify
 I would still have to do significant changes to it, right?

Yes.

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-11 Thread Luke Palmer
On Thu, Jun 10, 2010 at 2:10 PM, Maciej Piechotka uzytkown...@gmail.com wrote:
 data Named a = Named String a

 instance Functor Named where
    f `fmap` (Named s v) = Named s (f v)

 instance Applicative Named where
    pure x = Named  x
    (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

This is not technically a legal applicative instance, because it is
not associative.  This can be seen when you try to clean up the usage
as we have been discussing:

g . f = liftA2 (.) g f

f = Named f (+1)
g = Named g (*2)
h = Named h (^3)

ghci f * (g * (h * namedPure 42))
f(g(h(42)))
ghci (f . g . h) * namedPure 42
f(g)(h)(42)

The Applicative laws are supposed to guarantee that this refactor is
legal.  Of course, the latter answer is nonsense.

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


[Haskell-cafe] threadDelay correctness

2010-06-11 Thread Roman Cheplyaka
* David Powell da...@drp.id.au [2010-06-11 16:09:55+1000]
 This is a slightly different issue, but isn't there a potential problem with
 threadDelay?  I noticed that internally threadDelay uses gettimeofday() as
 the absolute time source (on linux at least).   Isn't there potential
 problem with this since wall-clock time isn't guaranteed to be monotonic
 increasing?  On linux, I'd have thought the right thing to do would be to
 use clock_gettime(CLOCK_MONOTONIC) although that is probably not very
 portable.

Good point -- I remember xmobar hanging after adjusting clock. Seems
like this is the cause.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Roman Cheplyaka
* Günther Schmidt gue.schm...@web.de [2010-06-11 01:22:27+0200]
 there is nothing wrong with ifs as such except the won't actually
 exit a long piece of code, the computation will continue, just in a
 useless way.

Can you clarify?

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-11 Thread Daniel Fischer
On Friday 11 June 2010 11:50:55, Luke Palmer wrote:
 On Thu, Jun 10, 2010 at 2:10 PM, Maciej Piechotka uzytkown...@gmail.com 
wrote:
  data Named a = Named String a
 
  instance Functor Named where
     f `fmap` (Named s v) = Named s (f v)
 
  instance Applicative Named where
     pure x = Named  x
     (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 This is not technically a legal applicative instance, because it is
 not associative.

Good spot.

I think

(Named s f) * (Named t v) = Named (s ++  $  ++ t) (f v)

fixes it.

 This can be seen when you try to clean up the usage
 as we have been discussing:

 g . f = liftA2 (.) g f

 f = Named f (+1)
 g = Named g (*2)
 h = Named h (^3)

 ghci f * (g * (h * namedPure 42))
 f(g(h(42)))
 ghci (f . g . h) * namedPure 42
 f(g)(h)(42)

 The Applicative laws are supposed to guarantee that this refactor is
 legal.  Of course, the latter answer is nonsense.

 Luke

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


[Haskell-cafe] Re: package naming policy

2010-06-11 Thread Henning Thielemann


On Tue, 8 Jun 2010, Don Stewart wrote:


Great points: I've added them to this wiki page of for and against
points:

   http://haskell.org/haskellwiki/Libraries/WhenToRewriteOrRename

Please add points as you see fit, and maybe we can come up with a
mitigation/change plan.


Closely related is the question of module names. 
'transformers'+'monads-fd' are somehow an successor of 'mtl' and chose 
distinct package names, but there were module name clashes. They mostly 
hurted GHCi users, but this led to a lot of confusion, too.


So the question is, if FGL gets a new name, should it also use different 
module names?

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


Re: [Haskell-cafe] Re: package naming policy

2010-06-11 Thread Ivan Lazar Miljenovic
Henning Thielemann lemm...@henning-thielemann.de writes:

 Closely related is the question of module
 names. 'transformers'+'monads-fd' are somehow an successor of 'mtl'
 and chose distinct package names, but there were module name
 clashes. They mostly hurted GHCi users, but this led to a lot of
 confusion, too.

 So the question is, if FGL gets a new name, should it also use
 different module names?

This has been brought up already.

My intention is, before we release it publically/visibly, we get in
contact with all package maintainers of hackage packages that use FGL
and help them migrate to the new version so we can do a mass
migrate/upgrade so that there would be no reason for users to have the
old version of FGL installed (unless there's a system package vs
cabal-install package clash, but there's not much we can do about
that).

The unfortunate aspect of this IMHO is that the FGL package name doesn't
match the module names; if it was the consensus of the community that we
change the package name of FGL one option I was thinking of was
something along the lines of inductive-graphs, but the obvious choice
of module names for that would be Data.Graph.Inductive, which FGL has
already taken.

-- 
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] How to Show an Operation?

2010-06-11 Thread Bas van Dijk
On Mon, Jun 7, 2010 at 9:49 PM, Claus Reinke claus.rei...@talk21.com wrote:
 As others have pointed out, you can't go from operation to representation,
 but you can pair operations and expressions with their representations.

This idea is also implemented in my little 'repr' package:

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

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Ben Millwood
On Fri, Jun 11, 2010 at 12:46 AM, Felipe Lessa felipe.le...@gmail.com wrote:

  eqTypeable :: (Typeable a, Eq a, Typeable b, Eq b) = a - b - Bool
  eqTypeable x y = case cast y of
                     Just y' - x == y'
                     Nothing - False


...or indeed:

eqTypeable x y = cast x == Just y
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Christopher Done
On 11 June 2010 10:12, Roman Cheplyaka r...@ro-che.info wrote:
 * Günther Schmidt gue.schm...@web.de [2010-06-11 01:22:27+0200]
 there is nothing wrong with ifs as such except the won't actually
 exit a long piece of code, the computation will continue, just in a
 useless way.

 Can you clarify?

I think Günther assumed that I was suggesting:

do if x
  then return ()
  else bar
   continueComputation

The problem is that if 'x' is true, continueComputation should
never happen. So you can solve it like this, which is what I was
actually suggesting:

do if x
  then return ()
  else do bar; continueComputation

But then you have this problem, which Günther addressed:

2010/6/11 Günther Schmidt gue.schm...@web.de:
 Primarily for every if I need two forks, so at every if the
 branches double.

Which can be a big problem if you have a sequence of heterogenous
actions that must be executed in order and are dependant and
nested. Continutations solve this, as do ErrorT and MaybeT which
are both restricted subsets for returning values. I'd use MaybeT
if a value needed to be returned, or nothing.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Bulat Ziganshin
Hello Christopher,

Friday, June 11, 2010, 4:06:05 PM, you wrote:

 do if x
   then return ()
   else do bar; continueComputation

i format it this way:

if x then return () else do
bar
continueComputation



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

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


Re: Re[2]: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Christopher Done
On 11 June 2010 14:27, Bulat Ziganshin bulat.zigans...@gmail.com wrote:
 i format it this way:

 if x then return () else do
 bar
 continueComputation

That's a nice way of formatting! God bless optional formatting! I like
this problem-specific indentation. Another is:

if xthen foo
else if y then bar
else if z then mu
else zot

Kind of similar to a COND statement from Lisp.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[4]: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Bulat Ziganshin
Hello Christopher,

Friday, June 11, 2010, 4:35:00 PM, you wrote:

 if xthen foo
 else if y then bar
 else if z then mu
 else zot

case () of
 _ | x - foo
   | y - bar
   | otherwise - zor

it's usually considered as haskell way of doing this


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

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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Ozgur Akgun
I don't know whether its a good name or not (the ===), but I have the
following in a generic utilities file I have, and I use it every now and
then.

(===) :: (Typeable a, Typeable b, Eq b) = a - b - Bool
(===) x y = cast x == Just y

(Notice you don't need Eq a in the context)

On 11 June 2010 12:51, Ben Millwood hask...@benmachine.co.uk wrote:

 On Fri, Jun 11, 2010 at 12:46 AM, Felipe Lessa felipe.le...@gmail.com
 wrote:
 
   eqTypeable :: (Typeable a, Eq a, Typeable b, Eq b) = a - b - Bool
   eqTypeable x y = case cast y of
  Just y' - x == y'
  Nothing - False
 

 ...or indeed:

 eqTypeable x y = cast x == Just y
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




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


[Haskell-cafe] Re: [Haskell] Woes on MacOS 10.6 - linking issues

2010-06-11 Thread Pepe Iborra
(moving to the cafe)

There is an incompatibility between the version of iconv in Mac Os and
the one included in MacPorts.
As the RTS of the build of ghc in the Haskell Platform is linked
against Mac Os iconv, you cannot use it with the build of gtk2hs from
MacPorts.

This is a known issue already commented elsewhere, in case you haven't
found it already:

http://www.mail-archive.com/haskell-cafe@haskell.org/msg69139.html
http://stackoverflow.com/questions/2726248/ghc-6-12-and-macports

Cheers,


On Fri, Jun 11, 2010 at 4:53 AM, Brett Giles brett.gi...@ucalgary.ca wrote:
 Hi Folks

 I seem to have Gtk2HS 0.11 installed, but not quite working. Interestingly, I 
 can run a demo, such as the hello/World.hs example, directly in ghci. 
 However, when I try to do a ghc --make on any code containing gtk2hs I get a 
 link error like this:

 Undefined symbols:
  _iconv_close, referenced from:
      _hs_iconv_close in libHSbase-4.2.0.0.a(iconv.o)
     (maybe you meant: _hs_iconv_close)
  _iconv, referenced from:
      _hs_iconv in libHSbase-4.2.0.0.a(iconv.o)
     (maybe you meant: _hs_iconv_open, _hs_iconv , _hs_iconv_close )
  _iconv_open, referenced from:
      _hs_iconv_open in libHSbase-4.2.0.0.a(iconv.o)
     (maybe you meant: _hs_iconv_open)
 ld: symbol(s) not found


 I do have libiconv installed as a universal library via macports. gtk, glade 
 etc., are also universal installed via macports.

 I downloaded the OSX Haskell Platform package and am running ghc 6.12.1

 Other programs seem to be having some issues as well though,  For instance, a 
 command line program seems to compile fine, but when it runs I get the 
 message:

 $ emlqpl (--- My successfully compiled program - batch only, no gtk 
 items)
 dyld: Library not loaded: /opt/local/lib/libgtk-quartz-2.0.0.dylib
  Referenced from: /usr/local/bin/emlqpl
  Reason: image not found
 Trace/BPT trap



 Does anyone have any suggestions?

 Brett Giles
 Grad Student, Formal Methods, Category Theory,
 University of Calgary
 brett.gi...@ucalgary.ca



 ___
 Haskell mailing list
 hask...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell




-- 
-- José Iborrahttp://www.dsic.upv.es/~jiborra
-- UPV Valencia   Telf. (+34) 96 387 00 00 (ext) 83529
-- Camino de Vera s/n. 46022 Valencia (Spain)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] Using the ContT monads for early exits of IO ?

2010-06-11 Thread Christopher Done
On 11 June 2010 14:40, Bulat Ziganshin bulat.zigans...@gmail.com wrote:
 if x        then foo
 else if y then bar
 else if z then mu
 else             zot

 case () of
  _ | x - foo
   | y - bar
   | otherwise - zor

 it's usually considered as haskell way of doing this

The example is merely to demonstrate how optional layout can encode
useful patterns, not to claim there aren't other ways to do it in
Haskell. For what it's worth, this solution is pretty hackish and so
not really Haskelly.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Encoding the encoding type of a string into its type

2010-06-11 Thread Christopher Done
There are a lot of issues with string encoding type mismatches.
Especially automatic conversions. This mailing list gets enough
posts about encoding confusions.

Would it make sense to make the string depend on its encoding type?

E.g. a String UTF16 cannot be used with putStrLn :: String UTF8, it
has to be used with putStrLn :: String UTF16. Provided the fundamental
functions that read and write strings are type safe, there'll be no
mix-ups?

I'll think about this more later. Just putting the question out there
so that I remember when I get home.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Encoding the encoding type of a string into its type

2010-06-11 Thread Felipe Lessa
On Fri, Jun 11, 2010 at 04:17:25PM +0200, Christopher Done wrote:
 There are a lot of issues with string encoding type mismatches.
 Especially automatic conversions. This mailing list gets enough
 posts about encoding confusions.

 Would it make sense to make the string depend on its encoding type?

I think our String type doesn't have semantic problems, a string
really is a list of Unicode codepoints.  However this
representation has serious performance drawbacks.

Now we have Data.Text, which should have better performance and
maintain nice semantics.  However it uses a single internal
encoding for various reasons.  So, if your input and your output
are on the same coding X, where X isn't UTF-16 (IIRC), then you
will have to do two reencodes, perhaps unnecessarily.

So maybe annotating the encoding *could* be useful on some
applications.  But I can't imagine how hairy the implementation
of such a generalised Data.Text would be, nor the performance
impact if the dictionary isn't inlined/specialized for the case
in hand.

 E.g. a String UTF16 cannot be used with putStrLn :: String UTF8, it
 has to be used with putStrLn :: String UTF16. Provided the fundamental
 functions that read and write strings are type safe, there'll be no
 mix-ups?

Note that right now you don't need this extra burden to get the
safety you want.  Just use Data.Text everywhere.  The problem
isn't Data.Text but the Prelude IO functions using String where
there should be [Word8].

Cheers,

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


[Haskell-cafe] Re: [Haskell] ANNOUNCE: Sifflet visual programming language, release 0.1.7

2010-06-11 Thread Henning Thielemann


On Fri, 11 Jun 2010, Ben Millwood wrote:


On Fri, Jun 11, 2010 at 2:52 PM, Henning Thielemann
lemm...@henning-thielemann.de wrote:


I'm uncertain whether fgl conforms to the package versioning policy, but
if it does, then changes in its Cabal file should not bother sifflet.
Thus upper bound fgl  5.4.3 should be restrictive enough.



The PVP says that one of the first two numbers are required to change
if an API change is likely to break code using it, so  5.5 would
probably suffice.


A bump to fgl-5.4.3 might include API *extensions* that may break sifflet, 
if it imports entire FGL modules in an unqualified way.

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


[Haskell-cafe] Code review of text-xml-generic

2010-06-11 Thread Oscar Finnsson
Hi,

I've been working on a (de)serialization package from/to XML (using
SYB) and wondering if anyone feels like giving me a quick code review
before I upload it to hackagedb.

The source code can be found at http://github.com/finnsson/Text.XML.Generic

It is *heavily* inspired by Text.JSON.Generic.

The three files DataEx.hs (slightly modified version of Olegs code),
ExGeneric.hs and ExTestGeneric.hs are not part of the package yet
since I haven't got the deserialization to work for existentials yet
(but I haven't given up!).

I plan to upload the package to hackagedb by the end of this weekend
so any comments before (and after) are more than welcome.

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


Re: [Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-11 Thread Maciej Piechotka
On Thu, 2010-06-10 at 21:21 +0100, Ben Millwood wrote:
 On Thu, Jun 10, 2010 at 8:57 PM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
 
  Error monad seems not to be a semantic solution as we exit on success
  not failure.
 
 
 Which is really why the Either monad should not necessarily have Error
 associations :)
 If you forget about the fail method, the Monad (Either e) instance
 doesn't need the e to be an error type.
 
 Alternatively, if even Error is more information than you need, you
 could use MaybeT:
 
 http://hackage.haskell.org/package/MaybeT
 
 which allows you to just stop. Given you're using it with IO it'd be
 easy to write a result to an IORef before terminating the computation,
 so it's of equivalent power, if slightly less convenient.

Over MaybeT I would prefer to simply iterate over list using helper
recursive function.

Either monad (without Error part) seems to be good solution - and it do
not contain too much information.

But the function with ContT IO seemed... nice. Also as it deals with
network I/O speed does not seems to be a great issue.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with threading?

2010-06-11 Thread Isaac Gouy

--- On Thu, 6/10/10, Louis Wasserman wasserman.lo...@gmail.com wrote:

 Date: Thursday, June 10, 2010, 1:32 AM

 Yeah, Control.Parallel would be nice to have.  Heck, ideally I could get 
 the whole Haskell Platform, which would be a reasonable comparison to 
 the huge Java and C++ libraries accessible to those languages.


And having the whole Haskell Platform still isn't enough to compile those  
regex-dna programs.




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


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Dupont Corentin
Thanks all, it works fine (see below).

I lamentably try to make the same for show:
 showTypeable :: (Typeable a) = a - String
 showTypeable x = case cast x of
  Just x' - show x'
  Nothing - 

Because it really upsets me to add this show constraints to the Equ
constructor ;)
what if i want to make an Obs instance with non showable elements, with no
intention to show it of course?

Corentin

 instance Typeable1 Obs where
typeOf1 _ = mkTyConApp (mkTyCon Obs) []

 (===) :: (Typeable a, Typeable b, Eq b) = a - b - Bool
 (===) x y = cast x == Just y


 data Obs a where
 Player   :: Obs Player
 Official :: Obs Bool
 Equ  :: (Eq a, Show a, Typeable a) = Obs a - Obs a - Obs Bool
 Plus :: (Num a) = Obs a - Obs a - Obs a
 Time :: (Num a) = Obs a - Obs a - Obs a
 Minus:: (Num a) = Obs a - Obs a - Obs a
 And  :: Obs Bool - Obs Bool - Obs Bool
 Or   :: Obs Bool - Obs Bool - Obs Bool
 Not  :: Obs Bool - Obs Bool
 Konst:: (Show a, Eq a) = a - Obs a



 instance Show t = Show (Obs t) where
 show Player  = Player
 show Official= Official
 show (Equ a b)   = (show a) ++  Eq  ++ (show b)
 show (Plus a b)  = (show a) ++  Plus  ++ (show b)
 show (Minus a b) = (show a) ++  Minus  ++ (show b)
 show (Time a b)  = (show a) ++  Time  ++ (show b)
 show (Konst a)   =  (Konst  ++ (show a) ++ )
 show (And a b)   = (show a) ++  And  ++ (show b)
 show (Or a b)= (show a) ++  Or  ++ (show b)
 show (Not a) =  (Not  ++ (show a) ++ )


 instance Eq t = Eq (Obs t) where
 Player == Player   = True
 Official == Official   = True
 Equ a b == Equ c d = (a,b) === (c,d)
 Plus a b == Plus c d   = (a == c)  (b == d)
 Minus a b == Minus c d = (a == c)  (b == d)
 Time a b == Time c d   = (a == c)  (b == d)
 And a b == And c d = (a == c)  (b == d)
 Or a b == Or c d   = (a == c)  (b == d)
 Not a == Not b = (a == b)
 Konst a == Konst b = a == b
 _ == _ = False
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GATD and pattern matching

2010-06-11 Thread Felipe Lessa
On Sat, Jun 12, 2010 at 12:13:14AM +0200, Dupont Corentin wrote:
 Thanks all, it works fine (see below).

 I lamentably try to make the same for show:
  showTypeable :: (Typeable a) = a - String
  showTypeable x = case cast x of
   Just x' - show x'
   Nothing - 

 Because it really upsets me to add this show constraints to the Equ
 constructor ;)
 what if i want to make an Obs instance with non showable elements, with no
 intention to show it of course?

Ad hoc solution:

  class MaybeShow a where
maybeShow :: a - Maybe String

  instance Show a = MaybeShow a where
maybeShow = Just . show

  instance MaybeShow a where
maybeShow = Nothing

  data MyData where
Something :: MaybeShow a = a - MyData

  instance MaybeShow MyData where
maybeShow (Something x) =
  fmap (\s - Something ( ++ s ++ )) (maybeShow x)

Hahahaha :).  Try to guess without using GHC/GHCi:

  1) Which extensions are required to make the code compile.

  2) After compiled, if it works as intended or not.

Cheers,

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


Re: [Haskell-cafe] GATD and pattern matching

2010-06-11 Thread Antoine Latter
On Friday, June 11, 2010, Felipe Lessa felipe.le...@gmail.com wrote:
 On Sat, Jun 12, 2010 at 12:13:14AM +0200, Dupont Corentin wrote:
 Thanks all, it works fine (see below).

 I lamentably try to make the same for show:
  showTypeable :: (Typeable a) = a - String
  showTypeable x = case cast x of
                       Just x' - show x'
                       Nothing - 

 Because it really upsets me to add this show constraints to the Equ
 constructor ;)
 what if i want to make an Obs instance with non showable elements, with no
 intention to show it of course?

 Ad hoc solution:

   class MaybeShow a where
     maybeShow :: a - Maybe String

   instance Show a = MaybeShow a where
     maybeShow = Just . show

   instance MaybeShow a where
     maybeShow = Nothing

   data MyData where
     Something :: MaybeShow a = a - MyData

   instance MaybeShow MyData where
     maybeShow (Something x) =
       fmap (\s - Something ( ++ s ++ )) (maybeShow x)

 Hahahaha :).  Try to guess without using GHC/GHCi:

   1) Which extensions are required to make the code compile.


OverlappingInstances (of course), and IncoherrentInstances, since
neither instance is more specific than the other.

   2) After compiled, if it works as intended or not.

It's hard for me to concieve of a situation where something requiring
IncoherrentInstances is work as intended, but maybe that's a failure
of imagtination.

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


Re: [Haskell-cafe] GATD and pattern matching

2010-06-11 Thread Felipe Lessa
On Fri, Jun 11, 2010 at 08:12:43PM -0500, Antoine Latter wrote:
    1) Which extensions are required to make the code compile.

 OverlappingInstances (of course), and IncoherrentInstances, since
 neither instance is more specific than the other.

Well, I guess it can't be compiled at all :(

  $ ghci -XGADTs -XOverlappingInstances -XIncoherentInstances 
-XFlexibleInstances -XUndecidableInstances
  GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
  Loading package ghc-prim ... linking ... done.
  Loading package integer ... linking ... done.
  Loading package base ... linking ... done.
  Prelude :l T
  [1 of 1] Compiling Main ( T.lhs, interpreted )

  T.lhs:4:12:
  Duplicate instance declarations:
instance [incoherent] (Show a) = MaybeShow a
  -- Defined at T.lhs:4:12-32
instance [incoherent] MaybeShow a -- Defined at T.lhs:7:12-22

    2) After compiled, if it works as intended or not.

 It's hard for me to concieve of a situation where something requiring
 IncoherrentInstances is work as intended, but maybe that's a failure
 of imagtination.

Perhaps we should omit the Nothing instance:

  class MaybeShow a where
maybeShow :: a - Maybe String

  instance Show a = MaybeShow a where
maybeShow = Just . show

Instances for any non-Show-able data types should be manually
written, such as:

  instance MaybeShow (a - b) where
maybeShow = const Nothing

I think this solution still requires OverlappingInstances and
UndecidableInstances.



Finally we could omit the Show a = MaybeShow a definition as
well and just manually write everything:

  class MaybeShow a where
may_I_show_you :: a - Maybe String

  yes_please :: Show a = a - Maybe String
  yes_please = Just . show

  no_thanks :: a - Maybe String
  no_thanks = const Nothing

  instance MaybeShow ()   where may_I_show_you = yes_please
  instance MaybeShow Char where may_I_show_you = yes_please
  instance MaybeShow Int  where may_I_show_you = yes_please
  instance MaybeShow (a - b) where may_I_show_you = no_thanks
  instance MaybeShow (IO a)   where may_I_show_you = no_thanks
  ...

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


Re: [Haskell-cafe] Problems with threading?

2010-06-11 Thread Isaac Gouy


--- On Wed, 6/9/10, Don Stewart d...@galois.com wrote:

-snip-
  Now how do we get those regex-dna and binary-trees
 programs to compile?
  
  http://shootout.alioth.debian.org/u32/measurements.php?lang=ghc
  
 
 binary-trees:
     Could not find module
 `Control.Parallel.Strategies':
 
         -- cabal install parallel
 
 regex-dna:
 
      cannot satisfy -package regex-posix
 
         -- cabal install
 regex-posix


parallel, regex-posix, regex-pcre are now installed and the current compile 
errors are caused by the programs not the absence of required libraries -

http://shootout.alioth.debian.org/u64q/program.php?test=binarytreeslang=ghcid=2#log

http://shootout.alioth.debian.org/u64q/program.php?test=binarytreeslang=ghcid=3#log

http://shootout.alioth.debian.org/u64q/program.php?test=regexdnalang=ghcid=4#log

http://shootout.alioth.debian.org/u64q/program.php?test=regexdnalang=ghcid=1#log





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


Re: [Haskell-cafe] Problems with threading?

2010-06-11 Thread Don Stewart
igouy2:
 
 parallel, regex-posix, regex-pcre are now installed and the current
 compile errors are caused by the programs not the absence of required
 libraries -
 
 http://shootout.alioth.debian.org/u64q/program.php?test=binarytreeslang=ghcid=2#log
 
 http://shootout.alioth.debian.org/u64q/program.php?test=binarytreeslang=ghcid=3#log
 
 http://shootout.alioth.debian.org/u64q/program.php?test=regexdnalang=ghcid=4#log
 
 http://shootout.alioth.debian.org/u64q/program.php?test=regexdnalang=ghcid=1#log

Great work!

For those keen to help out the Haskell programs, both compile failures
in regexdna and binarytrees are related to the change in how parallel
strategies work, as described here.


http://hackage.haskell.org/packages/archive/parallel/2.2.0.1/doc/html/Control-Parallel-Strategies.html

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