Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread wren ng thornton

On 8/27/12 6:27 PM, Tristan Seligmann wrote:

On Aug 27, 2012 8:40 PM, "Erik Hesselink"  wrote:


The other question is how useful test suites in a released package
are. Aren't they much more useful (and used more often) in source
repositories?


Having tests available in a released package allows one to verify that the
software is functional in its current configuration / state on your system;
this seems extremely useful to me.


indeed.

--
Live well,
~wren

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


Re: [Haskell-cafe] When is a composition of catamorphisms a catamorphism?

2012-08-27 Thread wren ng thornton

On 8/26/12 9:10 PM, Sebastien Zany wrote:

Thanks Wren. That was my guess too, but it seems not necessary:
http://stackoverflow.com/questions/12103309/when-is-a-composition-of-catamorphisms-a-catamorphism


Well, sure. I was meaning in the general case. If you have the right 
kind of distributivity property (as colah suggests) then things will 
work out for the particular case. But, having the right kind of 
distributivity property typically amounts to being a natural 
transformation in some appropriately related category; so that just 
defers the question to whether an appropriately related category always 
exists, and whether we can formalize what "appropriately related" means.


--
Live well,
~wren

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Tristan Seligmann
On Aug 27, 2012 8:40 PM, "Erik Hesselink"  wrote:
>
> The other question is how useful test suites in a released package
> are. Aren't they much more useful (and used more often) in source
> repositories?

Having tests available in a released package allows one to verify that the
software is functional in its current configuration / state on your system;
this seems extremely useful to me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Ryan Newton
Well, this one looks like it was my fault because I never read this thread
and this morning I uploaded that package (abstract-deque) with the
conditional in the test-suite.  The reason this conditional isn't there now
is that the package was hacked in place to remove tests, which is fine.

Actually, as a maintainer I'm not really clear on how to test this
behavior.  I tried "cabal configure" with cabal-install-0.10.2 as in the
original post and I couldn't reproduce the problem.



> For the record, abstract-deque was neither one of the packages fixed
> previously, nor does its .cabal file even contain a test section at
> all, much less one with a conditional.  So if cabal-install-0.10 is
> failing to read it, it is because of some different problem.  But I
> agree with Bryan in principle that we need a more principled approach.
>
> -Brent
>
> ___
> 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] Cabal install fails due to recent HUnit

2012-08-27 Thread Brandon Allbery
On Mon, Aug 27, 2012 at 4:23 PM, Bryan O'Sullivan wrote:

> On Mon, Aug 27, 2012 at 11:39 AM, Erik Hesselink wrote:
>
>>
>> Yes, you are right. So the question is how long to support systems
>> with the old cabal 0.10. This is the one included with the previous
>> haskell platform (and thus lots of linux distro's), which is less than
>> a year old. But it's also pretty old, since there weren't any cabal
>> releases for a while.
>>
>
> That's a very awkward situation. At least in the future, Johan and I have
> a proposal to make this class of problem more avoidable by introducing a
> regular release schedule. See the thread that starts here for details:
> http://www.haskell.org/pipermail/cabal-devel/2012-August/008987.html
>

While it's a bit late now, a regular extension syntax of some kind might
help.  Something that unavoidably breaks an actual install should throw an
error, other stuff should issue a warning (or even be ignored if not part
of the main sequence; these packages that  are causing breakage currently
are doing so via index entries, I think, not by the packages themselves
being built?).

One trick you see in some environments, for example, is that X-$thing is
ignored by older versions that don't know about $thing, and treated as
$thing by those that do.  If something needs $thing to build, then it will
throw the error about $thing, but it won't break just by having X-$thing
present.  Eventually you can remove the "X-" prefix.

(The difference between this and just ignoring unknowns is you don't
completely lose protection from typoes and such.  The "X-" could be
understood as downgrading an error to a warning in some circumstances.)

Another possibility, possibly used along with the above, is some kind of
syntax update that is shipped along with "cabal update".  It would not
enable cabal to *use* a new feature but could prime it to be *parsed* and
not throw unnecessary errors.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Bryan O'Sullivan
On Mon, Aug 27, 2012 at 11:39 AM, Erik Hesselink wrote:

>
> Yes, you are right. So the question is how long to support systems
> with the old cabal 0.10. This is the one included with the previous
> haskell platform (and thus lots of linux distro's), which is less than
> a year old. But it's also pretty old, since there weren't any cabal
> releases for a while.
>

That's a very awkward situation. At least in the future, Johan and I have a
proposal to make this class of problem more avoidable by introducing a
regular release schedule. See the thread that starts here for details:
http://www.haskell.org/pipermail/cabal-devel/2012-August/008987.html

For the state of things today, it's not obvious to me what to do.

It's burdensome to ask package authors to remove stuff from their packages
because it can't be handled by a broken version of cabal, especially since
there's no upper bound on how long that broken version will be floating
around. We'd essentially be giving up on this feature semi-permanently,
which would make me sad because it's so useful.

Just as unappealing is the idea of breaking builds for people who, through
no fault of their own, are using the broken cabal. However, at least this
class of people has the incentives aligned to do something about their
problem: either upgrade cabal-install or their distro.

The other question is how useful test suites in a released package
> are. Aren't they much more useful (and used more often) in source
> repositories?
>

They're certainly useful in source repositories, and we have historically
chosen not to make a distinction between what's in a source repo and what
gets shipped to end users via cabal, which makes sense to me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Ross Paterson
On Mon, Aug 27, 2012 at 09:03:18PM +0100, Brent Yorgey wrote:
> On Mon, Aug 27, 2012 at 10:52:59AM -0700, Bryan O'Sullivan wrote:
> > On Mon, Aug 27, 2012 at 9:57 AM, Erik Hesselink  wrote:
> > 
> > > I'm seeing this again, on abstract-deque-0.1.6. Ross, can you fix it 
> > > again?
> > >
> > 
> > Hang on a second.
> > 
> > The reason you're seeing build breakage is that the .cabal files of the
> > broken packages were edited in-place without communicating with any of the
> > package authors.
> > 
> > I understand that the collective intentions around this were good, but by
> > "fixing" things without telling anyone, package maintainers have no way to
> > know that anything has happened. Now we are seeing the problem begin to
> > recur as people issue new releases that don't incorporate those changes.
> 
> For the record, abstract-deque was neither one of the packages fixed
> previously, nor does its .cabal file even contain a test section at
> all, much less one with a conditional.

It did a couple of hours ago.

> But I
> agree with Bryan in principle that we need a more principled approach.

Yes, and Cabal is the place to test for this.

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Ross Paterson
On Mon, Aug 27, 2012 at 07:39:39PM +0100, Erik Hesselink wrote:
> If we do agree that we want to prevent this problem for a while (which
> I'm not sure about), we should probably do it by preventing uploads
> for packages like this. That way, package maintainers will know what
> is going on, just like with the other 'package quality' issues hackage
> enforces.

The place to check is Distribution.PackageDescription.Check.checkPackage
(in Cabal).  If this returns anything other than PackageDistSuspicious,
hackage will reject the upload.

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Brent Yorgey
On Mon, Aug 27, 2012 at 10:52:59AM -0700, Bryan O'Sullivan wrote:
> On Mon, Aug 27, 2012 at 9:57 AM, Erik Hesselink  wrote:
> 
> > I'm seeing this again, on abstract-deque-0.1.6. Ross, can you fix it again?
> >
> 
> Hang on a second.
> 
> The reason you're seeing build breakage is that the .cabal files of the
> broken packages were edited in-place without communicating with any of the
> package authors.
> 
> I understand that the collective intentions around this were good, but by
> "fixing" things without telling anyone, package maintainers have no way to
> know that anything has happened. Now we are seeing the problem begin to
> recur as people issue new releases that don't incorporate those changes.

For the record, abstract-deque was neither one of the packages fixed
previously, nor does its .cabal file even contain a test section at
all, much less one with a conditional.  So if cabal-install-0.10 is
failing to read it, it is because of some different problem.  But I
agree with Bryan in principle that we need a more principled approach.

-Brent

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Erik Hesselink
On Mon, Aug 27, 2012 at 7:52 PM, Bryan O'Sullivan  wrote:
> On Mon, Aug 27, 2012 at 9:57 AM, Erik Hesselink  wrote:
>>
>> I'm seeing this again, on abstract-deque-0.1.6. Ross, can you fix it
>> again?
>
>
> Hang on a second.
>
> The reason you're seeing build breakage is that the .cabal files of the
> broken packages were edited in-place without communicating with any of the
> package authors.
>
> I understand that the collective intentions around this were good, but by
> "fixing" things without telling anyone, package maintainers have no way to
> know that anything has happened. Now we are seeing the problem begin to
> recur as people issue new releases that don't incorporate those changes.
>
> So. Let's have a little conversation about how to handle this sustainably
> before wasting more of Ross's time.

Yes, you are right. So the question is how long to support systems
with the old cabal 0.10. This is the one included with the previous
haskell platform (and thus lots of linux distro's), which is less than
a year old. But it's also pretty old, since there weren't any cabal
releases for a while.

The other question is how useful test suites in a released package
are. Aren't they much more useful (and used more often) in source
repositories?

If we do agree that we want to prevent this problem for a while (which
I'm not sure about), we should probably do it by preventing uploads
for packages like this. That way, package maintainers will know what
is going on, just like with the other 'package quality' issues hackage
enforces.

Erik

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


Re: [Haskell-cafe] OS-independent auto-monitoring of a program to do things depending on resource usage at runtime

2012-08-27 Thread Alberto G. Corona
Joachim:

Thanks a lot

2012/8/27 Joachim Breitner 

> Hi,
>
> Am Montag, den 27.08.2012, 18:20 +0200 schrieb Alberto G. Corona :
> > For a caching library, I need to know the runtime usage of memory of
> > the  program and the total amount of memory, the total memory used by
> > all the programs etc.
> >
> >
> >  I need not do profiling or monitoring but to do different things
> > inside my program depending on memory usage.
> >
> > The search is difficult because all searches go to profiling utilities
> > which I don´t need.
> >
> >
> > Are there some  portable way to to this? . The various monitoring
> > libraries indicates that there are ways to do it, but they seem not to
> > allow  runtime "internal automonitoring"
>
> you can use the GHC.Stats module, see
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-Stats.html,
> and remember to pass +RTS -T to the program, or -with-rtsopts=-T to the
> compiler.
>
> Greetings,
> Joachim
>
> --
> Joachim "nomeata" Breitner
>   m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
>   xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
>
>
> ___
> 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] Simple shell scripts

2012-08-27 Thread Eric Tanter
Thanks Brandon and Iavor for your (fast!) responses.

Installing a silent handler as suggested by Brandon worked nicely.

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


Re: [Haskell-cafe] OS-independent auto-monitoring of a program to do things depending on resource usage at runtime

2012-08-27 Thread Joachim Breitner
Hi,

Am Montag, den 27.08.2012, 18:20 +0200 schrieb Alberto G. Corona :
> For a caching library, I need to know the runtime usage of memory of
> the  program and the total amount of memory, the total memory used by
> all the programs etc.
> 
> 
>  I need not do profiling or monitoring but to do different things
> inside my program depending on memory usage.
> 
> The search is difficult because all searches go to profiling utilities
> which I don´t need.
> 
> 
> Are there some  portable way to to this? . The various monitoring
> libraries indicates that there are ways to do it, but they seem not to
> allow  runtime "internal automonitoring"

you can use the GHC.Stats module, see
http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-Stats.html, and 
remember to pass +RTS -T to the program, or -with-rtsopts=-T to the compiler.

Greetings,
Joachim

-- 
Joachim "nomeata" Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



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


Re: [Haskell-cafe] Simple shell scripts

2012-08-27 Thread Brandon Allbery
On Mon, Aug 27, 2012 at 1:55 PM, Eric Tanter  wrote:

> Here is a simple shell script (upper.hs):
>

"shell script" means a script written in the shell's programming language.
 This is probably best referred to as a Haskell script.


> bash-3.2$ yes | runghc upper.hs | head -n 3
> Y
> Y
> Y
> : hFlush: resource vanished (Broken pipe)
>
> Any idea why this error occurs/how to avoid it?
>

It's normal, and shells normally ignore it when programs in the middle of a
pipeline die with SIGPIPE.  Problem here is the Haskell runtime is itself
intercepting the SIGPIPE and throwing a verbose Haskell exception.

Possibly the runtime should detect that stdout is a pipe and disable the
usual SIGPIPE handler, or if it must run cleanup stuff then it should not
print anything and it should after cleanup raise(SIGPIPE) on itself with
the default SIGPIPE handler so the shell will react properly.

You might be able to do this yourself with
(System.Posix.Signals.installHandler openEndedPipe Default Nothing).

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple shell scripts

2012-08-27 Thread Iavor Diatchki
Hello,
this happens because "head" probably closes the file descriptor after 3
lines, and then the Haskell program tries to write to a closed handle
(i.e., it's stdout is not there anymore).  The best thing to do depends on
the program. One fairly simple option would be to handle the exception, and
do something (perhaps ignore it).
-Iavor

On Mon, Aug 27, 2012 at 10:55 AM, Eric Tanter  wrote:

> Hi,
>
> Here is a simple shell script (upper.hs):
>
> import Data.Char
> main = interact $ map toUpper
>
> which composes fine with other scripts:
>
> bash-3.2$ yes | head -n 3 | runghc upper.hs
> Y
> Y
> Y
>
> but not always:
>
> bash-3.2$ yes | runghc upper.hs | head -n 3
> Y
> Y
> Y
> : hFlush: resource vanished (Broken pipe)
>
> Any idea why this error occurs/how to avoid it?
>
> (running just:
> yes | runghc upper.hs
> gives the expected infinite stream of Ys)
>
> Thanks!
>
> -- Éric
>
> ___
> 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] Simple shell scripts

2012-08-27 Thread Eric Tanter
Hi,

Here is a simple shell script (upper.hs):

import Data.Char
main = interact $ map toUpper

which composes fine with other scripts:

bash-3.2$ yes | head -n 3 | runghc upper.hs 
Y
Y
Y

but not always:

bash-3.2$ yes | runghc upper.hs | head -n 3
Y
Y
Y
: hFlush: resource vanished (Broken pipe)

Any idea why this error occurs/how to avoid it?

(running just:
yes | runghc upper.hs
gives the expected infinite stream of Ys)

Thanks!

-- Éric

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


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Bryan O'Sullivan
On Mon, Aug 27, 2012 at 9:57 AM, Erik Hesselink  wrote:

> I'm seeing this again, on abstract-deque-0.1.6. Ross, can you fix it again?
>

Hang on a second.

The reason you're seeing build breakage is that the .cabal files of the
broken packages were edited in-place without communicating with any of the
package authors.

I understand that the collective intentions around this were good, but by
"fixing" things without telling anyone, package maintainers have no way to
know that anything has happened. Now we are seeing the problem begin to
recur as people issue new releases that don't incorporate those changes.

So. Let's have a little conversation about how to handle this sustainably
before wasting more of Ross's time.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Erik Hesselink
On Mon, Jul 30, 2012 at 3:33 PM, Ross Paterson  wrote:
> On Mon, Jul 30, 2012 at 01:46:24PM +0100, Niklas Broberg wrote:
>> On Wed, Jul 25, 2012 at 12:22 PM, Ross Paterson  wrote:
>>
>> As I understand it, the plan is to modify the following packages in
>> hackage in-situ to remove the test sections (which contain the 
>> troublesome
>> conditionals):
>>
>>   HUnit-1.2.5.0
>>   bloomfilter-1.2.6.10
>>   codemonitor-0.1
>>   codemonitor-0.2
>>   fixhs-0.1.4
>>   leksah-server-0.12.0.3
>>   leksah-server-0.12.0.4
>>   leksah-server-0.12.0.5
>>   pqc-0.5
>>   pqc-0.5.1
>>
>> Does anyone object?
>>
>> No objections, but some impatience. ;-)
>
> OK, done.

I'm seeing this again, on abstract-deque-0.1.6. Ross, can you fix it again?

For the future: is there any way to prevent this from happening?
Perhaps a check in hackage? I'd be willing to implement this if people
think this is a good idea, and I'm pointed in the right direction.

Erik

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


Re: [Haskell-cafe] map over Bijections

2012-08-27 Thread Sergey Mironov
Yes, you are right, I don't really need the second argument. I am not
skilled enough to join the discussion, but I do understand your
solution. Thanks!

Sergey

2012/8/27 Tillmann Rendel :
> Hi,
>
>
> Sergey Mironov wrote:
>>
>> I need map equivalent for Bijection type which is defined in fclabels:
>>
>> data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }
>>
>> instance Category (~>) => Category (Bijection (~>)) where ...
>>
>> I can define this function as follows:
>> mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->)
>> [a] [c]
>> mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))
>
>
> Two observations.
>
> First observation: The second argument seems unnecessary, so we have the
> following instead:
>
>> mapBij :: Bijection (->) a c -> Bijection (->) [a] [c]
>> mapBij b = (map (fw b)) `Bij` (map (bw b))
>
>
> Second observation: I guess this works for arbitrary functors, not just
> lists, so we get the following:
>
>> fmapBij :: Functor f => Bijection (->) a c -> Bijection (->) (f a) (f c)
>> fmapBij b = (fmap (fw b)) `Bij` (fmap (bw b))
>
>
> Lets check that fmapBij returns a bijection:
>>
>>   fw (fmapBij b) . bw (fmapBij b)
>>   {- unfolding -}
>> = fmap (fw b) . fmap (bw b)
>>   {- functor -}
>> = fmap (fw b . bw b)
>>   {- bijection -}
>> = fmap id
>>   {- functor -}
>> = id
>
>
> Looks good.
>
>
> I guess we can generalize this to get: If f is a functor on a category c, it
> is also a functor on the category (Bijection c). But I am not sure how to
> express this with Haskell typeclasses. Maybe along the lines of:
>
>> import Control.Categorical.Functor -- package categories
>>
>> instance Endofunctor f cat => Endofunctor f (Bijection cat) where
>>   fmap b = (fmap (fw b)) `Bij` (fmap (bw b))
>
>
> So Bijection is a functor in the category of categories?
>
>   Tillmann
>
>
>
>

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


[Haskell-cafe] OS-independent auto-monitoring of a program to do things depending on resource usage at runtime

2012-08-27 Thread Alberto G. Corona
For a caching library, I need to know the runtime usage of memory of the
 program and the total amount of memory, the total memory used by all the
programs etc.

 I need not do profiling or monitoring but to do different things inside my
program depending on memory usage.

The search is difficult because all searches go to profiling utilities
which I don´t need.

Are there some  portable way to to this? . The various monitoring libraries
indicates that there are ways to do it, but they seem not to allow  runtime
"internal automonitoring"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map over Bijections

2012-08-27 Thread Tillmann Rendel

Hi,

Sergey Mironov wrote:

I need map equivalent for Bijection type which is defined in fclabels:

data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }

instance Category (~>) => Category (Bijection (~>)) where ...

I can define this function as follows:
mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c]
mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))


Two observations.

First observation: The second argument seems unnecessary, so we have the 
following instead:



mapBij :: Bijection (->) a c -> Bijection (->) [a] [c]
mapBij b = (map (fw b)) `Bij` (map (bw b))


Second observation: I guess this works for arbitrary functors, not just 
lists, so we get the following:



fmapBij :: Functor f => Bijection (->) a c -> Bijection (->) (f a) (f c)
fmapBij b = (fmap (fw b)) `Bij` (fmap (bw b))


Lets check that fmapBij returns a bijection:

  fw (fmapBij b) . bw (fmapBij b)
  {- unfolding -}
= fmap (fw b) . fmap (bw b)
  {- functor -}
= fmap (fw b . bw b)
  {- bijection -}
= fmap id
  {- functor -}
= id


Looks good.


I guess we can generalize this to get: If f is a functor on a category 
c, it is also a functor on the category (Bijection c). But I am not sure 
how to express this with Haskell typeclasses. Maybe along the lines of:



import Control.Categorical.Functor -- package categories

instance Endofunctor f cat => Endofunctor f (Bijection cat) where
  fmap b = (fmap (fw b)) `Bij` (fmap (bw b))


So Bijection is a functor in the category of categories?

  Tillmann





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


Re: [Haskell-cafe] map over Bijections

2012-08-27 Thread Erik Hesselink
If you remove the second argument (which you don't use), you have the
function `liftBij` that is in fclabels.

Erik

On Mon, Aug 27, 2012 at 3:55 PM, Sergey Mironov  wrote:
> Hi. I need map equivalent for Bijection type which is defined in fclabels:
>
> data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }
>
> instance Category (~>) => Category (Bijection (~>)) where ...
>
> I can define this function as follows:
> mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] 
> [c]
> mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))
>
> but do I really need to do it explicitly? Can I obtain same result
> using some Category combinators or other common stuff?
>
> Sergey
>
> ___
> 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] map over Bijections

2012-08-27 Thread Sergey Mironov
Hi. I need map equivalent for Bijection type which is defined in fclabels:

data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }

instance Category (~>) => Category (Bijection (~>)) where ...

I can define this function as follows:
mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c]
mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))

but do I really need to do it explicitly? Can I obtain same result
using some Category combinators or other common stuff?

Sergey

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


Re: [Haskell-cafe] Compiling Haskell targetting different OS/arch

2012-08-27 Thread Sergey Mironov
ARM guys use native ghc to build arm binaries

2012/8/24 Taylor Hedberg :
> Thiago Negri, Fri 2012-08-24 @ 13:27:32-0300:
>> Is it possible to compile Haskell code targetting a OS/arch that
>> differs from the one where the compiler (GHC) is running?
>
> No, GHC doesn't currently support cross-compilation.
>
> ___
> 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