[Haskell-cafe] Existentials and SYB [Was: GADTs and Scrap your Boilerplate]

2010-05-21 Thread oleg

Oscar Finnsson wrote:

 I got the GADT

 data DataBox where
   DataBox :: (Show d, Eq d, Data d) = d - DataBox

 and I'm trying to get this to compile

 instance Data DataBox where
   gfoldl k z (DataBox d) = z DataBox `k` d
   gunfold k z c = k (z DataBox)  -- not OK

As has been pointed out, DataBox is an ordinary existential data type,
only written using the new-style notation. For clarity, let us define
our DataBox with the conventional notation:

 data DataBox = forall d. (Show d, Eq d, Data d) = DataBox d

So, the question becomes of using existentials with Scrap your
Boilerplate.

On one hand, it is unnervingly trivial to incorporate existentials
into the SYB framework.

Let us consider the signature of gunfold, the problematic member of
the (Data a) type class.

  -- | Unfolding constructor applications
  gunfold :: (forall b r. Data b = c (b - r) - c r)
  - (forall r. r - c r)
  - Constr
  - c a

We have to eventually produce a value of the type (c DataBox). We
observe that our work is done if we manage to produce one value of the
type DataBox. We then apply the second argument to gunfold (which
`lifts' from any type r to the type c r), and we are done. To produce
an existential value, we need one witness of the constraints Show, Eq
and Data. For example, the type Int is such witness. Thus, we are
done indeed. Here is the complete code:

 {-# LANGUAGE ExistentialQuantification, Rank2Types #-}

 module F where

 import Data.Generics

 data DataBox = forall d. (Show d, Eq d, Data d) = DataBox d

 instance Typeable DataBox where
   typeOf _ = mkTyConApp (mkTyCon DataBox) []

 instance Data DataBox where
   gfoldl k z (DataBox d) = z DataBox `k` d
   gunfold k z c = z (DataBox (42::Int))


One may complain that we have fixed not only the type of the argument
to DataBox but also the value. We should let gunfold to `produce' the
value. Here is a sketch:

 enDataI :: (Int - DataBox)
 enDataI = DataBox

 enDataB :: (Bool - DataBox)
 enDataB = DataBox

 instance Data DataBox where
   gfoldl k z (DataBox d) = z DataBox `k` d
   gunfold k z c = (if True then k (z enDataI) else k (z enDataB))

Now, the particular Int value to supply to DataBox will be produced by
the function k. The above code used the constant True to fix the
choice of the type to Int. Generally, one could use the third argument
of gunfold to help make the choice. That is, we could incorporate the
choice of the type in the value of Constr.


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


Re: [Haskell-cafe] Intuitive function given type signature

2010-05-21 Thread Richard O'Keefe


On May 21, 2010, at 3:51 AM, Brent Yorgey wrote:


On Thu, May 20, 2010 at 11:53:09AM +1200, Richard O'Keefe wrote:


On May 20, 2010, at 3:18 AM, Brent Yorgey wrote:


On Wed, May 19, 2010 at 04:27:14AM +, R J wrote:


What are some simple functions that would naturally have the  
following

type signatures:
f :: (Integer - Integer) - Integer



The key point is the 'that would NATURALLY have', which I take
to mean as a result of type inference without any forcibly
imposed type signatures.


Given that this is an exercise in Chapter 1, I kind of doubt this is
really what it is supposed to mean.  Are people reading chapter 1
really expected to understand the intricacies of type inference and
the Num class?  And to know about 'toInteger' and the fact that
numeric constants are polymorphic?  I really doubt it.  I read the
question much more simply, with naturally having a much more
informal meaning than you suggest.  I interpret the question as simply
getting the reader some practice with basic higher-order types.


The other possibility, of course, is a setup where Integer is the
default type, so the function should just be f g = g 0 + 0.
But naturally has to mean *something*, and the questions are
clearly about type inference.




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


Re: [Haskell-cafe] Intuitive function given type signature

2010-05-21 Thread Tom Davies

On 20/05/2010, at 9:53 AM, Richard O'Keefe wrote:
 
 The key point is the 'that would NATURALLY have', which I take
 to mean as a result of type inference without any forcibly
 imposed type signatures.

In my second edition of Bird, the question just says: Give examples of 
functions with the following types:

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


Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-21 Thread Stephen Tetley
Hi Evan

EHC - Essential Haskell Compiler - is the 'family of compilers' that
UHC - Utrecht Haskell Compiler - is instance one of. The EHC family
starts with a simple Haskell subset and adds features building up to
(almost) Haskell98 for UHC and extended Haskell for some of the EHC
variations. This style of software development is sometime called
'feature oriented development' or 'software product lines', the ML
compiler MLPolyR is another compiler built as a family of variants.

UHC had a version 1.0 release last year. From the documentation it
doesn't look like UHC supports type class directives:

http://www.cs.uu.nl/wiki/bin/view/Ehc/UhcUserDocumentation

From a bit of nosing around, I'm not sure that any of the EHC variants
support type class directives either. It does look like Helium
(Utrecht's simplified Haskell variant for teaching) supports them, and
Helium has certainly been released. That said, I've no association
with the Utrecht developers, so I'm not really qualified to say for
EHC, though I have studied its source a bit and grepping hasn't turned
up an answer. Incidentally, studying the source of EHC is probably the
best way to learn idioms and techniques for UUAG.


From the 'Type Class Directives' paper here are some example directives:

never Eq (a - b):
  functions cannot be tested for equality
never Num Bool:
  arithmetic on booleans is forbidden

disjoint Integral Fractional:
  something which is fractional can never be integral

close Similar:
  the instances of Similar are @in...@.

(Similar being an Eq like class that is available only for integers)

Best wishes

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


Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-21 Thread Max Bolingbroke
On 21 May 2010 01:58, Carlos Camarao carlos.cama...@gmail.com wrote:
 But this type-correct program would become not typeable if
 instances such as the ones referred to before (by Daniel Fischer)

I was thinking this through, and the situation is more complex than I
had thought.

It seems that single param type classes enjoy a nice property:
* Adding an instance to the module defining the class cannot conflict
with any non-orphan instance defined elsewhere
* Adding an instance for a type for a class *to the module defining
that type* cannot conflict with any non-orphan instance defined
elsewhere

As long as you complicate the definition of orphan, this seems to
still hold for multi-param ones. The change you need is that an
instance defined in a module other than that defining the class must
be non-orphan *in each individual type variable*. So if a module
defined the D and E data types you could make a C D E instance, but a
C D Bool or C Bool E one is considered orphan by this definition.

Functional dependencies refine this slightly: if a variable (a)
functionally determines another (b), an instance can be declared
non-orphan as long as the a variable is being instantiated with a
data type which is defined in the same module. So if C a b has FD a
|- b you can declare an instance for C D Bool but not C Bool D.

With this definition of orphan I don't think it is possible to get
the library fragility issue as long as you stick to non-orphan
instances by that definition. I haven't tried to prove this, though.

Where this gets more interesting is that GHC's -fwarn-orphans check
does *not* flag a C D Bool instance in a module defining D but not C
as an orphan, whether C has a functional dependency or not. It will
only flag an instance as orphan if *all* of the class type variables
are being instantiated to a datatype defined in another module. This
seems like a bug?

So in summary I think I agree with you that your proposed mechanism
does have fragility characteristics similar to FDs as they stand. One
benefit (that I can see) to using explicitly declared FDs is that the
compiler could potentially use those FDs to implement a correct orphan
instance check, such that code that passed the check was guaranteed
not to cause the library fragility issue in those modules that import
it. However, it appears that GHC doesn't currently do this, which is
upsetting.

(Incidentally, the link to your paper is broken, so I haven't actually
been able to read it, sorry!)

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


[Haskell-cafe] Re: String rewriting

2010-05-21 Thread Johannes Waldmann
 ... to rewrite strings according to simple composable rules like ...

more often than not, regexp/replace is a hack to avoid the real thing 
(parse - AST - transform - AST' - print).

such hacks tend to grow into something that is definitely not composable.

but, you can be a hero ... http://xkcd.com/208/


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


[Haskell-cafe] Недвижимость во Франции, ар енда и продажа вилл

2010-05-21 Thread moreletto
Офис нашей компании находится в Ницце - в самом сердце Французской Ривьеры,
что дает нам непосредственную возможность предложить виллы для аренды и
продажи во всем их многообразии, а также сориентировать наших клиентов на
самые интересные и значимые мероприятия в богатой культурной и светской
жизни Лазурного берега. Мы предоставляем нашим клиентам широкий выбор вилл
класса люкс по всей протяжённости Лазурного берега Франции - от Сан Тропе до
Монако, оказываем визовую поддержку, а также организуем визиты на
приглянувшиеся Вам объекты при заключении контрактов по аренде или покупке
вилл и другой недвижимости http://www.property-serviceazur.com/


средиземноморского побережья. Уважаемые партнеры, мы предлагаем Вам
сотрудничество в приобретении Вашими клиентами *недвижимости во Франции, на
Лазурном берегу *, который всегда ценился поклонниками искусства, знатоками
истории, любителями изысканной кухни и живописных пейзажей.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Недвижимость во Ф ранции, аренда и продажа вилл

2010-05-21 Thread Roel van Dijk
Google translation:
 The office of our company is located in Nice - the heart of the
 Riviera, that gives us an immediate opportunity to offer villas
 for rent and sale in all their diversity, as well as guidance to
 our clients on the most interesting and important events in the
 rich cultural and social life Cote d'Azur. We offer our customers
 a wide choice of luxury villas on the entire length of the Côte
 d'Azur of France - from St Tropez to Monaco, visa support and
 arrange visits to your vending facility at the conclusion of
 contracts for lease or purchase of houses and other real estate

 Mediterranean coast. Dear partners, we offer you our cooperation
 in the acquisition of your clients property in France, Cote
 d'Azur, which has always valued art lovers, connoisseurs of
 history, lovers of fine cuisine and beautiful scenery.

So spam for luxury villa's? I guess Haskell really failed in avoiding success...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] making the GHC Api not write to stderr

2010-05-21 Thread Thomas Schilling
You could try changing the log_action[1] member of the DynFlags.  A
while ago I turned most printed errors into some form of error
message, but I wouldn't be surprised if I missed some places.  All
output should go through log_action, though, so try changing that to
intercept any output.

[1]: 
http://haskell.org/ghc/docs/6.12-latest/html/libraries/ghc-6.12.2/DynFlags.html#v%3Alog_action

On 20 May 2010 19:05, Phyx loneti...@gmail.com wrote:
 I was wondering how to forcibly quiet down the API. I have a custom handler
 in place, but when I call the function on failure both my handler gets
 called and somewhere somehow errors get printed to the stderr, which I
 really need to avoid.



 My current code looks like



 getModInfo :: Bool - String - String - IO (ApiResults ModuleInfo)

 getModInfo qual file path = handleSourceError processErrors $

 runGhc (Just libdir) $ do

     dflags - getSessionDynFlags

     setSessionDynFlags $ configureDynFlags dflags

     target - guessTarget file Nothing

     addTarget target

     setSessionDynFlags $ dflags { importPaths = [path] }

     load LoadAllTargets

 graph - depanal [] False

     let modifier = moduleName . ms_mod

     modName  = modifier $ head graph

     includes = includePaths dflags

     imports  = importPaths dflags



 dflags' - Debug.trace (moduleNameString modName) getSessionDynFlags

     setSessionDynFlags $ dflags' { includePaths = path:includes

  , importPaths  = path:imports

  }



     parsed  - parse modName

     checked - typecheckModule parsed

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





-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type families vs. functional dependencies -- how to express something

2010-05-21 Thread Tomáš Janoušek
Hello,

On Tue, May 18, 2010 at 04:47:50PM -0700, Dan Weston wrote:
  Unifying those two types by hand, I get:
 
  P (A t - B a)
  ~  P (B a)

 Maybe the problem is that type families (and associated types, their  
 class cousins) are not injective: P x ~ P y does not imply that x ~ y.  
 Maybe you need a data type (with appropriate wrapping and unwrapping) to  
 ensure injectivity. Cf:

 http://www.haskell.org/haskellwiki/GHC/Type_families#Injectivity.2C_type_inference.2C_and_ambiguity
 http://www.mail-archive.com/haskell-cafe@haskell.org/msg63359.html

That's probably it, thanks. I think I'll just stay with functional
dependencies this time, a data type with wrapping and unwrapping can't
possibly make the code more readable :-).

Regards,
-- 
Tomáš Janoušek, a.k.a. Liskni_si, http://work.lisk.in/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] making the GHC Api not write to stderr

2010-05-21 Thread Phyx
Hi,
I tried that, setting it to (\_ _ _ _ - return ()) and it still did the
same, also tried setting it to undefined to see whether the code that's
printing the error is using it, and it didn't crash
So I assume it's not.

---
*VsxParser getModInfo True
C:\\Users\\Phyx\\AppData\\Local\\Temp\\tmp5600.hs
  return ()

C:\Users\Phyx\AppData\Local\Temp\tmp5600.hs:11:13:
parse error on input `='
Printf
-

I think parseModule might still have a hardcoded print statement in it.

-Original Message-
From: Thomas Schilling [mailto:nomin...@googlemail.com] 
Sent: Friday, May 21, 2010 12:53
To: Phyx
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] making the GHC Api not write to stderr

You could try changing the log_action[1] member of the DynFlags.  A while
ago I turned most printed errors into some form of error message, but I
wouldn't be surprised if I missed some places.  All output should go through
log_action, though, so try changing that to intercept any output.

[1]:
http://haskell.org/ghc/docs/6.12-latest/html/libraries/ghc-6.12.2/DynFlags.h
tml#v%3Alog_action

On 20 May 2010 19:05, Phyx loneti...@gmail.com wrote:
 I was wondering how to forcibly quiet down the API. I have a custom 
 handler in place, but when I call the function on failure both my 
 handler gets called and somewhere somehow errors get printed to the 
 stderr, which I really need to avoid.



 My current code looks like



 getModInfo :: Bool - String - String - IO (ApiResults ModuleInfo)

 getModInfo qual file path = handleSourceError processErrors $

 runGhc (Just libdir) $ do

     dflags - getSessionDynFlags

     setSessionDynFlags $ configureDynFlags dflags

     target - guessTarget file Nothing

     addTarget target

     setSessionDynFlags $ dflags { importPaths = [path] }

     load LoadAllTargets

 graph - depanal [] False

     let modifier = moduleName . ms_mod

     modName  = modifier $ head graph

     includes = includePaths dflags

     imports  = importPaths dflags



 dflags' - Debug.trace (moduleNameString modName) 
 getSessionDynFlags

     setSessionDynFlags $ dflags' { includePaths = path:includes

  , importPaths  = path:imports

  }



     parsed  - parse modName

     checked - typecheckModule parsed

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





--
Push the envelope.  Watch it bend.

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


Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-21 Thread Marco Túlio Gontijo e Silva
Hi Max.

Excerpts from Max Bolingbroke's message of Sex Mai 21 04:56:51 -0300 2010:
(...)
 (Incidentally, the link to your paper is broken, so I haven't actually
 been able to read it, sorry!)

It was easy to find it on google.

http://www.dcc.ufmg.br/~camarao/CT/solution-to-mptc-dilemma.pdf

Greetings.
(...)
-- 
marcot
http://wiki.debian.org/MarcoSilva


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


[Haskell-cafe] Register now for: Haskell in Leipzig (Germany), June 4.

2010-05-21 Thread Johannes Waldmann
Schedule and registration for the Haskell in Leipzig
meeting on June 4 are now on-line: http://www.iba-cg.de/hal5.html

It's our fifth meeting, and here are five good reasons to go:

* learn Haskell:
 attend tutorials for beginners
* get first-hand information:
 authors of Leksah, HXT, Hawk  give tutorials/talks
* share your expert knowledge:
 at lambda camp
* see beyond Haskell:
 learn dependently typed programming in Agda
* relax at BBQ party and listen to strange sounds:
 unsafePerformance

The meeting is presented by http://www.fit-leipzig.de/ ,
in co-operation with http://www.imn.htwk-leipzig.de/ ,
http://www.leipziger-medienstiftung.de/, http://www.iba-cg.de/

Best regards, Johannes Waldmann (for the Hal5 program committee)



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Tools to make tidy HTML

2010-05-21 Thread Dmitri O.Kondratiev
Hello!
Please advise haskell libraries similar to convert real-world HTML to
well-formed XML.
I need something similat to HTML Tidy library:
http://tidy.sourceforge.net/

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


[Haskell-cafe] ambiguous type variable problem when using forall, multiparameter type classes, and constraints on polymorphic values (and syb-with-class)

2010-05-21 Thread Jeremy Shaw
Hello,

I am trying to understand why I am getting an ambigious type variable error,
and what I can do to work around it. The problem is occurring while trying
to use syb-with-class, but I have stripped it down to it's bare essentials,
so the following code is self-contained, and does not require an
understanding of syb-with-class.

 {-# LANGUAGE RankNTypes, KindSignatures, MultiParamTypeClasses,
FlexibleInstances, ScopedTypeVariables, FlexibleContexts #-}
 module Main where

A Proxy data type used to pass some extra type info around in gmapQ.

 data Proxy (a :: * - *) = Proxy

A simple multiple parameter type class.

 class Data (ctx :: * - *) a

gmapQ takes a function, forall a. (Data ctx a) = a - r, applies the
function to all the immediate sub-types of 'a' and collects the
results as a list. This is possible because the 'a' is forall'd, and
(in the real implementation) the Data class provides the mechanisms
for accessing all the immediate sub-types of 'a' and doing useful
things with them.

 gmapQ :: Proxy ctx - (forall a. (Data ctx a) = a - r) - (forall a.
(Data ctx a) = a - [r])
 gmapQ = undefined

Now we create a context.

 data Foo m a = Foo { unFoo :: m a }

And create a Data instance for it.

 instance Data (Foo m) a

Here is an example that attempts to recursively apply itself to all
the subtrees.

(I believe this function will ultimately return 0, since it tries to
sum the results of the children. When you reach types with no more
sub-types, I think you will get an empty list, and sum [] == 0. Though
it's not really important to the issue at hand).

 bar1 :: forall a m r. (Data (Foo m) a, Num r) = a - r
 bar1 x = sum $ gmapQ (undefined :: Proxy (Foo m)) bar1 x

The problem I have is when I try to add an additional constraint on 'm',
such as (Monad m) =

 -- bar2 :: forall a m r. (Monad m, Data (Foo m) a, Num r) = a - r
 -- bar2 x = sum $ gmapQ (undefined :: Proxy (Foo m)) (bar2 :: forall b.
(Monad m, Data (Foo m) b, Num r) = b - r) x

I get the error:

/tmp/a.lhs:48:54:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `bar2' at /tmp/a.lhs:48:54-57
Probable fix: add a type signature that fixes these type variable(s)
Failed, modules loaded: none.

Adding all the scoped type variable stuff does not seem to help. Alas,
I can not figure out if this is a limitation of the type-checker, or
something that is fundamentally impossible. Nor can I figure out how
to work around the issue.

In my real code I need to define the data instance like:

 -- instance (Monad m) = Data (Foo m) a

Which, by itself is fine. But that results in my needing to add (Monad
m) to the 'bar' function. And that is what I can't figure out how to
do..

Thanks!

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


[Haskell-cafe] FW: Why does this Ord-class instance crash?

2010-05-21 Thread R J

Why does the following, trivial  code snippet below hang GHCi when I 
typeScalene  Failure, and what's the fix?

data Triangle  =  Failure   |  
Equilateral   |  Isosceles  
 |  Scalene   deriving (Eq, Show)
instance Ord Triangle whereFailure  Failure  = FalseFailure
  _= True
Equilateral  Failure  = FalseEquilateral  Equilateral  = False
Equilateral  _= True
IsoscelesScalene  = TrueIsosceles_= False
Scalene  _= False

(I tried submitting this to beginn...@haskell.org, but even though I've signed 
up for that mailing list, I got a bounce-back saying that I needed admin 
approval to submit anything to that list, and I haven't heard from an admin, so 
I'm posting it here.) 
_
The New Busy is not the too busy. Combine all your e-mail accounts with Hotmail.
http://www.windowslive.com/campaign/thenewbusy?tile=multiaccountocid=PID28326::T:WLMTAGL:ON:WL:en-US:WM_HMP:042010_4___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-21 Thread David Menendez
On Fri, May 21, 2010 at 3:56 AM, Max Bolingbroke
batterseapo...@hotmail.com wrote:
 On 21 May 2010 01:58, Carlos Camarao carlos.cama...@gmail.com wrote:
 But this type-correct program would become not typeable if
 instances such as the ones referred to before (by Daniel Fischer)

 I was thinking this through, and the situation is more complex than I
 had thought.

 It seems that single param type classes enjoy a nice property:
 * Adding an instance to the module defining the class cannot conflict
 with any non-orphan instance defined elsewhere
 * Adding an instance for a type for a class *to the module defining
 that type* cannot conflict with any non-orphan instance defined
 elsewhere

This is only true in the absence of recursive imports. Otherwise,
those points imply that I can put one instance in the module defining
the type and another in the module defining the class without
conflict.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FW: Why does this Ord-class instance crash?

2010-05-21 Thread David Menendez
2010/5/21 R J rj248...@hotmail.com:
 Why does the following, trivial  code snippet below hang GHCi when I type
 Scalene  Failure, and what's the fix?

An instance of Ord must declare compare or (=). You only defined (),
so () is using the default definition. Here are the defaults:

compare x y = if x == y then EQ
  else if x = y then LT
  else GT

x   y = case compare x y of { LT - True;  _ - False }
x = y = case compare x y of { GT - False; _ - True }
x   y = case compare x y of { GT - True;  _ - False }
x = y = case compare x y of { LT - False; _ - True }
max x y = if x = y then y else x
min x y = if x = y then x else y

Note that the default definitions of (=) and compare call each other,
leading to an infinite loop when both are used.

Simple fix: define (=) instead of ().
-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FW: Why does this Ord-class instance crash?

2010-05-21 Thread Miguel Mitrofanov

From Prelude.hs:

class  (Eq a) = Ord a  where
compare  :: a - a - Ordering
(), (=), (), (=) :: a - a - Bool
max, min :: a - a - a

compare x y = if x == y then EQ
  -- NB: must be '=' not '' to validate the
  -- above claim about the minimal things that
  -- can be defined for an instance of Ord:
  else if x = y then LT
  else GT

x   y = case compare x y of { LT - True;  _ - False }
x = y = case compare x y of { GT - False; _ - True }
x   y = case compare x y of { GT - True;  _ - False }
x = y = case compare x y of { LT - False; _ - True }

-- These two default methods use '=' rather than 'compare'
-- because the latter is often more expensive
max x y = if x = y then y else x
min x y = if x = y then x else y

So, in your case:

Scalene  Failure
  -  {Gee, there's no definition of  in this Ord instance; I'll  
have to take the default one}

compare Scalene Failure
  - {There's no definition of compare either; again, the default  
one}

Scalene = Failure
  - {Again, there is no definition of =}
compare Scalene Failure
  - loop



On 21 May 2010, at 21:06, R J wrote:

Why does the following, trivial  code snippet below hang GHCi when I  
type

Scalene  Failure, and what's the fix?


data Triangle  =  Failure
   |  Equilateral
   |  Isosceles
   |  Scalene
   deriving (Eq, Show)

instance Ord Triangle where
Failure  Failure  = False
Failure  _= True

Equilateral  Failure  = False
Equilateral  Equilateral  = False
Equilateral  _= True

IsoscelesScalene  = True
Isosceles_= False

Scalene  _= False


(I tried submitting this to beginn...@haskell.org, but even though  
I've signed up for that mailing list, I got a bounce-back saying  
that I needed admin approval to submit anything to that list, and I  
haven't heard from an admin, so I'm posting it here.)



The New Busy is not the too busy. Combine all your e-mail accounts  
with Hotmail. Get busy.___

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] FW: Why does this Ord-class instance crash?

2010-05-21 Thread Daniel Fischer
On Friday 21 May 2010 19:06:51, R J wrote:
 Why does the following, trivial  code snippet below hang GHCi when I
 typeScalene  Failure, and what's the fix?

For an Ord instance, you need to define at least one of compare and (=) or 
the other functions from the class won't work.
All methods have default implementations in terms of compare, compare has a 
default implementation in terms of (=).
If you only implement () and then query (), it's going in circles.

Fixes:
a) implement compare or (=)
b) choose the correct order for the constructors and add Ord to the 
deriving clause.


 data Triangle  =  Failure  
 |  Equilateral   |  Isosceles   
|  Scalene   deriving (Eq,
 Show) instance Ord Triangle whereFailure  Failure  = False 
   Failure  _= True Equilateral  Failure  = False  
  Equilateral  Equilateral  = FalseEquilateral  _= True
 IsoscelesScalene  = TrueIsosceles_= False
 Scalene  _= False

Your newlines never make it to my mail programme, is your mail programme 
configured to send only '\r' and not '\n' ?


 (I tried submitting this to beginn...@haskell.org, but even though I've
 signed up for that mailing list, I got a bounce-back saying that I
 needed admin approval to submit anything to that list, and I haven't
 heard from an admin, so I'm posting it here.)

If you sent very shortly after subscribing, your subscription may not have 
been registered by the watchdog. If you continue to have problems you 
should contact the list manager.

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


Re: [Haskell-cafe] ambiguous type variable problem when using forall, multiparameter type classes, and constraints on polymorphic values (and syb-with-class)

2010-05-21 Thread C. McCann
On Fri, May 21, 2010 at 12:30 PM, Jeremy Shaw jer...@n-heptane.com wrote:
 Adding all the scoped type variable stuff does not seem to help. Alas,
 I can not figure out if this is a limitation of the type-checker, or
 something that is fundamentally impossible. Nor can I figure out how
 to work around the issue.

It's either one, depending on how you look at. To explain:

 The problem I have is when I try to add an additional constraint on 'm',
 such as (Monad m) =

 -- bar2 :: forall a m r. (Monad m, Data (Foo m) a, Num r) = a - r
 -- bar2 x = sum $ gmapQ (undefined :: Proxy (Foo m)) (bar2 :: forall b.
 (Monad m, Data (Foo m) b, Num r) = b - r) x

How might the compiler decide what specific m is meant when this
function is called, so that it can make sure that it's always a Monad?
All it has to work with are a and r. The only connection to m is
via the Data instance, but the second parameter to Data alone is not
really sufficient to find a specific instance--in fact, there could
well be multiple such instances.

 bar1 :: forall a m r. (Data (Foo m) a, Num r) = a - r
 bar1 x = sum $ gmapQ (undefined :: Proxy (Foo m)) bar1 x

Note that m is actually ambiguous here as well, but GHC won't
complain until it needs to care about the specific type. If everything
looks fully polymorphic GHC will just shrug, but by adding a class
constraint to the definition's context, you force the issue.

A classic, minimalist example of this problem--class constraints on
types that don't appear in the function signature--is the function
show . read. The type is just  String - String, but the behavior
depends on an unknown intermediate type.

 In my real code I need to define the data instance like:

 -- instance (Monad m) = Data (Foo m) a

 Which, by itself is fine. But that results in my needing to add (Monad
 m) to the 'bar' function. And that is what I can't figure out how to
 do..

The question you should answer first is: How do you expect the bar
function to know which monad to use--or, if it doesn't matter which
monad it picks, why do you care that it's given a monad at all?

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


[Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-21 Thread Anatoly Yakovenko
anyone else seeing this behavior?

anato...@anatolyy-linux ~ $ ghci
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
 1/2
0.5
*** Exception: : changeWorkingDirectory: does not exist (No such file
or directory)
 1/2
*** Exception: : changeWorkingDirectory: does not exist (No such file
or directory)

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


Re: [Haskell-cafe] Exception: : changeWorkingDirectory: does not exist (No such file or directory)

2010-05-21 Thread Daniel Fischer
On Friday 21 May 2010 20:50:39, Anatoly Yakovenko wrote:
 anyone else seeing this behavior?

 anato...@anatolyy-linux ~ $ ghci
 GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.

  1/2

 0.5
 *** Exception: : changeWorkingDirectory: does not exist (No such file
 or directory)

  1/2

 *** Exception: : changeWorkingDirectory: does not exist (No such file
 or directory)

Never seen that.
Just to make sure, there's nothing in any of your .ghci files that might 
cause it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Daniel van den Eijkel

Dear Haskellers,

I just want to share an observation. I had to convert a Double to a 
Float value in an inner loop of an application, and I used somethin like 
this:


xf = (fromRational $ toRational xd) :: Float

The program works on windows but it did not on OSX - it was too slow. 
Now, after big headaches and much frustration, I replaced the code above 
with this line (why didn't I come up with this earlier?):


xf = double2Float xd

and now everything works just fine.

I am not really surprised by the speed-up (and no-one should be), but I 
am still surprised how often such kinds of unobvious problems occur 
while programming in Haskell. So I write this email just to remind me 
and you to look out for such pitfalls.


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


Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Henning Thielemann


On Fri, 21 May 2010, Daniel van den Eijkel wrote:


Dear Haskellers,

I just want to share an observation. I had to convert a Double to a Float 
value in an inner loop of an application, and I used somethin like this:


xf = (fromRational $ toRational xd) :: Float


I think realToFrac is the function to use here, and this might be replaced 
by double2Float by an optimizer rule. I think double2Float is from a GHC 
package and thus one should avoid to call double2Float directly.

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


Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Daniel van den Eijkel

I see. And I changed the code, it works well. Thanks for that!
Daniel


Henning Thielemann schrieb:


On Fri, 21 May 2010, Daniel van den Eijkel wrote:


Dear Haskellers,

I just want to share an observation. I had to convert a Double to a 
Float value in an inner loop of an application, and I used somethin 
like this:


xf = (fromRational $ toRational xd) :: Float


I think realToFrac is the function to use here, and this might be 
replaced by double2Float by an optimizer rule. I think double2Float is 
from a GHC package and thus one should avoid to call double2Float 
directly.



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


Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Daniel Fischer
On Friday 21 May 2010 22:06:43, Henning Thielemann wrote:
 On Fri, 21 May 2010, Daniel van den Eijkel wrote:
  Dear Haskellers,
 
  I just want to share an observation. I had to convert a Double to a
  Float value in an inner loop of an application, and I used somethin
  like this:
 
  xf = (fromRational $ toRational xd) :: Float

 I think realToFrac is the function to use here, and this might be
 replaced by double2Float by an optimizer rule. I think double2Float is
 from a GHC package and thus one should avoid to call double2Float
 directly.

In GHC.Real:

-- | general coercion to fractional types
realToFrac :: (Real a, Fractional b) = a - b
realToFrac = fromRational . toRational

{-# RULES
realToFrac/Int-Int realToFrac = id :: Int - Int
#-}

There are more rules elsewhere. If you compile with optimisations, GHC 
turns your realToFrac into double2Float# nicely, so it's okay to use 
realToFrac.
However, without optimisations, no rules fire, so you'll get 
(fromRational . toRational).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Don Stewart
dvde:
 Dear Haskellers,

 I just want to share an observation. I had to convert a Double to a  
 Float value in an inner loop of an application, and I used somethin like  
 this:

 xf = (fromRational $ toRational xd) :: Float

 The program works on windows but it did not on OSX - it was too slow.  
 Now, after big headaches and much frustration, I replaced the code above  
 with this line (why didn't I come up with this earlier?):

 xf = double2Float xd

 and now everything works just fine.

 I am not really surprised by the speed-up (and no-one should be), but I  
 am still surprised how often such kinds of unobvious problems occur  
 while programming in Haskell. So I write this email just to remind me  
 and you to look out for such pitfalls.

There's no rewrite rule for this optimization. There's a ticket though
with some of the solutions.

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


Re: [Haskell-cafe] double2Float is faster than (fromRational . toRational)

2010-05-21 Thread Pierre-Etienne Meunier
By the way, speaking of floating-point precision, is there a real reason why 
haskell forces us to write :

foreign import ccall unsafe math.h frexp c_frexp::CDouble-(Ptr CInt)-IO ()
foreign import ccall unsafe math.h ldexp c_ldexp::CDouble-CInt-IO CDouble

ulp::Double-Double
ulp x=unsafePerformIO $ do
  expon-alloca (\e-do
c_frexp (realToFrac x) e
peek e)
  (c_ldexp 0.5 $ expon-52) = return.realToFrac

To allow us to change the IEEE-754 rounding mode ? Shouldn't it be rather 
roundDown $ x+3*y/z or roundUp $ (cos x)**y ?

Moreover, due to laziness it appears quite difficult (at least to me !) to 
implement these roundDown and roundUp functions with C calls to select a 
hardware rounding mode, then unsafePerformIO. It would be way faster than an 
allocation (on the stack, I agree), then C calls with a memory access (probably 
cached, but...) in between !

Does anyone know how this translates to LLVM (maybe in the forthcoming GHC 
backend) ?
If anyone has got an answer or a solution...

Cheers,
PE

El 21/05/2010, a las 17:10, Don Stewart escribió:

 dvde:
 Dear Haskellers,
 
 I just want to share an observation. I had to convert a Double to a  
 Float value in an inner loop of an application, and I used somethin like  
 this:
 
 xf = (fromRational $ toRational xd) :: Float
 
 The program works on windows but it did not on OSX - it was too slow.  
 Now, after big headaches and much frustration, I replaced the code above  
 with this line (why didn't I come up with this earlier?):
 
 xf = double2Float xd
 
 and now everything works just fine.
 
 I am not really surprised by the speed-up (and no-one should be), but I  
 am still surprised how often such kinds of unobvious problems occur  
 while programming in Haskell. So I write this email just to remind me  
 and you to look out for such pitfalls.
 
 There's no rewrite rule for this optimization. There's a ticket though
 with some of the solutions.
 
 -- Don
 ___
 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] Proof question -- (==) over Bool

2010-05-21 Thread R J

I'm trying to prove that (==) is reflexive, symmetric, and transitive over the 
Bools, given this definition:
(==)   :: Bool - Bool - Boolx == y =  
(x  y) || (not x  not y)
My question is:  are the proofs below for reflexivity and symmetricity 
rigorous, and what is the proof of transitivity, which eludes me?  Thanks. 
Theorem (reflexivity):  For all x `elem` Bool, x == x.
Proof:
  x == x  ={definition of ==}  (x  x) || (not x  not x)  =
{logic (law of the excluded middle)}  True
Theorem (symmetricity):  For all x, y `elem` Bool, if x == y, then y == x.
Proof:
  x == y  ={definition of ==}  (x  y) || (not x  not y)  =
{lemma:  () is commutative}  (y  x) || (not x  not y)  ={lemma: 
 () is commutative}  (y  x) || (not y  not x)  ={definition of 
==}  y == x
Theorem (transitivity):  For all x, y, z `elem` Bool, if x == y, and y == 
z,then x == z.
Proof: ?  
_
Hotmail has tools for the New Busy. Search, chat and e-mail from your inbox.
http://www.windowslive.com/campaign/thenewbusy?ocid=PID28326::T:WLMTAGL:ON:WL:en-US:WM_HMP:042010_1___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] making the GHC Api not write to stderr

2010-05-21 Thread Daniel Peebles
Have you tried freopen on stderr?

On Fri, May 21, 2010 at 8:43 AM, Phyx loneti...@gmail.com wrote:

 Hi,
 I tried that, setting it to (\_ _ _ _ - return ()) and it still did the
 same, also tried setting it to undefined to see whether the code that's
 printing the error is using it, and it didn't crash
 So I assume it's not.

 ---
 *VsxParser getModInfo True
 C:\\Users\\Phyx\\AppData\\Local\\Temp\\tmp5600.hs
   return ()

 C:\Users\Phyx\AppData\Local\Temp\tmp5600.hs:11:13:
parse error on input `='
 Printf
 -

 I think parseModule might still have a hardcoded print statement in it.

 -Original Message-
 From: Thomas Schilling [mailto:nomin...@googlemail.com]
 Sent: Friday, May 21, 2010 12:53
 To: Phyx
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] making the GHC Api not write to stderr

 You could try changing the log_action[1] member of the DynFlags.  A while
 ago I turned most printed errors into some form of error message, but I
 wouldn't be surprised if I missed some places.  All output should go
 through
 log_action, though, so try changing that to intercept any output.

 [1]:

 http://haskell.org/ghc/docs/6.12-latest/html/libraries/ghc-6.12.2/DynFlags.h
 tml#v%3Alog_action

 On 20 May 2010 19:05, Phyx loneti...@gmail.com wrote:
  I was wondering how to forcibly quiet down the API. I have a custom
  handler in place, but when I call the function on failure both my
  handler gets called and somewhere somehow errors get printed to the
  stderr, which I really need to avoid.
 
 
 
  My current code looks like
 
 
 
  getModInfo :: Bool - String - String - IO (ApiResults ModuleInfo)
 
  getModInfo qual file path = handleSourceError processErrors $
 
  runGhc (Just libdir) $ do
 
  dflags - getSessionDynFlags
 
  setSessionDynFlags $ configureDynFlags dflags
 
  target - guessTarget file Nothing
 
  addTarget target
 
  setSessionDynFlags $ dflags { importPaths = [path] }
 
  load LoadAllTargets
 
  graph - depanal [] False
 
  let modifier = moduleName . ms_mod
 
  modName  = modifier $ head graph
 
  includes = includePaths dflags
 
  imports  = importPaths dflags
 
 
 
  dflags' - Debug.trace (moduleNameString modName)
  getSessionDynFlags
 
  setSessionDynFlags $ dflags' { includePaths = path:includes
 
   , importPaths  = path:imports
 
   }
 
 
 
  parsed  - parse modName
 
  checked - typecheckModule parsed
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 



 --
 Push the envelope.  Watch it bend.

 ___
 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] Enum instantiation

2010-05-21 Thread R J

I'd like to make Day an instance of class Enum, but the definition of 
toEnum below seems to be completely wrong, because integers seem not permit 
pattern matching.  How is toEnum defined?  Thanks.
data Day   =  Sunday   |  Monday
   |  Tuesday   |  Wednesday
   |  Thursday   |  Friday  
 |  Saturday   deriving (Eq, Ord, Show)
instance Enum Day wherefromEnum Sunday=  0fromEnum Monday   
 =  1fromEnum Tuesday   =  2fromEnum Wednesday =  3fromEnum 
Thursday  =  4fromEnum Friday=  5fromEnum Saturday  =  
6toEnum 0   =  SundaytoEnum 1   =  Monday   
 toEnum 2   =  TuesdaytoEnum 3   =  Wednesday
toEnum 4   =  ThursdaytoEnum 5   =  Friday
toEnum 6   =  Saturday  
_
Hotmail is redefining busy with tools for the New Busy. Get more from your 
inbox.
http://www.windowslive.com/campaign/thenewbusy?ocid=PID28326::T:WLMTAGL:ON:WL:en-US:WM_HMP:042010_2___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Enum instantiation

2010-05-21 Thread Antoine Latter
2010/5/21 R J rj248...@hotmail.com:
 I'd like to make Day an instance of class Enum, but the definition of
 toEnum below seems to be completely wrong, because integers seem not permit
 pattern matching.  How is toEnum defined?  Thanks.

Hi,

What error are you getting when you try your class instance?

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


Re: [Haskell-cafe] Enum instantiation

2010-05-21 Thread Gregory Collins
R J rj248...@hotmail.com writes:

 I'd like to make Day an instance of class Enum, but the definition
 of toEnum below seems to be completely wrong, because integers seem
 not permit pattern matching.  How is toEnum defined?  Thanks.

You could try using guards:

 toEnum x | x == 0= Sunday
  | x == 1= Monday
  | x == 2= Tuesday
  | x == 3= Wednesday
  | x == 4= Thursday
  | x == 5= Friday
  | x == 6= Saturday
  | otherwise = error bad enum

BTW if none of your constructors have fields you can just add Enum to
the deriving (...) list for your type, and the compiler will write
basically the same instance for you.

G.
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proof question -- (==) over Bool

2010-05-21 Thread Luke Palmer
2010/5/21 R J rj248...@hotmail.com:
 I'm trying to prove that (==) is reflexive, symmetric, and transitive over
 the Bools, given this definition:
 (==)                       :: Bool - Bool - Bool
 x == y                     =  (x  y) || (not x  not y)
 My question is:  are the proofs below for reflexivity and symmetricity
 rigorous, and what is the proof of transitivity, which eludes me?  Thanks.

 Theorem (reflexivity):  For all x `elem` Bool, x == x.
 Proof:
       x == x
   =    {definition of ==}
       (x  x) || (not x  not x)
   =    {logic (law of the excluded middle)}
       True

This one depends on what you mean by rigorous.  But you would have to
have lemmas showing that  and || correspond to the predicate logic
notions.  I would do this by cases:

x = True:
  (True  True) || (not True  not True)
  ...
  True || False
  True
x = False
  (False  False) || (not False  not False)
  ...
  False || True
  True



 Theorem (symmetricity):  For all x, y `elem` Bool, if x == y, then y == x.
 Proof:
       x == y
   =    {definition of ==}
       (x  y) || (not x  not y)
   =    {lemma:  () is commutative}
       (y  x) || (not x  not y)
   =    {lemma:  () is commutative}
       (y  x) || (not y  not x)
   =    {definition of ==}
       y == x

Yes, given the lemmas about  and ||, this is rigorous.  You can
prove those lemmas by case analysis.

 Theorem (transitivity):  For all x, y, z `elem` Bool, if x == y, and y == z,
 then x == z.
 Proof: ?

My first hunch here is to try the following lemma:

  Lemma: if (x == y) = True if and only if x = y.

where == is the version you defined, and = is regular equality from
logic, if you are allowed to rely on that.  I would prove this by
cases.

At this point, you can convert transitivity of == to transitivity of
=, which is assumed by the axioms.  You could do the same for the
other proofs you asked about instead of brute-forcing them.

If you aren't allowed such magic, then I guess you could do all 8
cases of x, y, and z (i.e. proof by truth table).  Somebody else might
have a cleverer idea.

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


Re: [Haskell-cafe] Enum instantiation

2010-05-21 Thread Antoine Latter
On Fri, May 21, 2010 at 8:59 PM, R J rj248...@hotmail.com wrote:
 If I type toEnum 5, the error I get is:
 interactive:1:0:
     Ambiguous type variable `a' in the constraint:
       `Enum a' arising from a use of `toEnum' at interactive:1:0-7
     Probable fix: add a type signature that fixes these type variable(s)
 *Main

Here the problem is not in your instance of Enum, but that GHCi
doesn't know which instance of enum to use.

In most code this isn't a problem, because the surrounding context
often gives enough information for the type-checker to work with.

But when there isn't enough context, you'll need to provide a type signature.

Does toEnum 5 :: Day work?

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


[Haskell-cafe] [ANNOUNCE] First Public Release of the Snap Framework

2010-05-21 Thread Gregory Collins
Hello all,

To coincide with Hac Phi 2010
(http://www.haskell.org/haskellwiki/Hac_%CF%86), the Snap team is happy
to announce the first public release of the Snap Framework, a simple and
fast Haskell web programming server and library for unix systems. For
installation instructions, documentation, and more information, see our
website at http://snapframework.com/.

Snap is well-documented and has a test suite with a high level of code
coverage, but it is early-stage software with still-evolving interfaces. Snap
is therefore most likely to be of interest to early adopters and potential
contributors.

Snap is BSD-licensed and currently only runs on Unix platforms; it has been
developed and tested on Linux and Mac OSX Snow Leopard.

Snap Features:

 * A simple and clean monad for web programming, similar to happstack's but
   simpler.

 * A *fast* HTTP server library with an optional high-concurrency backend
   (using libev).

 * An XML-based templating system for generating xhtml that allows you to bind
   Haskell functionality to XML tags in your templates.

 * Some useful utilities for web handlers, including gzip compression and
   fileServe.

 * Iteratee-based I/O, allowing composable streaming in O(1) space without any
   of the unpredictable consequences of lazy I/O.

If you have questions or comments, please contact us on our mailing list
(http://mailman-mail5.webfaction.com/listinfo/snap) or in the
#snapframework channel on the freenode IRC network.

Cheers,
G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe