Re: [Haskell-cafe] MonadBaseControl IO instance for conduits ?

2013-10-11 Thread John Wiegley
 Aleksey Uymanov s9gf4...@gmail.com writes:

 Is it posible to create instance of MonadBaseControl IO (ConduitM i o m) ?

No, it is not, for approximately the same reason that you cannot create one
for ContT (or any form of continuation).

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-07 Thread John Wiegley
 Daniil Frumin difru...@gmail.com writes:

 Isn't it the case that there could be more than one natural transformation
 between functors?

Yes, I imagine there would have to be some newtype wrappers to distinguish in
those cases.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lifting IO actions into Applicatives

2013-10-01 Thread John Wiegley
 Yitzchak Gale g...@sefer.org writes:

 In fact, it even makes sense to define it as FunctorIO, with the only laws
 being that liftIO commutes with fmap and preserves id, i.e., that it is a
 natural transformation. (Those laws are also needed for ApplicativeIO and
 MonadIO.)

Given that we are moving toward Applicative (and thus Functor) as a superclass
of Monad, why not just solve the MonadIO problem and similar type classes with
natural transformations?  It requires 3 extensions, but these are extensions I
believe should become part of Haskell anyway:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}

module NatTrans where

import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe

class (Functor s, Functor t) = NatTrans s t where
nmap :: forall a. s a - t a
-- Such that: nmap . fmap f = fmap f . nmap

-- In 7.10, this Functor constraint becomes redundant
instance (Functor m, MonadIO m) = NatTrans IO m where
nmap = liftIO

main :: IO ()
main = void $ runMaybeT $ nmap $ print (10 :: Int)

Now if I have a functor of one kind and need another, I reach for nmap in the
same way that I reach for fmap to transform the mapped type.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Creating a local Hoogle ...

2013-09-23 Thread John Wiegley
 aditya siram aditya.si...@gmail.com writes:

 Combining 4263 databases hoogle: embroidery.hoo: openFile: resource
 exhausted (Too many open files)

 Any help is appreciated. Thanks!

I created the 'rehoo' utility to solve this very problem.  Change directory to
where your .hoo files are, and run:

rehoo -j4 -c64 .

Where 4 is for a 4-core machine.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] This is a mail system test, please ignore

2013-09-10 Thread John Wiegley
Testing the new e-mail services at haskell.org.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Please excuse brief service disruption

2013-09-10 Thread John Wiegley
The e-mail services at haskell.org were switched from exim4 to postfix
tonight, please excuse the service disruption.  For about one hour e-mails
were not being accepted to the mailing lists.  All should be resolved now.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-10 Thread John Wiegley
 Niklas Hambüchen m...@nh2.me writes:

 Code written in cucumber syntax is concise and easy to read

concise |kənˈsīs|, adj.

giving a lot of information clearly and in a few words; brief but
comprehensive.

Compare:

Scenario: Defining the function foldl
  Given I want do define foldl
  Which has the type (in brackets) a to b to a (end of brackets),
 to a, to list of b, to a
  And my arguments are called f, acc, and l
  When l is empty
  Then the result better be acc
  Otherwise l is x cons xs
  Then the result should be foldl f (in brackets) f acc x
(end of brackets) xs

To:

foldl :: (a - b - a) - a - [b] - a
foldl f z [] = z
foldl f z (x:xs) = foldl f (f z x) xs

How is that more concise or preferable?

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] definition of the term combinator

2013-08-23 Thread John Wiegley
 Jason Dagit dag...@gmail.com writes:

 Where can I find a formal and precise definition of the term
 combinator,

A function that uses nothing but its arguments.

 as a term used by the Haskell community to describe something?

I find that Haskellers often use combinator to mean a function that makes new
functions out of other functions, which it can often do as a pure combinator,
but isn't always a combinator per se.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] inv f g = f . g . f

2013-08-17 Thread John Wiegley
 Dan Burton danburton.em...@gmail.com writes:

 under reversed (take 10) ['a'.. 'z']
 qrstuvwxyz

Excellent, thanks!

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANNOUNCE: tasty, a new testing framework

2013-08-06 Thread John Wiegley
 Roman Cheplyaka r...@ro-che.info writes:

 I am pleased to announce the first release of tasty, a new testing framework
 for Haskell. It is meant to be a successor to test-framework (which is
 unmaintained).

It would be nice to see a comparison of the various test frameworks and why
one might select one over another.  I use hspec currently (which also
integrates with HUnit, QuickCheck, etc.), and couldn't tell at a glance what
tasty might offer.  And I particularly dislike writing tests inside of a
gigantic list; I much prefer the monadic style of hspec.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ScopedTypeVariables

2013-08-06 Thread John Wiegley
 Evan Laforge qdun...@gmail.com writes:

 Would it make sense to split it into a separate extension like
 TypesOnArguments so I can more accurately express my deviation from
 haskell2010 orthodoxy?  Or is there some deeper tie between scoped
 type variables and annotations on arguments?

I've also wondered why I have to enable ScopedTypeVariables in those cases --
when I'm not turning it on to scope any type variables, but just to make
annotations possible in more places.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANNOUNCE: module-management-0.9.3 - clean import lists, split and merge modules

2013-06-28 Thread John Wiegley
 David Fox d...@seereason.com writes:

 Cliff Beshers wrote a CLI for this, I will add it as a cabal
 executable in the next version.

Oh, also, I was unable to build the library using GHC 7.4.2.  It looks like it
still depends on the old Exception stuff that used to be Prelude?

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANNOUNCE: module-management-0.9.3 - clean import lists, split and merge modules

2013-06-27 Thread John Wiegley
 David Fox d...@seereason.com writes:

 I am pleased to announce the first release of module-management, a package
 for cleaning import lists, and splitting and merging modules.  You can see a
 description at the top of the documentation for Language.Haskell.Modules
 (once it appears) here:

How about building an executable along with the library called cleanImports,
so that I can use it from the command-line.  Otherwise, every who wants to use
your library in this way will be writing pretty much the exact same code.

cleanImports is something I've been wanting, just hadn't gotten around to
writing it yet.  Thanks!

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Nightly builds of GHC HEAD for OS X 10.8

2013-06-21 Thread John Wiegley
 John Wiegley jo...@fpcomplete.com writes:

 Since mid-January, I’ve been running nightly builds of GHC on my Mac Pro for
 10.8.x, 64-bit. I’ve decided to make these results publically downloadable
 here:
 
 http://ghc.newartisans.com.

Just a note: I'm now including builds and logs for Ubuntu 12.04.x LTS 64-bit
as well, in addition to OS X 10.8.x.

If anyone has another platform they'd like to add, and can give me SSH access
to an account on their machine, the build needs about 10G of disk space and
eight hours a day of full CPU access (on average).  It can run in whatever
time range works best for you.  Let me know by e-mail if you're interested in
contributing to these nightlies.

As a next step, I plan to build source tarballs as well, so that the binaries
can be used forensically to allow bisecting among the builds for a breakage.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


[Haskell-cafe] Nightly builds of GHC HEAD for OS X 10.8

2013-06-12 Thread John Wiegley
Since mid-January, I’ve been running nightly builds of GHC on my Mac Pro for
10.8.x, 64-bit. I’ve decided to make these results publically downloadable
here:

http://ghc.newartisans.com.

The installer tarballs are in dist, while the fulltest and nofib logs are in
logs. According to Jenkins this build takes 8h15m minutes, so I figured this
might save others some CPU heat.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] GSoC Project Proposal: Markdown support for Haddock

2013-04-05 Thread John Wiegley
 Johan Tibell johan.tib...@gmail.com writes:

 I suggest that we implement an alternative haddock syntax that's a superset
 of Markdown.

Definite +1 from me too.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Threadscope 0.2.2 goes in segmentation fault on Mac Os X 10.8.3

2013-03-30 Thread John Wiegley
 Alfredo Di Napoli alfredo.dinap...@gmail.com writes:

 I know it's a bit difficult to debug this way, I can try debugging with gdb
 if it can help.

Yes, can you show us a backtrace from gdb, and also look in your CrashReports
log folder to see if it gives a bit more information on the state of the
process at the time it died?

Thanks,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: lazy-csv - the fastest and most space-efficient parser for CSV

2013-02-25 Thread John Wiegley
 Malcolm Wallace malcolm.wall...@me.com writes:

 Simple answer - I have never heard of cassava, and suspect it did not exist
 when I first did the benchmarking. I'd be happy to re-do my performance
 comparison, including cassava and any other recent-ish CSV libraries, if I
 can find them.

I would be very interested in those results, Malcolm.

Thanks,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Use forM_ with Maybe, it's Foldable!

2013-01-26 Thread John Wiegley
 Felipe Almeida Lessa felipe.le...@gmail.com writes:

 A few days ago I decided to hoogle the type of whenJust [2] and what I
 discovered is that

   import Data.Foldable (forM_)
   whenJust = forM_

You can also use for_, if you want to use Applicative instead of Monad.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-23 Thread John Wiegley
 Petr P petr@gmail.com writes:

 Don't take it so hard. Trying to reinvent something is always a great
 exercise and makes you really understand the problem. And it can have
 interesting results too. One of my university professors once heard about
 some concept, but didn't know the details. He tried to derive the concept
 himself, and he actually invented something different, new and very useful.

Thank you very much to everyone for the encouragement, and especially to
Edward and Shachaf for the education on #haskell.  It will be hard to unlearn
a lesson like this one. :)  And I will certainly endeavor to make the most
valuable mistakes I can from here on, with the help of such a gracious
community. :)

Yours,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


[Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
monad-bool implements a pair of Boolean monoids and monads, to support
short-circuiting, value-returning computations similar to what Python and Ruby
offer with their native  and || operators.

For example, in Python you might see this:

x = [1,2,3,0]
print x[1] || x[3]   -- prints 2

With this library, you can now mirror such code in Haskell:

let x = [1,2,3,0]
print $ (x !! 1) ||? (x !! 3)   -- prints Success 2

Booleanness is based on each type having an instance of the
'Control.Conditional.ToBool' type, for which only the basic types are covered
(Bool, Int, Integer, Maybe a, Either a b, [a], Attempt a).  If you wish to
define a truth value for your own types, simply provide an instance for
ToBool:

instance ToBool MyType where
toBool = ...

The And/Or monoids use the Attempt library so that the actual type of the
successful results depends on case analysis.  It could be a list, a Maybe, an
Either, or an exception in the IO Monad.

The monad variants, AndM, AndMT, OrM and OrMT provide short-circuiting
behavior in a Monad, which returns the last value returned before truth was
determined.  Here are two examples:

Use 'onlyIf' with AndM and AndMT to guard later statements, which are only
evaluated if every preceding 'onlyIf' evaluates to True.  For example:

foo :: AndM Int
foo = do onlyIf (True == True)
 return 100
 onlyIf (True == True)
 return 150
 onlyIf (True == False)
 return 200

When run with `evalAndM foo (-1)` (where (-1) provides a default value), 'foo'
returns 150.

Use 'endIf' with OrM and OrMT to chain statements, which are only executed if
every preceding 'endIf' evaluated to False.  For example:

bar :: OrM Int
bar = do endIf (True == False)
 return 100
 endIf (True == False)
 return 150
 endIf (True == True)
 return 200

When run with `evalOrM bar (-1)` (where (-1) again provides a default value),
'bar' returns 150.

And please, somebody let me know if this has already been done.  A search for
likely candidates did not turn up anything obvious in Hoogle, but as my
knowledge of the whole of Hackage is minimal, I would appreciate any wiser
minds that can inform me.

Thank you,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] [Haskell] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 Henning Thielemann lemm...@henning-thielemann.de writes:

 Does the And monad fulfill the monad laws? In a proper monad an interim
 (return x) (without a '-') is a no-op.

You are very right.  I will make the necessary changes.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 Conrad Parker con...@metadecks.org writes:

 these sound powerful, but how would I do something esoteric like
 if/elseIf/endIf ?

Can you show me an example of what you'd like to express?

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 Roman Cheplyaka r...@ro-che.info writes:

 - what do you need unsafeCoerce for?

Ok, after much discussion with edwardk and shachaf, I came to realize a few
things:

 1. The functionality of my two monads 'AndM' and 'OrR' can be boiled down to
two helper functions inside EitherT:

returnIf :: Monad m = Bool - e - EitherT e m ()
returnIf p a = if p then left a else right ()

returnUnless :: Monad m = Bool - e - EitherT e m ()
returnUnless p = returnIf (not p)

These let you short-circuit monadic computations, returning the
short-circuiting value as a Left; or as a Right if it reaches the end.

 2. The 'shortcircuit' library already provides short-circuiting variants of
 and || that work just like Python's and Ruby's.  In fact, I think I'll
talk to aristid about merging my Monoid definitions into that library.

Here are the updated docs:

http://ftp.newartisans.com/pub/monoid-bool/Data-Monoid-Bool.html

I'll ask Ross Paterson to deprecate monad-bool.  And in future, I'll seek
review here first before uploading.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 Ertugrul Söylemez e...@ertes.de writes:

 There is a good reason why Haskell's type system would never have allowed to
 write this library.  I recommend the author to try again without
 unsafeCoerce.  It won't work.

You are right, and in fact what I wanted to do cannot be done.  It requires
distinguishing the final value as either a Left (result from short-circuiting)
or a Right (final value).  And EitherT can already do that, it just lacks a
convenience function to make it easier (i.e, not having to write lots of
nested if statements).

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 John Wiegley jo...@fpcomplete.com writes:

 And EitherT can already do that, it just lacks a convenience function to
 make it easier (i.e, not having to write lots of nested if statements).

Never mind, when/unless + left work just fine for this.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] ANN: monad-bool 0.1

2013-01-22 Thread John Wiegley
 John Wiegley jo...@fpcomplete.com writes:

 Never mind, when/unless + left work just fine for this.

You know, it's been a humorous day.

First ekmett showed that I can't make a sane Monad instance for AndM or OrM.

Then I discovered I can't make a reasonable Monoid (no mempty, given only
'toBool'), so I dropped down to a Semigroup.  Further, my combinators for
EitherT can be implemented using just 'when' and 'left' to provide the
short-circuiting.

Already I had very little code left, until he showed me the Applicative
instance for Either, plus a little trick:

 Right 1 * Right 2 * Left 2 * Right 5
Left 2  -- same functionality as my And semigroup

 let Left x | y = y; x | _ = x in Left 1 | Right 2 | Right 3
Right 2-- same functionality as my Or semigroup

And poof, all my code just disappeared...

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Is there a tool like ri from ruby?

2012-11-25 Thread John Wiegley
 Tikhon Jelvis tik...@jelv.is writes:

 Have you tried Hoogle? I know you can install it locally and use it from
 GHCi or Emacs. I'm not familiar with ri, but from your description I think a
 local Hoogle would serve the same purpose with the added benefit of being
 able to search by types.

 Here's the wiki page about it: http://www.haskell.org/haskellwiki/Hoogle

See also:

http://newartisans.com/2012/09/running-a-fully-local-hoogle/

With this setup I can use :doc head in my ghci sessions, and see docs very
similar to what ri would show.

-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Category Theory and Haskell

2012-11-25 Thread John Wiegley
 Gytis Žilinskas gytis.zilins...@gmail.com writes:

 How difficult would it be to study category theory and simultaneously come
 up with Haskell examples of various results that it presents?

There are some aspects of CT that you will not be able to express in Haskell
easily (try encoding the forgetful functor, for instance).  But there are
other things which translate quite nicely.  As one example, I've been using
Haskell to explore the connection between adjunctions and monads, and have
found it quite rewarding.  My efforts so far are here:


https://github.com/jwiegley/posts/blob/master/Adjunctions%20in%20Haskell/Adjunction.hs

What I found most compelling from that code is I only need a minimal
definition of the Prod ⊣ Hom adjunction, (ε and η -- and their definitions are
trivial), I get all the behavior of the well-known State monad, whose typical
implementation via = is rather tricky.

Doing this exploration in Haskell -- with the aid of the type-checker -- made
certain connections clear that were difficult to see in the abstract.  And it
was plenty of fun besides. :)

Happy brain spelunking,
-- 
John Wiegley
FP Complete Haskell tools, training and consulting
http://fpcomplete.com   johnw on #haskell/irc.freenode.net

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


Re: [Haskell-cafe] Instead of Haskell running on the JVM is there a way for Haskell to call a JVM language ...

2012-11-19 Thread John Wiegley
 KC  kc1...@gmail.com writes:

 Instead of Haskell running on the JVM is there a way for Haskell to call a
 JVM language (or generate bytecode) to access the Java class libraries when
 needed?

 Or

 Is there a way for a JVM language or bytecode to call Haskell when needed?

I'd be very interested to know the answer to this as well.  Please let me know
what you discover.

John

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


Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread John Wiegley
 Greg Fitzgerald gari...@gmail.com writes:

 I've recently found myself using the expression: foldr (.) id to compose a
 list (or Foldable) of functions.

You want the Endo monoid:

ghci appEndo (Endo (+ 10)  Endo (+ 20)) $ 3
  33

John


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


Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread John Wiegley
 Thiago Negri evoh...@gmail.com writes:

 Can you please show some examples where it might be useful?
 I miss the point.

I guess if he already has a list of functions, Endo won't help.  Endo just
lets you treat functions as monoids, so you can foldMap, etc.  In that case,
foldr (.) id is pretty idiomatic, and Google turns up several uses of it.

John

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


Re: [Haskell-cafe] Is Hackage down?

2012-09-14 Thread John Wiegley
 C K Kashyap ckkash...@gmail.com writes:

 Is it just me or is Hackage indeed been going down more frequently of late?

It's not just you.


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


Re: [Haskell-cafe] Over general types are too easy to make.

2012-08-31 Thread John Wiegley
   timothyho...@seznam.cz writes:

 data BadFoo =
 BadBar{
 badFoo::Int} |
 BadFrog{
 badFrog::String,
 badChicken::Int}

 This is fine, until we want to write a function that acts on Frogs but not
 on Bars.  The best we can do is throw a runtime error when passed a Bar and
 not a Foo:

You can use wrapper types to solve this:

data BadBarType  = BadBarType BadFoo
data BadFrogType = BadFrogType BadFoo

Now you can have:

deBadFrog :: BadFrogType - String

And call it as:

deBadFrog $ BadFrogType (BadFrog { badFrog = Hey, badChicken = 1})

Needless to say, you will have to create helper functions for creating Bars
and Frogs, and not allow your BadBar or BadFrog value constructors to be
visible outside your module.

John

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