Re: [Haskell-cafe] Problem with haddock 2.3.0 (again)

2008-12-12 Thread Sean Leather
   Call the original haddockHook with the updated flags rather
   than the
   haddock command.

 main = defaultMainWithHooks simpleUserHooks {
  haddockHook = \pkg lbi h f -
 let progs = userSpecifyArgs haddock [--optghc=-D__HADDOCK__]
  (withPrograms lbi)
 in haddockHook simpleUserHooks pkg lbi { withPrograms = progs } h f
 }


This worked. Thanks, Duncan.

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


Re: [Haskell-cafe] Problem with haddock 2.3.0 (again)

2008-12-12 Thread Sean Leather
  I've been using cabal haddock to run haddock on my package. I also
  get the same error using haddock directly:
 
   $ haddock -odir=tmp --debug --verbose --html
  Generics/EMGM.hs
   haddock: internal Haddock or GHC error: Maybe.fromJust: Nothing

 Have you filed a ticket for this in the haddock trac so that he doesn't
 forget?
 http://trac.haskell.org/haddock/


There seemed to be perhaps one or two tickets related, but I wasn't sure if
any exactly matched the issue, so I created a new one with a minimal
testcase.

http://trac.haskell.org/haddock/ticket/68

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


Re: [Haskell-cafe] A curios monad

2008-12-12 Thread Martijn van Steenbergen

Andrew Coppin wrote:
In other words, you can store a value (of arbitrary type) under a unique 
key. The monad chooses what key for you, and tells you the key so you 
can look up or alter the value again later. Under the covers, it uses 
Data.Map to store stuff. I used some trickery with existential 
quantification and unsafeCoerce (!!) to make it work. Notice the sneaky 
phantom type in the key, telling the type system what type to coerce the 
value back to when you read it. Neat, eh?


I did exactly that in my Yogurt project[1]. It felt dirty but in a good 
way, mostly because the interface was exactly what I needed. :-)


...until I realised that somebody that somebody could generate a key in 
one run and then try to use it in another run. o_O


I've worried about this but I couldn't find a good code example of when 
this goes wrong. Can you? Without using any of the unsafeXxx functions, 
of course.


Maybe I should build my monad on top of the ST monad if that makes 
things safer.


Martijn.


[1] 
http://hackage.haskell.org/packages/archive/Yogurt/0.2/doc/html/Network-Yogurt-Mud.html#5

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


Re: [Haskell-cafe] Problem with haddock 2.3.0 (again)

2008-12-12 Thread Sean Leather
  I've been using cabal haddock to run haddock on my package. I also
  get the same error using haddock directly:
 
   $ haddock -odir=tmp --debug --verbose --html
  Generics/EMGM.hs
   haddock: internal Haddock or GHC error: Maybe.fromJust: Nothing

 Have you filed a ticket for this in the haddock trac so that he doesn't
 forget?
 http://trac.haskell.org/haddock/


 There seemed to be perhaps one or two tickets related, but I wasn't sure if
 any exactly matched the issue, so I created a new one with a minimal
 testcase.

 http://trac.haskell.org/haddock/ticket/68


And for anyone who later comes upon this thread seeking an answer to a
similar problem, this is apparently a bug in the GHC API on which Haddock is
dependent:

http://hackage.haskell.org/trac/ghc/ticket/2739

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


Re: [Haskell-cafe] Problem with haddock 2.3.0 (again)

2008-12-12 Thread Thomas Schilling
The fromJust error is a bug, of course, however, the underlying
problem is a bit more difficult:

Haddock doesn't generate any code, it only typechecks.  If the code
uses Template Haskell, however, the typechecker will have to run
Haskell code and potentially this code will have to come from a module
of the same package.  If the code indeed comes from the same package,
fixing the fromJust error will just lead to GHCi linker error, since
Haddock didn't generate any code for these.

Here are a couple of solutions and non-solutions:

  - Detect whether a package uses TH by looking at the ghc flags and
the OPTIONS pragmas.  This might work in many cases, but:

  - We cannot generate Bytecode for all modules, because unboxed
tuples and foreign exports are not supported by GHCi.  This drawback
would only affect a few packages, though, and cpp magic could hide the
tricky parts from Haddock.

  - The bigger issue is security.  TH can run arbitrary IO actions
so, by default, we should just fail, and only enable it if the user
says so.

 - Skip modules using TH.  Won't work, because other modules may
depend on those modules.  We also cannot know which modules may
require TH if the flag is set globally.

 - Disallow TH.  That'll require a way to use #ifdef's to show
alternative code.  I guess, that's the current workaround.

 - Do a best-effort Renaming pass and run the typechecker without
trying to resolve Splices.  Lot's of work and may result to incorrect
documentation, so I'm not sure it's worth it.

Any other?

/ Thomas

2008/12/12 Sean Leather leat...@cs.uu.nl:

  I've been using cabal haddock to run haddock on my package. I also
  get the same error using haddock directly:
 
   $ haddock -odir=tmp --debug --verbose --html
  Generics/EMGM.hs
   haddock: internal Haddock or GHC error: Maybe.fromJust: Nothing

 Have you filed a ticket for this in the haddock trac so that he doesn't
 forget?
 http://trac.haskell.org/haddock/

 There seemed to be perhaps one or two tickets related, but I wasn't sure
 if any exactly matched the issue, so I created a new one with a minimal
 testcase.

 http://trac.haskell.org/haddock/ticket/68

 And for anyone who later comes upon this thread seeking an answer to a
 similar problem, this is apparently a bug in the GHC API on which Haddock is
 dependent:

 http://hackage.haskell.org/trac/ghc/ticket/2739

 Regards,
 Sean

 ___
 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] Re: Windows vs. Linux x64

2008-12-12 Thread Simon Marlow

John Meacham wrote:

On Tue, Nov 25, 2008 at 09:39:35PM +0100, Ketil Malde wrote:

This corresponds to my experiences - 64 bits is slower, something I've
ascribed to the cost of increased pointer size.


ghc unfortunatly also uses 64 bit integers when in 64 bit mode, so the
cost paid is increased due to that as well, Also since each math
instruction needs an extra byte telling it to work on 64 bit data so the
code is less dense.


Right - in the Java world they use tricks to keep pointers down to 32-bits 
on a 64-bit platform, e.g. by shifting pointers by a couple of bits (giving 
you access to 16Gb).  There are a number of problems with doing this in 
GHC, though:


 - we already use those low pointer bits for encoding tag information.
   So perhaps we could take only one bit, giving you access to 8Gb,
   and lose one tag bit.

 - it means recompiling *everything*.  It's a complete new way, so you
   have to make the decision to do this once and for all, or build all
   your libraries + RTS twice.  In JITed languages they can make the
   choice at runtime, which makes it much easier.

 - it tends to be a bit platform-specific, because you need a base
   address in the address space for your 16Gb of memory, and different
   platforms lay out the address space differently.  The nice thing about
   GHC's memory manager is that it currently has *no* dependencies on
   address-space layout (except in the ELF64 dynamic linker... sigh).

 - as usual with code-generation knobs, it multiplies the testing
   surface, which is something we're quite sensitive to (our surface is
   already on the verge of being larger than we can cope with given our
   resources).

So my current take on this is that it isn't worth it just to get access to 
more memory and slightly improved performance.  However, perhaps we should 
work on making it easier to use the 32-bit GHC on 64-bit platforms - IIRC 
right now you have to use something like -opta-m32 -optc-m32.


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


[Haskell-cafe] Re: Data.Array.Storable vs GC

2008-12-12 Thread Simon Marlow

John Meacham wrote:

GHC has 'pinned arrays' that have this behavior. however, you probably
don't want to use them as they simply give the garbage collector less
choices about what to do possibly decreasing its efficiency. The garbage
collector already is free to not copy arrays if it feels it isn't worth
it, by pinning them you simply take away its ability to choose to do so
if it is needed.


To be a little more concrete, all arrays larger than ~3k are effectively 
pinned in GHC right now, as in they are never copied.  If the array is 
unboxed, then it is never traversed by the GC either, so large unboxed 
arrays have basically zero GC cost.  There's no need for any help from the 
programmer, it's done automatically by the GC.


For smaller arrays, as John says there's a tradeoff in whether to pin them 
or not.  Pinning avoids copying in the GC, but might lead to fragmentation. 
 Pinning is necessary if you want to pass the address of the memory to an 
FFI call at any point, which is why bytestring pins its arrays.


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


Re: [Haskell-cafe] Problem with haddock 2.3.0 (again)

2008-12-12 Thread Sean Leather
On Fri, Dec 12, 2008 at 13:22, Thomas Schilling wrote:

 The fromJust error is a bug, of course, however, the underlying
 problem is a bit more difficult:

 Haddock doesn't generate any code, it only typechecks.  If the code
 uses Template Haskell, however, the typechecker will have to run
 Haskell code and potentially this code will have to come from a module
 of the same package.  If the code indeed comes from the same package,
 fixing the fromJust error will just lead to GHCi linker error, since
 Haddock didn't generate any code for these.


Thanks for enlightening us, Thomas.

Here are a couple of solutions and non-solutions:


[...]


 Any other?


What about the eventual (maybe never?) solution of collecting comments and
types for Haddock after splicing in code? This is more long term, perhaps,
but in the end ideal if it can be made to work.

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


Re: [Haskell-cafe] Memoization-question

2008-12-12 Thread Bertram Felgenhauer
Mattias Bengtsson wrote:
 The program below computes (f 27) almost instantly but if i replace the
 definition of (f n) below with (f n = f (n - 1) * f (n -1)) then it
 takes around 12s to terminate. I realize this is because the original
 version caches results and only has to calculate, for example, (f 25)
 once instead of (i guess) four times.
 There is probably a good reason why this isn't caught by the compiler.
 But I'm interested in why. Anyone care to explain?

GHC does opportunistic CSE, when optimizations are enabled. See

http://www.haskell.org/haskellwiki/GHC:FAQ#Does_GHC_do_common_subexpression_elimination.3F
(http://tinyurl.com/33q93a)

I've found it very hard to predict whether this will happen or not, from
a given source code, because the optimizer will transform the program a
lot and the opportunistic CSE rule may apply to one of the transformed
versions.

It's best to make sharing explicit when you need it, as you did below.

  main = print (f 27)
  
  f 0 = 1
  f n = let f' = f (n-1)
in f' * f'

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


Re: [Haskell-cafe] A curios monad

2008-12-12 Thread Ryan Ingram
On Fri, Dec 12, 2008 at 2:48 AM, Martijn van Steenbergen
mart...@van.steenbergen.nl wrote:
 I've worried about this but I couldn't find a good code example of when this
 goes wrong. Can you? Without using any of the unsafeXxx functions, of
 course.

 Maybe I should build my monad on top of the ST monad if that makes things
 safer.

 [1]
 http://hackage.haskell.org/packages/archive/Yogurt/0.2/doc/html/Network-Yogurt-Mud.html#5

Here's a simple example:

runMud :: Mud a - a
runMud = flip evalState emptyMud

main = do
let v = runMud (mkVar hello)
let crash = runMud $ do
v2 - mkVar True  -- v2 :: Var Bool
res - readVar v -- v :: Var String
return res
print crash -- boom!

Both v2 and v are the same variable index (0), but different types.
Since there's nothing preventing the variable from escaping from the
first runMud, we can import it into the second one where it fails.
The key is that both use the same initial state, so you have lost
the uniqueness of variables.

ST is safer, although you can make these systems just as safe with the
phantom state type like ST does.  It's also faster; variables turn
directly into pointer references, instead of traversing an IntMap.
But it gets kind of annoying writing all the extra s on your type
signatures.

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


[Haskell-cafe] gtk2hs question - derive SettingsWindow from Window

2008-12-12 Thread Cetin Sert
Hi all,

For a network manager of sorts I'm working on, I want to derive a
SettingsWindowClass from the WindowClass present in Gtk2Hs:

I want (the) instance(s) of the SettingsWindowClass to have a field to store
connection settings:

1) Is it safe to do it like this?

class WindowClass self ⇒ SettingsWindowClass self where
  settingsWindowGetSettings :: self → IO [ConnectionSetting]
  settingsWindowSetSettings :: self → [ConnectionSetting] → IO ()

newtype SettingsWindow = SettingsWindow (Window,[ConnectionSetting])

mkSettingsWindow = SettingsWindow
unSettingsWindow (SettingsWindow o) = o

settingsWindowNew :: IO SettingsWindow
settingsWindowNew = do
  win ← windowNew
  return $ mkSettingsWindow (win,[])

2) Is this a common practice in gtk2hs usage?
3) And will GC properly free the memory allocated for the Window object? How
is this ensured, do ForeignPtr's always call delete on the underlying C ptr
when they get garbage collected?

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


Re: [Haskell-cafe] A curios monad

2008-12-12 Thread Martijn van Steenbergen

Ryan Ingram wrote:

Here's a simple example:

runMud :: Mud a - a
runMud = flip evalState emptyMud

main = do
let v = runMud (mkVar hello)
let crash = runMud $ do
v2 - mkVar True  -- v2 :: Var Bool
res - readVar v -- v :: Var String
return res
print crash -- boom!

Both v2 and v are the same variable index (0), but different types.
Since there's nothing preventing the variable from escaping from the
first runMud, we can import it into the second one where it fails.
The key is that both use the same initial state, so you have lost
the uniqueness of variables.


Ah, yes, of course, thank you. :-) I was trying to break it from within 
the monad.


Martijn.

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


[Haskell-cafe] Parsec and (then?) type-check

2008-12-12 Thread Greg Fitzgerald
Parser gurus,

When you write a parser with a library like Parsec, do you typically
type-check while parsing, or afterward in a separate pass?  The latter
is more modular, but it means labeling every element in the AST with
the parser position so that you can give good error messages.  Do you
find the added modularity worth the hassle or just pack type-checking
into the parser pass?

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


Re: [Haskell-cafe] Parsec and (then?) type-check

2008-12-12 Thread sam lee
I use my type checking monad, which is separate from Parsec's monad.
So, I can't think of a way to type check during parsing in Parsec's monad.

Anyways, this is what I did:

data Expr = ... | At SourcePos Expr

SourcePos is from Parsec.

Basically, my parse actions will return (At pos e).

And I pass At pos e to typeCheck action.

typeCheck (At pos e) = do
put pos
-- typeCheck is in State monad.
-- in case of error, I'll pos - get and report source position.
typeCheck e

typeCheck (Variable a) = do
   ...

check out this:
http://www.lipl.googlepages.com/index.html#source


On Fri, Dec 12, 2008 at 5:06 PM, Greg Fitzgerald gari...@gmail.com wrote:
 Parser gurus,

 When you write a parser with a library like Parsec, do you typically
 type-check while parsing, or afterward in a separate pass?  The latter
 is more modular, but it means labeling every element in the AST with
 the parser position so that you can give good error messages.  Do you
 find the added modularity worth the hassle or just pack type-checking
 into the parser pass?

 Thanks,
 Greg
 ___
 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] Numerics implementing different instances of the same class

2008-12-12 Thread George Pollard
Is there a good way of doing this? My running example is Monoid:

 class Monoid a where
   operation :: a - a - a
   identity :: a

With the obvious examples on Num:

 instance (Num a) = Monoid a where
   operation = (+)
   identity = 1
 
 instance (Num a) = Monoid a where
   operation = (*)
   identity = 0

Of course, this won't work. I could introduce a newtype wrapper:

 newtype (Num a) = MulNum a = MulNum a
 newtype (Num a) = AddNum a = AddNum a
 
 instance (Num a) = Monoid (MulNum a) where
   operation (MulNum x) (MulNum y) = MulNum (x * y)
   identity = MulNum 1
 
 instance (Num a) = Monoid (AddNum a) where ... -- etc

However, when it comes to defining (e.g.) a Field class you have two
Abelian groups over the same type, which won't work straight off:

 class Field a where ...
 instance (AbelianGroup a, AbelianGroup a) = Field a where ...

Could try using the newtypes again:
 
 instance (AbelianGroup (x a), AbelianGroup (y a) = Field a where ...

... but this requires undecidable instances. I'm not even sure if it
will do what I want. (For one thing it would also require an indication
of which group distributes over the other, and this may restore
decidability.)

I'm beginning to think that the best way to do things would be to drop
the newtype wrappers and include instead an additional parameter of a
type-level Nat to allow multiple definitions per type. Is this a good
way to do things?

Has anyone else done something similar? I've taken a look at the Numeric
Prelude but it seems to be doing things a bit differently. (e.g. there
aren't constraints on Ring that require Monoid, etc)

- George


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


[Haskell-cafe] wlan library

2008-12-12 Thread Cetin Sert
Hi *^o^*,

I am writing a network manager http://sert.homedns.org/hnm/ as a
replacement for some broken, already existing knetworkmanager for a friend's
computer.

I was looking for some haskell libraries that provide access to wlan cards
but could not find any on hackage. Maybe I missed something. Currently my
tool is using linux the commands: modprobe, ifconfig, iwconfig, iwlist,
dhclient etc.. Can a library calling external stand-alone linux commands be
considered good enough as is? Or should one definitely write a wrapper
around a more low-level, stable, POSIX-compliant foreign library to access
and configure, control WLAN cards? I'd love to hear your comments.

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


Re: [Haskell-cafe] wlan library

2008-12-12 Thread Don Stewart
cetin.sert:
Hi *^o^*,
 
I am writing [1]a network manager as a replacement for some broken,
already existing knetworkmanager for a friend's computer.
 
I was looking for some haskell libraries that provide access to wlan cards
but could not find any on hackage. Maybe I missed something. Currently my
tool is using linux the commands: modprobe, ifconfig, iwconfig, iwlist,
dhclient etc.. Can a library calling external stand-alone linux commands
be considered good enough as is? Or should one definitely write a wrapper
around a more low-level, stable, POSIX-compliant foreign library to access
and configure, control WLAN cards? I'd love to hear your comments.

Hmm. For the long run, using the C FFI is probably more robust (a few
less points of failure). A binding to the shell commands will be cheaper
and more cheerful.

Go for it!

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


Re: [Haskell-cafe] Numerics implementing different instances of the same class

2008-12-12 Thread Dan Weston

What about something like

data AddMult a b = AddMult a b

class Monoid a where
  operation :: a - a - a
  identity  :: a

instance (Monoid a, Monoid b) = Monoid (AddMult a b) where
  operation  (AddMult a1 m1)
 (AddMult a2 m2)
   =  AddMult (operation a1 a2)
  (operation m1 m2)
  identity =  AddMult identity identity

class Commutative a where
  -- Nothing, this is a programmer proof obligation

class Monoid a = Group a where
  inverse :: a - a

class (Commutative a, Group a) = AbelianGroup a where

class (AbelianGroup a, AbelianGroup b) = Field a b where

instance AbelianGroup a = Field a a where


George Pollard wrote:

Is there a good way of doing this? My running example is Monoid:


class Monoid a where
operation :: a - a - a
identity :: a


With the obvious examples on Num:


instance (Num a) = Monoid a where
operation = (+)
identity = 1

instance (Num a) = Monoid a where
operation = (*)
identity = 0


Of course, this won't work. I could introduce a newtype wrapper:


newtype (Num a) = MulNum a = MulNum a
newtype (Num a) = AddNum a = AddNum a

instance (Num a) = Monoid (MulNum a) where
operation (MulNum x) (MulNum y) = MulNum (x * y)
identity = MulNum 1

instance (Num a) = Monoid (AddNum a) where ... -- etc


However, when it comes to defining (e.g.) a Field class you have two
Abelian groups over the same type, which won't work straight off:


class Field a where ...
instance (AbelianGroup a, AbelianGroup a) = Field a where ...


Could try using the newtypes again:

instance (AbelianGroup (x a), AbelianGroup (y a) = Field a where ...


... but this requires undecidable instances. I'm not even sure if it
will do what I want. (For one thing it would also require an indication
of which group distributes over the other, and this may restore
decidability.)

I'm beginning to think that the best way to do things would be to drop
the newtype wrappers and include instead an additional parameter of a
type-level Nat to allow multiple definitions per type. Is this a good
way to do things?

Has anyone else done something similar? I've taken a look at the Numeric
Prelude but it seems to be doing things a bit differently. (e.g. there
aren't constraints on Ring that require Monoid, etc)

- George




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


Re: [Haskell-cafe] Numerics implementing different instances of the same class

2008-12-12 Thread David Menendez
2008/12/12 George Pollard por...@porg.es:

 However, when it comes to defining (e.g.) a Field class you have two
 Abelian groups over the same type, which won't work straight off:

Especially since you generally can't take the multiplicative inverse
of the additive identity.

 I'm beginning to think that the best way to do things would be to drop
 the newtype wrappers and include instead an additional parameter of a
 type-level Nat to allow multiple definitions per type. Is this a good
 way to do things?

That depends on what you're trying to do. I don't think this is an
area where there is a single best solution.

I've occasionally toyed with labeled monoid classes, like this one:

class Monoid label a where
unit :: label - a
mult :: label - a - a - a

data Plus
instance (Num a) = Monoid Plus a where
unit _ = 0
mult _ = (+)

... and so forth.

Even here, there are several design possibilities. For example, here
the label and the carrier jointly determine the operation, but you can
also have the label determine the operation and the carrier.

Moving on, you can then have:

class (Monoid label a) = Group label a where
inverse :: label - a - a

class (Group labP a, Monoid labM a) = Ring labP labM a

Of course, you now need to provide labels for all your operations. I
suspect the overhead isn't worth it.

 Has anyone else done something similar? I've taken a look at the Numeric
 Prelude but it seems to be doing things a bit differently. (e.g. there
 aren't constraints on Ring that require Monoid, etc)

A couple of years ago, I suggested breaking Num into Monoid, Semiring,
Group, Ring, and something else for abs and signum.

http://www.haskell.org/pipermail/haskell-cafe/2006-September/018118.html

Thus,

class Monoid a where
zero :: a
(+) :: a - a - a

class (Monoid a) = Semiring a where
one :: a
(*) :: a - a - a

Semiring has laws which require one and (*) to form a monoid, so:

newtype Product a = Product a

instance (Semiring a) = Monoid (Product a) where
zero = Product one
Product x + Product y = Product (x * y)

Note that the Monoid instance is now a consequence of the Semiring
instance, rather than a requirement.

-- 
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


[Haskell-cafe] ghc on CentOS 5 ?

2008-12-12 Thread Steve Lihn
I recently got a CentOS server, but noticed that ghc rpm is not available
from CentOS yum. After investigation, I found ghc is in Fedora repository,
but does not make its way to EPEL, which yum on CentOS can use. (
http://download.fedora.redhat.com/pub/epel/5/x86_64/)

Is there any plan to get it to EPEL? Or is there any missing piece
preventing it?
Thanks, Steve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc on CentOS 5 ?

2008-12-12 Thread Jeff Heard
I had luck building the latest GHC from source using the ghc 6.6
binary build to bootstrap.  The 6.8+ binary builds run into a timer
issue, at least on 64 bit CentOS that causes them to bork out during
the configure script.

2008/12/12 Steve Lihn stevel...@gmail.com:
 I recently got a CentOS server, but noticed that ghc rpm is not available
 from CentOS yum. After investigation, I found ghc is in Fedora repository,
 but does not make its way to EPEL, which yum on CentOS can use.
 (http://download.fedora.redhat.com/pub/epel/5/x86_64/)

 Is there any plan to get it to EPEL? Or is there any missing piece
 preventing it?
 Thanks, Steve



 ___
 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