Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread damodar kulkarni
Thanks again for the detailed and explanatory answer.

That's the reason I'm writing these huge responses, because I hope I can
> shorten this journey for others.
>

This has certainly helped me grasp some aspects in this regard.

While Monad Transformers are awesome and can solve many problems quite
> easily, I'm pretty sure that there is almost always a nicer, "more
> functional" way to solve such a problem.


Incidentally, I happened to bump in to this paper, it claims they have
found a way that allows us get rid of the need of monad transformers in a
more systematic manner, by using what they call "Monad coproduct". The
paper titled "Composing Monads Using Coproducts" is here. [1]

I haven't understood it much till now, and it seems I will have to try real
hard to read this paper.

Ref.
[1] http://isi.uni-bremen.de/~cxl/habil/papers/icfp02.pdf


Thanks and regards,
-Damodar Kulkarni
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Hartmut Pfarr

... thx all for helping. Now the coding works: it puts the following out.
Kind regards
Hartmut


*Main> main
Only {fromOnly = 4}
--
Only {fromOnly = 101}
Only {fromOnly = 102}
Only {fromOnly = 103}
--
blub 101 51
blub 102 52
blub 103 53


The Coding is:

-- PostgreSQL-Simple test

{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple
import Data.Foldable
import qualified Data.Text as Text

myconn :: ConnectInfo
myconn = defaultConnectInfo {
connectUser = "test",
connectPassword = "test",
connectDatabase = "test"}

db_calc :: (FromRow a) => IO [a]
db_calc = do
  conn <- connect myconn
  query_ conn "select 2 + 2"

hr :: IO ()
hr = putStrLn "--"

main :: IO ()
main = do
  conn <- connect myconn

  -- Let Database calculate 2+2
  x1 <- db_calc
  forM_ x1 $ \h ->
putStrLn $ show (h :: Only Int)

  -- Select single integer column
  hr; x2 <- query_ conn "select aaa from aaa"
  forM_ x2 $ \(col1) ->
putStrLn $ show (col1 :: Only Int)

  -- select integer and text columns together
  hr; x3 <- query_ conn "select aaa,bbb,textcol from aaa"
  forM_ x3 $ \(int_col_1,int_col_2,text_col_3) ->
putStrLn $
  Text.unpack text_col_3 ++ " "
  ++ show (int_col_1 :: Int) ++ " "
  ++ show (int_col_2 :: Int)

  return ()



On 08/18/2013 12:12 AM, Brandon Allbery wrote:

On Sat, Aug 17, 2013 at 5:59 PM, Hartmut Pfarr
mailto:hartmut0...@googlemail.com>> wrote:

   query_ conn "select 2 + 2"

I've no errors any more.
But: I don't see any result (for sure, it is not coeded yet)


Yes, because you're not capturing it; it's the return value from
`query_`, which you are throwing away above instead of capturing with
some kind of `res <- query_ ...`. Again, see that section of the
documentation I pointed to for how to get results.

--
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net

unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net



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


Re: [Haskell-cafe] continuations and monads

2013-08-17 Thread Tikhon Jelvis
Yes they are. Purely intuitively, you can see how writing code in a monadic
style (using >>= a lot) is very similar to writing in continuation-passing
style.

You can express this the most directly with the continuation monad. Then,
from this monad, you can express other monads. In some sense, the
continuation monad is very fundamental. Take a look at "The Mother of all
Monads"[1] from The Neighborhood of Infinity for more details.

[1]: http://blog.sigfpe.com/2008/12/mother-of-all-monads.html?m=1
On Aug 17, 2013 7:02 PM, "Christopher Howard" <
christopher.how...@frigidcode.com> wrote:

> Q: Are the "continuations" in Scheme related to the "monads" from Haskell?
> If so, could someone elaborate on that?
>
> __**_
> 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] continuations and monads

2013-08-17 Thread Christopher Howard
Q: Are the "continuations" in Scheme related to the "monads" from 
Haskell? If so, could someone elaborate on that?


___
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  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] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Brandon Allbery
On Sat, Aug 17, 2013 at 5:59 PM, Hartmut Pfarr
wrote:

>   query_ conn "select 2 + 2"
>
> I've no errors any more.
> But: I don't see any result (for sure, it is not coeded yet)
>

Yes, because you're not capturing it; it's the return value from `query_`,
which you are throwing away above instead of capturing with some kind of
`res <- query_ ...`. Again, see that section of the documentation I pointed
to for how to get results.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Tom Ellis
On Sat, Aug 17, 2013 at 11:59:24PM +0200, Hartmut Pfarr wrote:
> {-# LANGUAGE OverloadedStrings #-}
> 
> import Database.PostgreSQL.Simple
> import Database.PostgreSQL.Simple.FromRow
> 
> hello :: (FromRow a) => IO [a]
> hello = do
>   conn <- connect defaultConnectInfo
>   query_ conn "select 2 + 2"

Either

main = print =<< (hello :: IO [Int])

or give hello a monomorphic type signature, such as 

hello :: IO [Int]

Tom

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


Re: [Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Hartmut Pfarr

Thx, I changed now from query to query_
Now the coding is like that:


{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.FromRow

hello :: (FromRow a) => IO [a]
hello = do
  conn <- connect defaultConnectInfo
  query_ conn "select 2 + 2"

main = return ()


I've no errors any more.
But: I don't see any result (for sure, it is not coeded yet)

I need some help to get data from "hello" via "FromRow" into the main 
function.


E.g. I want to put the "hello" database result (the number "4") to the 
screen.


Could anybody give an advice how I can accomplish this?

Kind regards
Hartmut


On 08/17/2013 07:53 PM, Brandon Allbery wrote:

On Sat, Aug 17, 2013 at 1:35 PM, Hartmut Pfarr
mailto:hartmut0...@googlemail.com>> wrote:

(The example is identical to the first 5-liner-example in the
package documentation)


As I read it, the example has a typo: it should be using `query_`
instead of `query`. See
http://hackage.haskell.org/packages/archive/postgresql-simple/0.3.5.0/doc/html/Database-PostgreSQL-Simple.html#g:9
for detals.

--
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net

unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.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 Dan Burton
The lens docs even have an example of another helper function, "involuted"
for functions which are their own inverse.

>>> "live" & involuted reverse %~ ('d':)
"lived"

inv f g = involuted f %~ g

http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/Control-Lens-Iso.html#v:involuted

-- Dan Burton


On Sat, Aug 17, 2013 at 1:43 PM, Dan Burton wrote:

> This is indeed a job for lens, particularly, the Iso type, and the "under"
> function. Lens conveniently comes with a typeclassed isomorphism called
> "reversed", which of course has a list instance.
>
> >>> under reversed (take 10) ['a'.. 'z']
> "qrstuvwxyz"
>
> -- Dan Burton
> On Aug 17, 2013 10:23 AM, "Anton Nikishaev"  wrote:
>
>> Christopher Done  writes:
>>
>> > Anyone ever needed this? Me and John Wiegley were discussing a decent
>> > name for it, John suggested inv as in involution. E.g.
>> >
>> > inv reverse (take 10)
>> > inv reverse (dropWhile isDigit)
>> > trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
>> >
>> > That seems to be the only use-case I've ever come across.
>>
>> And it's here only because reverse^-1 ≡ reverse, is not it?
>> I only can see how f ∘ g ∘ f^-1 can be a pattern.
>>
>> > There's also this one:
>> >
>> > co f g = f g . g
>> >
>> > which means you can write
>> >
>> > trim = co (inv reverse) (dropWhile isSpace)
>> >
>> > but that's optimizing an ever rarer use-case.
>>
>>
>> --
>> lelf
>>
>>
>>
>> ___
>> 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] inv f g = f . g . f

2013-08-17 Thread Dan Burton
This is indeed a job for lens, particularly, the Iso type, and the "under"
function. Lens conveniently comes with a typeclassed isomorphism called
"reversed", which of course has a list instance.

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

-- Dan Burton
On Aug 17, 2013 10:23 AM, "Anton Nikishaev"  wrote:

> Christopher Done  writes:
>
> > Anyone ever needed this? Me and John Wiegley were discussing a decent
> > name for it, John suggested inv as in involution. E.g.
> >
> > inv reverse (take 10)
> > inv reverse (dropWhile isDigit)
> > trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
> >
> > That seems to be the only use-case I've ever come across.
>
> And it's here only because reverse^-1 ≡ reverse, is not it?
> I only can see how f ∘ g ∘ f^-1 can be a pattern.
>
> > There's also this one:
> >
> > co f g = f g . g
> >
> > which means you can write
> >
> > trim = co (inv reverse) (dropWhile isSpace)
> >
> > but that's optimizing an ever rarer use-case.
>
>
> --
> lelf
>
>
>
> ___
> 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] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Brandon Allbery
On Sat, Aug 17, 2013 at 1:35 PM, Hartmut Pfarr
wrote:

> (The example is identical to the first 5-liner-example in the package
> documentation)
>

As I read it, the example has a typo: it should be using `query_` instead
of `query`. See
http://hackage.haskell.org/packages/archive/postgresql-simple/0.3.5.0/doc/html/Database-PostgreSQL-Simple.html#g:9for
detals.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread David Menendez
On Sat, Aug 17, 2013 at 8:23 AM, Mathijs Kwik wrote:

> damodar kulkarni  writes:
>
> > Thanks for this nice analogy and explanation. This brings "monad
> > transformers" to my mind.
> > "without" monad transformers, the monads are bit crippled in their
> > applicability (please correct me if I am wrong)
> > and
> > "with" monad transformers the code becomes to some extent ugly (again,
> > please correct me if I am wrong)
> >
> > I wonder, where and how the Monad transformers fit in here?
>
> Well, I'm glad you all liked my explanation =)
>
> Let me first correct 1 stupid mistake I wrote in the first paragraph:
> - Every idiom is an arrow and every arrow is a monad, but not the other
>   way around.
> should obviously be:
> + Every Monad is an Arrow (with ArrowApply) and every Arrow is an Idiom,
>   but not the other way around.
>

Every Idiom defines a static arrow:

newtype Static f a b = Static (f (a -> b))

instance Applicative f => Arrow (Static f)


Similarly, every arrow defines an idiom:

newtype WrappedArrow a b c = WrappedArrow (a b c)

instance Arrow a => Applicative (WrappedArrow a b)


The difference is that WrappedArrow (Static f) () is essentially the same
as f, but Static (WrappedArrow a ()) is not necessarily the same as a.

Basically, if an arrow can be made an instance of ArrowDelay, then it is no
more powerful than an Idiom (meaning anything you can write using the arrow
combinators can also be written with just the Applicative combinators):

class Arrow a => ArrowDelay a where
delay :: a b c -> a () (b -> c)

-- 
Dave Menendez 

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


[Haskell-cafe] Database.postgreSQL.Simple - ambigious type

2013-08-17 Thread Hartmut Pfarr

Hello,

I've a problem connecting to my postgresql database.
Can You help me fix the ambigious type signature?

(The example is identical to the first 5-liner-example in the package 
documentation)


http://hackage.haskell.org/packages/archive/postgresql-simple/0.3.5.0/doc/html/Database-PostgreSQL-Simple.html

Kind regards
Hartmut


{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple

main = do
  conn <- connect defaultConnectInfo
  query conn "select 2 + 2"
  return ()

But this leads to error:

Line 9: 1 error(s), 0 warning(s)

Couldn't match expected type `IO a0'
with actual type `q0 -> IO [r0]'
In the return type of a call of `query'
Probable cause: `query' is applied to too few arguments
In a stmt of a 'do' block: query conn "select 2 + 2"
In the expression:
  do { conn <- connect defaultConnectInfo;
   query conn "select 2 + 2";
   return () }

OK, I see, that a parameter q is missing.
I change the source code to

{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple

main = do
  conn <- connect defaultConnectInfo
  query conn "select 2 + 2" ( )  {- added ( ) here  -}
  return ()

Now, I run into next error:

Line 9: 1 error(s), 0 warning(s)

No instance for (FromRow r0) arising from a use of `query'
The type variable `r0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
  instance (FromField a, FromField b) => FromRow (a, b)
-- Defined in `Database.PostgreSQL.Simple.FromRow'
  instance (FromField a, FromField b, FromField c) =>
   FromRow (a, b, c)
-- Defined in `Database.PostgreSQL.Simple.FromRow'
  instance (FromField a, FromField b, FromField c, FromField d) =>
   FromRow (a, b, c, d)
-- Defined in `Database.PostgreSQL.Simple.FromRow'
  ...plus 10 others
In a stmt of a 'do' block: query conn "select 2 + 2" ()
In the expression:
  do { conn <- connect defaultConnectInfo;
   query conn "select 2 + 2" ();
   return () }
In an equation for `main':
main
  = do { conn <- connect defaultConnectInfo;
 query conn "select 2 + 2" ();
 return () }


___
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 Anton Nikishaev
Christopher Done  writes:

> Anyone ever needed this? Me and John Wiegley were discussing a decent
> name for it, John suggested inv as in involution. E.g.
>
> inv reverse (take 10)
> inv reverse (dropWhile isDigit)
> trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
>
> That seems to be the only use-case I've ever come across.

And it's here only because reverse^-1 ≡ reverse, is not it?
I only can see how f ∘ g ∘ f^-1 can be a pattern.

> There's also this one:
>
> co f g = f g . g
>
> which means you can write
>
> trim = co (inv reverse) (dropWhile isSpace)
>
> but that's optimizing an ever rarer use-case.


-- 
lelf



___
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 Joachim Breitner
Hi,

Am Samstag, den 17.08.2013, 11:11 +0200 schrieb Christopher Done:
> inv reverse (take 10)

if you want that fast and lazy, check out
http://www.joachim-breitner.de/blog/archives/600-On-taking-the-last-n-elements-of-a-list.html

Greetings,
Joachim

-- 
Joachim “nomeata” Breitner
  m...@joachim-breitner.de • http://www.joachim-breitner.de/
  Jabber: nome...@joachim-breitner.de  • GPG-Key: 0x4743206C
  Debian Developer: nome...@debian.org


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] inv f g = f . g . f

2013-08-17 Thread Tobias Dammers
Note that at least for the dropWhile example, there is a specialized
function, dropWhileEnd, which is most likely more efficient than reversing
the list twice.
On Aug 17, 2013 3:35 PM, "Tom Ellis" <
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote:

> On Sat, Aug 17, 2013 at 11:11:07AM +0200, Christopher Done wrote:
> > Anyone ever needed this? Me and John Wiegley were discussing a decent
> > name for it, John suggested inv as in involution. E.g.
> >
> > inv reverse (take 10)
> > inv reverse (dropWhile isDigit)
> > trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
>
> This sounds like a job for a lens, or similar.
>
> Tom
>
>
> ___
> 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] inv f g = f . g . f

2013-08-17 Thread Tom Ellis
On Sat, Aug 17, 2013 at 11:11:07AM +0200, Christopher Done wrote:
> Anyone ever needed this? Me and John Wiegley were discussing a decent
> name for it, John suggested inv as in involution. E.g.
> 
> inv reverse (take 10)
> inv reverse (dropWhile isDigit)
> trim = inv reverse (dropWhile isSpace) . dropWhile isSpace

This sounds like a job for a lens, or similar.

Tom


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


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread Mathijs Kwik
damodar kulkarni  writes:

> Thanks for this nice analogy and explanation. This brings "monad
> transformers" to my mind.
> "without" monad transformers, the monads are bit crippled in their
> applicability (please correct me if I am wrong)
> and
> "with" monad transformers the code becomes to some extent ugly (again,
> please correct me if I am wrong)
>
> I wonder, where and how the Monad transformers fit in here?

Well, I'm glad you all liked my explanation =)

Let me first correct 1 stupid mistake I wrote in the first paragraph:
- Every idiom is an arrow and every arrow is a monad, but not the other
  way around. 
should obviously be:
+ Every Monad is an Arrow (with ArrowApply) and every Arrow is an Idiom,
  but not the other way around.

Monad transformers are not really related to the subjects discussed thus
far, but through them I thought of 1 more distinction between Monad,
Arrow and Idiom that doesn't get mentioned often.

First I want to stress that Transformers are not some way to
uncripple/clean Monads. There is nothing unclean/cripple to begin
with. It's just that they lead to very dynamic assemble-on-the-go
factories, which does not seem to be necessary for most applications.

I should have pointed out the line that Dan Burton mentions as it is
really important. The idioms-arrows-monads paper words this as:
> monads allay the distinction between terms and commands
Which I pictured as workers reorganizing the factory, assembly-lines
arriving in a box and why not just package up the workers themselves to
deliver them to a spot they can start working.

Now, Monad transformers do not change anything about this, they are not
meant to lead this into more strict bounds or anything. There is no way
to do this anyway, given by the sheer fact that monads use (a -> m b), a
function, on every step, so anything can happen.


So what _are_ transformers for?
They are for composing Monads. Let's say we want to express a process
that can fail, but can deliver multiple values as well. Maybe [Int] for
example.

As a first thought we might try to just connect 2 factories, the list
factory and the maybe factory. First we'll find out that there is no
generic way to just connect 2 monadic factories, simply because there is
no generic way to get a value (box) out. Remember, all we have is
return :: a -> m a
fmap   :: (a -> b) -> m a -> m b -- inherited from Functor
(>>=)  :: m a (a -> m b) -> m b
So no generic way to get from (m a -> a). In other words, to look inside
a box, you have to be in the factory and promise to package up your
result in the same factory.

Even if we had such a magical way to connect 2 factories, it wouldn't do
us much good. If a box would roll from a State factory, to a Maybe
factory, then into another State factory, we end up with 2 different
state factories, both with their own "state cupboard", while the purpose
of state was to have something available during the entire process!
The same way, workers in List and State don't know how to signal/handle
failure (Maybe) and Maybe and State workers cannot handle
multiple-result boxes.

So instead of trying this, Monad Transformers allow you to build 1 big
factory, with - at every step - workers from all combined monads.
At any stage in the assembly line, those workers work together to share
their expertise. Envision them lined up behind each other, because their
order is very important. If the failure-dude (Maybe) is first in line
(next to the assembly line, he is the one opening boxes and packaging
results), with multi-answer-dude(List) behind him, the result is quite
different from doing it the other way around.
Possible results the first way:
- Just [12, 14]
- Nothing
Possible results the other way around:
- [Just 6, Nothing, Just 8]
- []
Basically every worker has a way of passing boxes to the workers
standing behind them, so they do not need to know about the special
effect. The List-worker will just unpack all values and repack them in
1-value boxes and hand them 1-by-1 to the worker behind. So for the
worker behind him, there is no way to know if these values came from 1
big multi-value box (List) or arrived one by one over the assembly line.
Maybe-guy removes Just when passing stuff backwards, and in case of
Nothing he just acts as if no boxes arrived. State guy might walk to the
cupboard before handing boxes backwards, you get the idea.
The way back works similar, Maybe guy just wraps Just around values,
List guy had to remember he gave 4 boxes backwards, so he waits for 4
results and packages them up in 1 multi-value box.

So, how do transformers get the workers to cooperate?
The main trick is to "upgrade" normal workers with 1 extra special
effect called "lift". For our factory this can be called "pass
backwards". So a program will basically have a number of "lift"
instructions at every step, to address the right worker in the line, so
an instruction like "get" is not gonna end up at Maybe-guy, who does not
know how to handle it.
This

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

2013-08-17 Thread Ian Ross
In J (a sort of dialect of APL), there's a thing called "under", written
"&.".  The expression "(f &. g) x" is equivalent to "(g^:_1) (f (g x))"
where "g^:_1" is J's "obverse" of g, which in cases where it exists is
usually the inverse of g (
http://www.jsoftware.com/help/dictionary/intro26.htm).  Abusing notation
with some weird mixture of Haskell and J, this means that "((+) &. log)"
multiplies numbers by taking logs, adding and exponentiating.  You "inv" is
"under" for cases where g == g^-1 (reverse being a good example).  In cases
where g /= g^-1, it's obviously a useful operation, but the case where g ==
g^-1 seems a bit specialised.  Can you think of any other useful cases than
g == reverse?  I guess "inv (1/) sum" is the harmonic mean, but that's
another special case.


On 17 August 2013 11:40, Mateusz Kowalczyk  wrote:

> On 17/08/13 10:11, Christopher Done wrote:
> > Anyone ever needed this? Me and John Wiegley were discussing a decent
> > name for it, John suggested inv as in involution. E.g.
> First thing I thought was ‘inverse’…
> >
> > inv reverse (take 10)
> > inv reverse (dropWhile isDigit)
> > trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
> >
> > That seems to be the only use-case I've ever come across.
> >
> I do this a lot as well. Why not skip the ‘g’ all together and have ‘f .
> reverse . f’ if that's all we're doing? You could even call it fromEnd
> at that point and we end up with a rather intuitive ‘fromEnd (drop 10)’.
> Maybe even just have an operator.
> > There's also this one:
> >
> > co f g = f g . g
> >
> > which means you can write
> >
> > trim = co (inv reverse) (dropWhile isSpace)
> >
> > but that's optimizing an ever rarer use-case.
> >
>
>
> Is this a proposal for addition to something or is it just general
> discussion?
>
>
> --
> Mateusz K.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
Ian Ross   Tel: +43(0)6804451378   i...@skybluetrades.net
www.skybluetrades.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 Mateusz Kowalczyk
On 17/08/13 10:11, Christopher Done wrote:
> Anyone ever needed this? Me and John Wiegley were discussing a decent
> name for it, John suggested inv as in involution. E.g.
First thing I thought was ‘inverse’…
> 
> inv reverse (take 10)
> inv reverse (dropWhile isDigit)
> trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
> 
> That seems to be the only use-case I've ever come across.
> 
I do this a lot as well. Why not skip the ‘g’ all together and have ‘f .
reverse . f’ if that's all we're doing? You could even call it fromEnd
at that point and we end up with a rather intuitive ‘fromEnd (drop 10)’.
Maybe even just have an operator.
> There's also this one:
> 
> co f g = f g . g
> 
> which means you can write
> 
> trim = co (inv reverse) (dropWhile isSpace)
> 
> but that's optimizing an ever rarer use-case.
> 


Is this a proposal for addition to something or is it just general
discussion?


-- 
Mateusz K.


0x2ADA9A97.asc
Description: application/pgp-keys
___
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 Ivan Lazar Miljenovic
On 17 August 2013 19:11, Christopher Done  wrote:
> Anyone ever needed this? Me and John Wiegley were discussing a decent
> name for it, John suggested inv as in involution. E.g.

In terms of a decent name: as soon as I saw the subject, I thought you
were somehow inverting a function :/

In terms of how useful it is, I don't think I tend to use such an idiom.

>
> inv reverse (take 10)
> inv reverse (dropWhile isDigit)
> trim = inv reverse (dropWhile isSpace) . dropWhile isSpace
>
> That seems to be the only use-case I've ever come across.
>
> There's also this one:
>
> co f g = f g . g
>
> which means you can write
>
> trim = co (inv reverse) (dropWhile isSpace)
>
> but that's optimizing an ever rarer use-case.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


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

2013-08-17 Thread Christopher Done
Anyone ever needed this? Me and John Wiegley were discussing a decent
name for it, John suggested inv as in involution. E.g.

inv reverse (take 10)
inv reverse (dropWhile isDigit)
trim = inv reverse (dropWhile isSpace) . dropWhile isSpace

That seems to be the only use-case I've ever come across.

There's also this one:

co f g = f g . g

which means you can write

trim = co (inv reverse) (dropWhile isSpace)

but that's optimizing an ever rarer use-case.

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