Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-11 Thread Daniel Fischer
On Friday 11 June 2010 07:47:03, Martin Drautzburg wrote:
 On Friday, 11. June 2010 00:12:03 Daniel Fischer wrote:

 Thanks Daniel.

  Upgrade. We're at 6.12 now!

 Did that. Everything is available now.

 I am still having trouble with the test function. First it seems I need
 braces, so I can mix == and *.
 test :: Num a
  = (a - a) - (a - a) - (a - a) - [String]
 test f g h = do
 [f', g', h'] - permutations [Named f f, Named g g, Named h h]
 guard $ namedPure 42 == (f' * g' * h' * namedPure 42)
 return $ show f' ++  .  ++ show g' ++  .  ++ show h'

 But this leads to

 Occurs check: cannot construct the infinite type:
   a = (a - a) - a1 - t
 When generalising the type(s) for `test'

Ah, yes, (*) is left associative (infixl 4, hence you also need the 
parentheses since (==) is infix 4; same fixity and different 
associativities don't mix), here it must be associated to the right,

namedPure 42 == (f' * (g' * (h' * namedPure 42)))

:(

If you'd want to use it a lot, define a right associative alias with higher 
fixity:

infixr 5 *

(*) = (*)


 This error message is still the maximum penalty for me (along with
 Corba marshall exception in J2EE and Missing right parenthesis in
 Oracle SQL)

 Then generally speaking, I have the feeling that this code does not
 allow namifying existing code either. In this respect it does not seem
 to do better than the apply method pattern discussed earlier in this
 thread.

You'd have to rewrite; either way.


 The problem it solves is very simple and therefore using (*) and
 namedPure isn't much of a drawback. But if I had tons of code to namify
 I would still have to do significant changes to it, right?

Yes.

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-11 Thread Luke Palmer
On Thu, Jun 10, 2010 at 2:10 PM, Maciej Piechotka uzytkown...@gmail.com wrote:
 data Named a = Named String a

 instance Functor Named where
    f `fmap` (Named s v) = Named s (f v)

 instance Applicative Named where
    pure x = Named  x
    (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

This is not technically a legal applicative instance, because it is
not associative.  This can be seen when you try to clean up the usage
as we have been discussing:

g . f = liftA2 (.) g f

f = Named f (+1)
g = Named g (*2)
h = Named h (^3)

ghci f * (g * (h * namedPure 42))
f(g(h(42)))
ghci (f . g . h) * namedPure 42
f(g)(h)(42)

The Applicative laws are supposed to guarantee that this refactor is
legal.  Of course, the latter answer is nonsense.

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-11 Thread Daniel Fischer
On Friday 11 June 2010 11:50:55, Luke Palmer wrote:
 On Thu, Jun 10, 2010 at 2:10 PM, Maciej Piechotka uzytkown...@gmail.com 
wrote:
  data Named a = Named String a
 
  instance Functor Named where
     f `fmap` (Named s v) = Named s (f v)
 
  instance Applicative Named where
     pure x = Named  x
     (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 This is not technically a legal applicative instance, because it is
 not associative.

Good spot.

I think

(Named s f) * (Named t v) = Named (s ++  $  ++ t) (f v)

fixes it.

 This can be seen when you try to clean up the usage
 as we have been discussing:

 g . f = liftA2 (.) g f

 f = Named f (+1)
 g = Named g (*2)
 h = Named h (^3)

 ghci f * (g * (h * namedPure 42))
 f(g(h(42)))
 ghci (f . g . h) * namedPure 42
 f(g)(h)(42)

 The Applicative laws are supposed to guarantee that this refactor is
 legal.  Of course, the latter answer is nonsense.

 Luke

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Daniel Fischer
On Thursday 10 June 2010 23:38:15, Martin Drautzburg wrote:
 On Thursday, 10. June 2010 22:10:08 Maciej Piechotka wrote:

 Wow!

 this is somewhat above my level. I guess I need to go back to the books.
 I'll document my ignorance nontheless.

  data Named a = Named String a
 
  instance Functor Named where
  f `fmap` (Named s v) = Named s (f v)

 okay so far

  instance Applicative Named where
  pure x = Named  x
  (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 Applicative. Need to study that
 Control.Applicative   (*) :: Applicative f = f (a - b) - f a - f b

 So in our case the Applicative is a Named.

Here, we define (*) for the type

(*) :: (Named (a - b)) - (Named a) - (Named b)

(redundant parentheses against ambiguity errors).

A 'Named' thing is a thing together with a name.
So how do we apply a function with a name to an argument with a name?
What we get is a value with a name. The value is of course the function 
applied to the argument ignoring names. The name of the result is the 
textual representation of the function application, e.g.

Named sin sin * Named pi pi ~ Named sin(pi) 1.2246063538223773e-16

(*) is application of named functions to named values, or 'lifting 
function application to named things'.

 When I apply a Named to a
 function, then I get a function between the corresponding Named types.
 When I pass it an Int-Char function, I get a Named Int - Named Char
 function.

 But here it is applied to another Named ... is that the (a-b)?
 Puzzeled.

  instance Eq a = Eq (Named a) where
  (Named _ x) == (Named _ y) = x == y
 
  instance Show (Named a) where
  show (Named s _) = s

 Understood.

  namedPure :: Show a = a - Named a
  namedPure x = Named (show x) x

 When I can show something I can always name it so its name is what
 'show' would return. Okay I guess I got it. This turns a showable into
 a Named.

  test :: Num a
   = (a - a) - (a - a) - (a - a) - [String]
  test f g h = do
  [f', g', h'] - permutations [Named f f, Named g g, Named h
  h]

 According to Hoogle permutations should be in Data.List. Mine (GHCI
 6.8.2) does not seem to have it. Seems to have something to do with

Upgrade. We're at 6.12 now!
Lots of improvements.
permutations was added in 6.10, IIRC.

 base, whatever that is.

  guard $ namedPure 42 == f' * g' * h' * namedPure 42

 Ah, the 42 needs namedPure.

Simplest way, it could be
Named answer to Life, the Universe and Everything 42

 Again this * operator...
 I believe the whole thing is using a List Monad.

  return $ show f' ++  .  ++ show g' ++  .  ++ show h'

 I wonder if the thing returns just one string or a list of strings. I

A list, one string for every permutation satisfying the condition.

 guess return cannot return anything more unwrapped than a List, so it
 must be a List. But does it contain just the first match or all of them?
 All of them! And how many brackets are around them?


do x - list
   guard (condition x)
   return (f x)

is syntactic sugar for

concat (map (\x - if condition x then [f x] else []) list)

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


[Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Maciej Piechotka
On Thu, 2010-06-10 at 19:44 +0200, Martin Drautzburg wrote:
 On Thursday, 10. June 2010 00:08:34 Luke Palmer wrote:
 
  Or just:
 
  apply = val_of
 
  So, to summarize:  if you have something that isn't a function and you
  want to use it like a function, convert it to a function (using
  another function :-P).  That's all.  No syntax magic, just say what
  you're doing.
 
 Thanks Luke
 
 The reason I was asking is the following: suppose I have some code which uses 
 some functions, and what it primarily does with those functions is CALL them 
 in different orders.
 
 Now at a later point in time I decide I need to give names to  those 
 functions 
 because at the end I need to print information about the functions which 
 together solved a certain problem. Think of my problem as In which order do 
 I have to call f,g,h such that (f.g.h) 42 = 42?.
 
 I don't want to change all places where those functions are called 
 into apply style. Therefore I was looking for some idiom like the python 
 __call__() method, which, when present, can turn just about anything into a 
 callable.
 
 I could change the *definition* of my original functions into apply style 
 and the rest of the code would not notice any difference. But that does not 
 really help, because in the end I want to Show something like [g,h,f], but my 
 functions would no longer carry names.
 
 Alternatively I could associate functions with names in some association 
 function, but that function simply has to know to much for my taste.
 
 The thing is, I only need the names at the very end. Throughout the majority 
 of the computation they should stay out of the way.
 
 

data Named a = Named String a

instance Functor Named where
f `fmap` (Named s v) = Named s (f v)

instance Applicative Named where
pure x = Named  x
(Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

instance Eq a = Eq (Named a) where
(Named _ x) == (Named _ y) = x == y

instance Show (Named a) where
show (Named s _) = s

namedPure :: Show a = a - Named a
namedPure x = Named (show x) x

test :: Num a
 = (a - a) - (a - a) - (a - a) - [String]
test f g h = do
[f', g', h'] - permutations [Named f f, Named g g, Named h h]
guard $ namedPure 42 == f' * g' * h' * namedPure 42
return $ show f' ++  .  ++ show g' ++  .  ++ show h'

(code is not tested but it should work)

Regards


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] Re: How to Show an Operation?

2010-06-10 Thread Martin Drautzburg
On Thursday, 10. June 2010 22:10:08 Maciej Piechotka wrote:

Wow!

this is somewhat above my level. I guess I need to go back to the books. I'll 
document my ignorance nontheless.

 data Named a = Named String a

 instance Functor Named where
 f `fmap` (Named s v) = Named s (f v)

okay so far

 instance Applicative Named where
 pure x = Named  x
 (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

Applicative. Need to study that
Control.Applicative (*) :: Applicative f = f (a - b) - f a - f b

So in our case the Applicative is a Named. When I apply a Named to a 
function, then I get a function between the corresponding Named types. When I 
pass it an Int-Char function, I get a Named Int - Named Char function.

But here it is applied to another Named ... is that the (a-b)? Puzzeled.

 instance Eq a = Eq (Named a) where
 (Named _ x) == (Named _ y) = x == y

 instance Show (Named a) where
 show (Named s _) = s


Understood.

 namedPure :: Show a = a - Named a
 namedPure x = Named (show x) x

When I can show something I can always name it so its name is what 'show' 
would return. Okay I guess I got it. This turns a showable into a Named.


 test :: Num a
  = (a - a) - (a - a) - (a - a) - [String]
 test f g h = do
 [f', g', h'] - permutations [Named f f, Named g g, Named h h]

According to Hoogle permutations should be in Data.List. Mine (GHCI 6.8.2) 
does not seem to have it. Seems to have something to do with base, whatever 
that is.

 guard $ namedPure 42 == f' * g' * h' * namedPure 42

Ah, the 42 needs namedPure.
Again this * operator... 
I believe the whole thing is using a List Monad. 

 return $ show f' ++  .  ++ show g' ++  .  ++ show h'

I wonder if the thing returns just one string or a list of strings. I 
guess return cannot return anything more unwrapped than a List, so it must 
be a List. But does it contain just the first match or all of them? All of 
them! And how many brackets are around them?

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Brandon S. Allbery KF8NH

On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote:

instance Applicative Named where
   pure x = Named  x
   (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)


Applicative. Need to study that


The above is just the Functor, rephrased in Applicative style.  * is  
exactly fmap.  Likewise, Monad has a function liftM which is exactly  
fmap.  (For historical reasons, these are not related the way they  
should be:  all Monads should be Applicatives, all Applicatives should  
be Functors, and all Functors should be instances of an even more  
primitive class Pointed.)


According to Hoogle permutations should be in Data.List. Mine (GHCI  
6.8.2)
does not seem to have it. Seems to have something to do with base,  
whatever

that is.


Things have gradually been moving out of base; you probably need to  
install containers from Hackage.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
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] Re: How to Show an Operation?

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 10:43 PM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:
 On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote:

 instance Applicative Named where
   pure x = Named  x
   (Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

 Applicative. Need to study that

 The above is just the Functor, rephrased in Applicative style.  * is
 exactly fmap.  Likewise, Monad has a function liftM which is exactly fmap.
  (For historical reasons, these are not related the way they should be:  all
 Monads should be Applicatives, all Applicatives should be Functors, and all
 Functors should be instances of an even more primitive class Pointed.)

(*) :: Applicative f = f (a - b) - f a - f b
($) :: Functor f = (a - b) - f a - f b

($) is fmap, not (*).  (*) is available for monads as Control.Monad.ap.

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


Re: [Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Martin Drautzburg
On Friday, 11. June 2010 00:12:03 Daniel Fischer wrote:

Thanks Daniel. 

 Upgrade. We're at 6.12 now!

Did that. Everything is available now.

I am still having trouble with the test function. First it seems I need 
braces, so I can mix == and *.
test :: Num a
 = (a - a) - (a - a) - (a - a) - [String]
test f g h = do
[f', g', h'] - permutations [Named f f, Named g g, Named h h]
guard $ namedPure 42 == (f' * g' * h' * namedPure 42)
return $ show f' ++  .  ++ show g' ++  .  ++ show h'

But this leads to

Occurs check: cannot construct the infinite type:
  a = (a - a) - a1 - t
When generalising the type(s) for `test'

This error message is still the maximum penalty for me (along with Corba 
marshall exception in J2EE and Missing right parenthesis in Oracle SQL)

Then generally speaking, I have the feeling that this code does not 
allow namifying existing code either. In this respect it does not seem to 
do better than the apply method pattern discussed earlier in this thread.

The problem it solves is very simple and therefore using (*) and namedPure 
isn't much of a drawback. But if I had tons of code to namify I would still 
have to do significant changes to it, right?





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