Re: [Haskell-cafe] guards in applicative style

2012-09-17 Thread Ryan Ingram
Not exactly what you asked for, but...

filter (uncurry somePredicate) $ (,) $ list1 * list2

does the job.

Using only applicative operations, it's impossible to affect the 'shape' of
the result--this is the difference in power between applicative and monad.

  -- ryan


On Wed, Sep 12, 2012 at 7:40 AM, felipe zapata tifonza...@gmail.com wrote:

 Hi Haskellers,

 Suppose I have two list and I want to calculate
 the cartesian product between the two of them,
 constrained to a predicate.
 In List comprehension notation is just

 result = [ (x, y) | x - list1, y -list2, somePredicate x y ]

 or in monadic notation

 result = do
  x - list1
  y - list2
  guard (somePredicate x y)
 return $ (x,y)

 Then I was wondering if we can do something similar using an applicative
 style

 result = (,) $ list1 * list2 (somePredicate ???)

 The question is then,
 there is a way for defining a guard in applicative Style?

 Thanks in advance,

 Felipe Zapata.



 ___
 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] guards in applicative style

2012-09-12 Thread felipe zapata
Hi Haskellers,

Suppose I have two list and I want to calculate
the cartesian product between the two of them,
constrained to a predicate.
In List comprehension notation is just

result = [ (x, y) | x - list1, y -list2, somePredicate x y ]

or in monadic notation

result = do
 x - list1
 y - list2
 guard (somePredicate x y)
return $ (x,y)

Then I was wondering if we can do something similar using an applicative
style

result = (,) $ list1 * list2 (somePredicate ???)

The question is then,
there is a way for defining a guard in applicative Style?

Thanks in advance,

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


Re: [Haskell-cafe] guards in applicative style

2012-09-12 Thread Lorenzo Bolla
I'm no expert at all, but I would say no.
guard type is:
guard :: MonadPlus m = Bool - m ()

and MonadPlus is a monad plus (ehm...) mzero and mplus
(http://en.wikibooks.org/wiki/Haskell/MonadPlus).
On the other hand Applicative is less than a monad
(http://www.haskell.org/haskellwiki/Applicative_functor), therefore
guard as is cannot be defined.

But, in your specific example, with lists, you can always use filter:
filter (uncurry somePredicate) ((,) $ list1 * list2 (somePredicate ???))

hth,
L.


On Wed, Sep 12, 2012 at 3:40 PM, felipe zapata tifonza...@gmail.com wrote:

 Hi Haskellers,

 Suppose I have two list and I want to calculate
 the cartesian product between the two of them,
 constrained to a predicate.
 In List comprehension notation is just

 result = [ (x, y) | x - list1, y -list2, somePredicate x y ]

 or in monadic notation

 result = do
  x - list1
  y - list2
  guard (somePredicate x y)
 return $ (x,y)

 Then I was wondering if we can do something similar using an applicative style

 result = (,) $ list1 * list2 (somePredicate ???)

 The question is then,
 there is a way for defining a guard in applicative Style?

 Thanks in advance,

 Felipe Zapata.



 ___
 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] guards in applicative style

2012-09-12 Thread Brent Yorgey
Lorenzo is correct, but actually for the wrong reason. =) The *type*
of guard is a historical accident, and the fact that it requires
MonadPlus doesn't really tell us anything.  Let's take a look at its
implementation:

  guard   :: (MonadPlus m) = Bool - m ()
  guard True  =  return ()
  guard False =  mzero

'return' is not specific to Monad; we could just as well use 'pure'.
'mzero' is a method of 'MonadPlus' but there is no reason we can't use
'empty' from the 'Alternative' class.  So we could define

  guardA :: Alternative f = Bool - f ()
  guardA True  = pure ()
  guardA False = empty

(As another example, consider the function 'sequence :: Monad m = [m
a] - m [a]'.  Actually this function does not need Monad at all, it
only needs Applicative.)

However, guardA is not as useful as guard, and it is not possible to
do the equivalent of the example shown using a list comprehension with
a guard.  The reason is that whereas monadic computations can make use
of intermediate computed values to decide what to do next, Applicative
computations cannot.  So there is no way to generate values for x and
y and then pass them to 'guardA' to do the filtering.  guardA can only
be used to conditionally abort an Applicative computation using
information *external* to the Applicative computation; it cannot
express a condition on the intermediate values computed by the
Applicative computation itself.

-Brent

On Wed, Sep 12, 2012 at 03:52:03PM +0100, Lorenzo Bolla wrote:
 I'm no expert at all, but I would say no.
 guard type is:
 guard :: MonadPlus m = Bool - m ()
 
 and MonadPlus is a monad plus (ehm...) mzero and mplus
 (http://en.wikibooks.org/wiki/Haskell/MonadPlus).
 On the other hand Applicative is less than a monad
 (http://www.haskell.org/haskellwiki/Applicative_functor), therefore
 guard as is cannot be defined.
 
 But, in your specific example, with lists, you can always use filter:
 filter (uncurry somePredicate) ((,) $ list1 * list2 (somePredicate ???))
 
 hth,
 L.
 
 
 On Wed, Sep 12, 2012 at 3:40 PM, felipe zapata tifonza...@gmail.com wrote:
 
  Hi Haskellers,
 
  Suppose I have two list and I want to calculate
  the cartesian product between the two of them,
  constrained to a predicate.
  In List comprehension notation is just
 
  result = [ (x, y) | x - list1, y -list2, somePredicate x y ]
 
  or in monadic notation
 
  result = do
   x - list1
   y - list2
   guard (somePredicate x y)
  return $ (x,y)
 
  Then I was wondering if we can do something similar using an applicative 
  style
 
  result = (,) $ list1 * list2 (somePredicate ???)
 
  The question is then,
  there is a way for defining a guard in applicative Style?
 
  Thanks in advance,
 
  Felipe Zapata.
 
 
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] guards in applicative style

2012-09-12 Thread Ertugrul Söylemez
Brent Yorgey byor...@seas.upenn.edu wrote:

 However, guardA is not as useful as guard, and it is not possible to
 do the equivalent of the example shown using a list comprehension with
 a guard.  The reason is that whereas monadic computations can make use
 of intermediate computed values to decide what to do next, Applicative
 computations cannot.  So there is no way to generate values for x and
 y and then pass them to 'guardA' to do the filtering.  guardA can only
 be used to conditionally abort an Applicative computation using
 information *external* to the Applicative computation; it cannot
 express a condition on the intermediate values computed by the
 Applicative computation itself.

To continue this story, from most applicative functors you can construct
a category, which is interesting for non-monads.  Let's examine the
SparseStream functor, which is not a monad:

data SparseStream a =
SparseStream {
  headS :: Maybe a,
  tailS :: SparseStream a
}

This is an applicative functor,

instance Applicative SparseStream where
pure x = let str = SparseStream (Just x) str in str

SparseStream f fs * SparseStream x xs =
SparseStream (f * x) (fs * xs)

but with a little extension it becomes a category, the wire category:

newtype Wire a b = Wire (a - (Maybe b, Wire a b))

This is like SparseStream, but for each head/tail pair it wants an
argument.  Given a Category instance you can now actually make use of
guardA without resorting to monadic combinators:

guardA p . myStream

This is conceptually how Netwire's applicative FRP works and how events
are implemented.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


[Haskell-cafe] ANNOUNCE: optparse-applicative 0.0.1

2012-06-09 Thread Paolo Capriotti
I'm pleased to announce the release of version 0.0.1 of
[optparse-applicative][1], a
library for writing command line option parsers in Applicative style.

You can find an introduction and tutorial on the [github page][2], and an
explanation of the internals on [my blog][3].

 [1]: http://hackage.haskell.org/package/optparse-applicative
 [2]: https://github.com/pcapriotti/optparse-applicative
 [3]: http://paolocapriotti.com/blog/2012/04/27/applicative-option-parser/

BR,
Paolo

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


Re: [Haskell-cafe] why are applicative functors (often) faster than monads? (WAS Google Summer of Code - Lock-free data structures)

2012-04-21 Thread Heinrich Apfelmus

Ben wrote:

however, this does bring up a general question : why are applicative
functors (often) faster than monads?  malcolm wallace mentioned this
is true for polyparse, and heinrich mentioned this is true more
generally.  is there a yoga by which one can write monadic functors
which have a specialized, faster applicative implementation?


I'm not knowledgeable enough on the multicore stuff, but I can comment 
on the monad vs applicative issue.


Applicative functors are not per se faster than monads, it's just that 
the former can encode static analysis while the latter can't. As you can 
see from the type of bind


   (=) :: m a - (a - m b) - m b

the structure of the computation in the second argument, i.e. its 
various side effects, can depend on a value of type  a  , which is only 
available at run-time.


In contrast, the type of apply

   (*) :: m (a - b) - m a - m b

makes it clear that the side effects are the same, no matter what the 
value of  a  will be at run-time. In other words, the structure of the 
computation is known statically.



For parsers, interesting analyses are

* Does a parser accept the empty set?
* What are the first characters that a parser can accept?

The answers can be obtained easily enough from an applicative functors, 
for instance


acceptsEmpty (pure x)  = True
acceptsEmpty (f * g) = acceptsEmpty f  acceptsEmpty g

But the corresponding analysis for monadic parsers is either harder or 
hopelessly inefficient because we don't know the structure of the parser 
until we run it on some input.


See also this answer on StackOverflow:

  http://stackoverflow.com/a/7863380/403805



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


[Haskell-cafe] why are applicative functors (often) faster than monads? (WAS Google Summer of Code - Lock-free data structures)

2012-04-20 Thread Ben
heinrich and all --

thanks for the illuminating comments, as usual.  i've had a little bit of time 
to play around with this and here's what i've concluded (hopefully i'm not 
mistaken.)

1 - while composeability makes STM a great silver bullet, there are other 
composable lower level paradigms.  aaron has identified a few fundamental 
algorithms that appear to be composable, and used a lot in concurrent 
algorithms / data structures : k-CAS, exponential backoff, helping and 
elimination.

2 - k-CAS (and more generally k-RMW) is composable.  i'm not exactly sure if 
i'd call k-CAS monadic but it is at least applicative (i'm not sure what the 
exact definition of k-CAS is.  a bunch of 1-CASs done atomically seems 
applicative; allowing them to interact seems monadic.  certainly k-RMW is 
monadic.)  while it is possible to implement STM on top of k-CAS and vice 
versa, k-CAS can get you closer to the metal, and if you can special case 1-CAS 
to hardware you will win on a lot of benchmarks.  a lot of concurrent 
algorithms only need 1-CAS.

3 - backoff, elimination and helping help scalability a lot, so you want 
support for them.  elimination and helping require communication between 
transactions, whereas STM is all about isolation, so reagents are fundamentally 
different in this regard.

reagents as implemented in the paper are not entirely monadic (by accident, i 
think the author intended them to be.)  as far as i can see he uses an 
applicative form of k-CAS, and the reagents on top of it are applicative : his 
computed combinator (monadic bind) does not allow post-composition (it has no 
continuation.)  there is no reason why it could not be built on top of a 
monadic k-RMW and be fully monadic.  however he is able to recognize and 
special-case 1-CAS, which gives great performance of course.

however, this does bring up a general question : why are applicative functors 
(often) faster than monads?  malcolm wallace mentioned this is true for 
polyparse, and heinrich mentioned this is true more generally.  is there a yoga 
by which one can write monadic functors which have a specialized, faster 
applicative implementation?

right now i'm reading up on k-CAS / k-RMW implementations, and i think i'm 
going to start writing that monad before moving on to elimination / helping.  
i'm finding a two things difficult :

- it is hard to represent a unified transaction log because of heterogeneous 
types, and 
- allowing a fully monadic interface makes it hard for me to special case 1-CAS 
(or applicative k-CAS.)

there are workarounds for the first issue (separate logs for each reference, or 
a global clock as in Transactional Locking II.)  for the second, right now i'm 
wondering if i'm going to have to write a compiler for a little DSL; i'd like 
to be able to exploit applicative performance gains generally, and special case 
1-CAS.  

best, ben

On Apr 6, 2012, at 5:38 AM, Heinrich Apfelmus wrote:

 Ben wrote:
 perhaps it is too late to suggest things for GSOC --
 but stephen tetley on a different thread pointed at aaron turon's
 work, which there's a very interesting new concurrency framework he
 calls reagents which seems to give the best of all worlds : it is
 declarative and compositional like STM, but gives performance akin to
 hand-coded lock-free data structures.  he seems to have straddled the
 duality of isolation vs message-passing nicely, and can subsume
 things like actors and the join calculus.
 http://www.ccs.neu.edu/home/turon/reagents.pdf
 he has a BSD licensed library in scala at
 https://github.com/aturon/ChemistrySet
 if someone doesn't want to pick this up for GSOC i might have a hand
 at implementing it myself.
 
 That looks great! While I didn't take the time to understand the concurrency 
 model in detail, the overall idea is to use arrows that can be run atomically
 
   runAtomically :: Reagent a b - (a - IO b)
 
 This is very similar to STM: combining computations within the monad/arrow is 
 atomic while combining computations outside the monad/arrow can interleave 
 them.
 
   runAtomically (f . g)  -- atomic
   runAtomically f . runAtomically g  -- interleaving
 
 
 Actually, it turns out that the  Reagent  arrow is also a monad, but the 
 author seems to claim that the static arrow style enables certain 
 optimizations. I haven't checked his model in detail to see whether this is 
 really the case and how exactly it differs from STM, but we know that 
 situations like this happen for parser combinators. Maybe it's enough to 
 recast reagents as an applicative functor?
 
 To summarize: the way I understand it is that it's apparently possible to 
 improve the STM monad by turning it into an arrow. (I refer to STM in a 
 very liberal sense here: whether memory is transactional or not is 
 unimportant, the only thing that matters is a computation that composes 
 atomically.)
 
 
 Best regards,
 Heinrich Apfelmus
 
 --
 http://apfelmus.nfshost.com
 
 
 

Re: [Haskell-cafe] why are applicative functors (often) faster than monads? (WAS Google Summer of Code - Lock-free data structures)

2012-04-20 Thread KC
Think of the differences (and similarities) of Applicative Functors and
Monads and the extra context that monads carry around.


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


Re: [Haskell-cafe] why are applicative functors (often) faster than monads? (WAS Google Summer of Code - Lock-free data structures)

2012-04-20 Thread Ben
i'm not sure what your email is pointing at.  if it is unclear, i understand 
the difference between applicative and monadic.  i suppose the easy answer to 
why applicative can be faster than monadic is that you can give a more 
specialized instance declaration.  i was just wondering if there was a way to 
make a monad recognize when it is being used applicatively, but that is 
probably hard in general.

b

On Apr 20, 2012, at 2:54 PM, KC wrote:

 Think of the differences (and similarities) of Applicative Functors and 
 Monads and the extra context that monads carry around.
 
 
 -- 
 --
 Regards,
 KC


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


Re: [Haskell-cafe] why are applicative functors (often) faster than monads? (WAS Google Summer of Code - Lock-free data structures)

2012-04-20 Thread KC
Sorry, I thought you or someone was asking why are Applicative Functors
faster in general than Monads.

Functional programming is structured function calling to achieve a result
where the functions can be evaluated in an unspecified order; I
thought Applicative Functors had the same unspecified evaluation order;
whereas, Monads could carry some sequencing of computations which has the
extra overhead of continuation passing.

Do I have that correct?


On Fri, Apr 20, 2012 at 4:05 PM, Ben midfi...@gmail.com wrote:

 i'm not sure what your email is pointing at.  if it is unclear, i
 understand the difference between applicative and monadic.  i suppose the
 easy answer to why applicative can be faster than monadic is that you can
 give a more specialized instance declaration.  i was just wondering if
 there was a way to make a monad recognize when it is being used
 applicatively, but that is probably hard in general.

 b

 On Apr 20, 2012, at 2:54 PM, KC wrote:

  Think of the differences (and similarities) of Applicative Functors and
 Monads and the extra context that monads carry around.
 
 
  --
  --
  Regards,
  KC




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


Re: [Haskell-cafe] why are applicative functors (often) faster than monads? (WAS Google Summer of Code - Lock-free data structures)

2012-04-20 Thread Ben
the sequencing matters for applicative functors.  from McBride and Patterson 
[1]:

The idea is that 'pure' embeds pure computations into the pure fragment of an 
effectful world -- the resulting computations may thus be shunted around 
freely, as long as the order of the genuinely effectful computations is 
preserved.

it is interesting to note that sequencing only matters a little for k-CAS : you 
just have to read before you write, but you can do the reads and writes in any 
order (as long as it is ultimately atomic.)

b

[1] McBride C, Patterson R. Applicative programming with effects Journal of 
Functional Programming 18:1 (2008), pages 1-13.

On Apr 20, 2012, at 4:41 PM, KC wrote:

 Sorry, I thought you or someone was asking why are Applicative Functors 
 faster in general than Monads.
 
 Functional programming is structured function calling to achieve a result 
 where the functions can be evaluated in an unspecified order; I thought 
 Applicative Functors had the same unspecified evaluation order; whereas, 
 Monads could carry some sequencing of computations which has the extra 
 overhead of continuation passing.
 
 Do I have that correct?
 
 
 On Fri, Apr 20, 2012 at 4:05 PM, Ben midfi...@gmail.com wrote:
 i'm not sure what your email is pointing at.  if it is unclear, i understand 
 the difference between applicative and monadic.  i suppose the easy answer to 
 why applicative can be faster than monadic is that you can give a more 
 specialized instance declaration.  i was just wondering if there was a way to 
 make a monad recognize when it is being used applicatively, but that is 
 probably hard in general.
 
 b
 
 On Apr 20, 2012, at 2:54 PM, KC wrote:
 
  Think of the differences (and similarities) of Applicative Functors and 
  Monads and the extra context that monads carry around.
 
 
  --
  --
  Regards,
  KC
 
 
 
 
 -- 
 --
 Regards,
 KC


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


[Haskell-cafe] ANNOUNCE: regex-applicative-0.1

2011-07-03 Thread Roman Cheplyaka
I am glad to announce the initial release of regex-applicative.

Hackage:  http://hackage.haskell.org/package/regex-applicative
Repository:   https://github.com/feuerbach/regex-applicative
Issues:   https://github.com/feuerbach/regex-applicative/issues

regex-applicative is aimed to be an efficient and easy to use parsing combinator
library based on regular expressions.

Perl programmers often use regular expressions for parsing, even if it is not
an appropriate tool for the job, because Perl has so good support for regexps.

The opposite seems to be valid about Haskell programmers -- they use parsing
combinators (which recognize context-free or even context-sensitive grammars),
even when the language is actually regular!

Hopefully, this library will improve the situation.

This is an early preview release. Some features are lacking, and performance is
probably not very good yet.

Among the features that we are going to support in future versions are:

* Non-greedy operators
* Search-and-replace functionality
* Error reporting

The implementation is heavily based on the ideas from A Play on Regular
Expressions by Sebastian Fischer, Frank Huch and Thomas Wilke.
http://sebfisch.github.com/haskell-regexp/regexp-play.pdf

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-16 Thread John Smith

On 15/12/2010 14:31, Lennart Augustsson wrote:

Yes, I think there should be a MonadFail distinct from MonadPlus.
Some types, like IO, are not in MonadPlus, but have a special implementation of 
the fail method.

Personally, I think fail should just be removed, but that would break existing 
code.
The fail method was introduced for the wrong reasons (better error messages was 
the excuse).


Which other monads (other than MonadPlus subclasses) define fail?


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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-16 Thread Antoine Latter
On Thu, Dec 16, 2010 at 12:03 PM, John Smith volderm...@hotmail.com wrote:
 On 15/12/2010 14:31, Lennart Augustsson wrote:

 Yes, I think there should be a MonadFail distinct from MonadPlus.
 Some types, like IO, are not in MonadPlus, but have a special
 implementation of the fail method.

 Personally, I think fail should just be removed, but that would break
 existing code.
 The fail method was introduced for the wrong reasons (better error
 messages was the excuse).

 Which other monads (other than MonadPlus subclasses) define fail?


STM is in MonadPlus, but I don't think pattern-match failure should be
the same as STM.retry.

Antoine

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-16 Thread Lennart Augustsson
IO

On Thu, Dec 16, 2010 at 6:03 PM, John Smith volderm...@hotmail.com wrote:

 On 15/12/2010 14:31, Lennart Augustsson wrote:

 Yes, I think there should be a MonadFail distinct from MonadPlus.
 Some types, like IO, are not in MonadPlus, but have a special
 implementation of the fail method.

 Personally, I think fail should just be removed, but that would break
 existing code.
 The fail method was introduced for the wrong reasons (better error
 messages was the excuse).


 Which other monads (other than MonadPlus subclasses) define fail?



 ___
 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] [Haskell] Functor = Applicative = Monad

2010-12-16 Thread Iavor Diatchki
Hello,

I think that we should make both changes (make Applicative a
super-class of Monad, and remove the fail method from Monad).  Code
will break but we can fix it.

By the way, just for reference, the proposal to have a separate
failure class and using it in the do notation, is how things used to
be back in Haskell 1.4 (one version before Haskell 98).  For the
curious, take a look at page 21 of
http://haskell.org/definition/haskell-report-1.4.ps.gz

-Iavor


On Thu, Dec 16, 2010 at 3:57 PM, Lennart Augustsson
lenn...@augustsson.net wrote:
 IO

 On Thu, Dec 16, 2010 at 6:03 PM, John Smith volderm...@hotmail.com wrote:

 On 15/12/2010 14:31, Lennart Augustsson wrote:

 Yes, I think there should be a MonadFail distinct from MonadPlus.
 Some types, like IO, are not in MonadPlus, but have a special
 implementation of the fail method.

 Personally, I think fail should just be removed, but that would break
 existing code.
 The fail method was introduced for the wrong reasons (better error
 messages was the excuse).

 Which other monads (other than MonadPlus subclasses) define fail?


 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread John Smith

On 15/12/2010 04:01, Jonathan Geddes wrote:

Fail can't just be removed. That would just break too much code. For
example, I find myself writing code like the following:


[a,b,c]- Just someList


in place of


let [a,b,c] = someList


so that pattern match failure is lifted into the maybe monad (as
long as I'm already in the maybe monad).

I would like to see a MonadFail class, with one method 'fail', such
that it is a compile-time error to try 'failable' pattern matches in a
monad that is not an instance of MonadFail.

--Jonathan


Perhaps pattern match failures in a MonadPlus should bind to mzero - I believe that this is what your example and 
similar wish to achieve.


I've updated http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal to mention this. Does anyone know why 
fail and Pointed (in the paragraph This would eliminate...) aren't beginning a new paragraph? They are both preceded 
by a blank line in the wiki source.



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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Tillmann Rendel

Hi John,

John Smith wrote:

Perhaps pattern match failures in a MonadPlus should bind to mzero - I
believe that this is what your example and similar wish to achieve.


You updated the proposal to say:

a failed pattern match should error in the same way as is does for pure code, 
while in
MonadPlus, the current behaviour could be maintained with mzero


Can you be more specific as to how that would interact with polymorphism 
and type inference? What does it mean to be in MonadPlus? How does the 
compiler know?


For example, what would be the static types and dynamic semantics of the 
following expressions:


 1. \a - do {Just x - return (Just a); return x}

 2. do {Just x - return Nothing; return x}

 3. \a - do {Just x - a; return x}

 4. \a b - do {(x, _) - return (a, b); return x}

 5. \a - do {(x, _) - return a; return x}

Tillmann

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Lennart Augustsson
Any refutable pattern match in do would force MonadFail (or MonadPlus if you
prefer).  So
1.  (MonadFail m) = a - m a,   \ a - return a
2.  (MonadFail m) = m a,   mfail ...
3.  (MonadFail m) = Maybe a - m a,   \ a - case a of Nothing - mfail
...; Just x - return x
4.  (Monad m) = a - b - m a,   \ a b - return a
5.  (Monad m) = (a, b) - m a,   \ (a, b) - return a

As far as type inference and desugaring goes, it seems very little would
have to be changed in an implementation.

  -- Lennart

2010/12/15 Tillmann Rendel ren...@informatik.uni-marburg.de

 Hi John,


 John Smith wrote:

 Perhaps pattern match failures in a MonadPlus should bind to mzero - I
 believe that this is what your example and similar wish to achieve.


 You updated the proposal to say:

 a failed pattern match should error in the same way as is does for pure
 code, while in
 MonadPlus, the current behaviour could be maintained with mzero


 Can you be more specific as to how that would interact with polymorphism
 and type inference? What does it mean to be in MonadPlus? How does the
 compiler know?

 For example, what would be the static types and dynamic semantics of the
 following expressions:

  1. \a - do {Just x - return (Just a); return x}

  2. do {Just x - return Nothing; return x}

  3. \a - do {Just x - a; return x}

  4. \a b - do {(x, _) - return (a, b); return x}

  5. \a - do {(x, _) - return a; return x}

Tillmann


 ___
 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] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Tillmann Rendel

John Smith proposed:

a failed pattern match should error in the same way as is does for
pure code, while in MonadPlus, the current behaviour could be
maintained with mzero


Lennart Augustsson wrote:

Any refutable pattern match in do would force MonadFail (or MonadPlus
if you prefer).


I guess that would work out, but I think John proposed something else.

  Tillmann

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread John Smith

On 15/12/2010 11:39, Lennart Augustsson wrote:

Any refutable pattern match in do would force MonadFail (or MonadPlus if you 
prefer).  So
1.  (MonadFail m) = a - m a,   \ a - return a
2.  (MonadFail m) = m a,   mfail ...
3.  (MonadFail m) = Maybe a - m a,   \ a - case a of Nothing - mfail ...; 
Just x - return x
4.  (Monad m) = a - b - m a,   \ a b - return a
5.  (Monad m) = (a, b) - m a,   \ (a, b) - return a

As far as type inference and desugaring goes, it seems very little would have 
to be changed in an implementation.


Is there a need for a MonadFail, as distinct from mzero? fail always seems to be defined as error in ordinary monads, 
and as mzero in MonadPlus (or left at the default error).



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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Lennart Augustsson
Yes, I think there should be a MonadFail distinct from MonadPlus.
Some types, like IO, are not in MonadPlus, but have a special implementation
of the fail method.

Personally, I think fail should just be removed, but that would break
existing code.
The fail method was introduced for the wrong reasons (better error messages
was the excuse).

  -- Lennart

On Wed, Dec 15, 2010 at 11:51 AM, John Smith volderm...@hotmail.com wrote:

 On 15/12/2010 11:39, Lennart Augustsson wrote:

 Any refutable pattern match in do would force MonadFail (or MonadPlus if
 you prefer).  So
 1.  (MonadFail m) = a - m a,   \ a - return a
 2.  (MonadFail m) = m a,   mfail ...
 3.  (MonadFail m) = Maybe a - m a,   \ a - case a of Nothing - mfail
 ...; Just x - return x
 4.  (Monad m) = a - b - m a,   \ a b - return a
 5.  (Monad m) = (a, b) - m a,   \ (a, b) - return a

 As far as type inference and desugaring goes, it seems very little would
 have to be changed in an implementation.


 Is there a need for a MonadFail, as distinct from mzero? fail always seems
 to be defined as error in ordinary monads, and as mzero in MonadPlus (or
 left at the default error).



 ___
 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] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Maciej Piechotka
On Wed, 2010-12-15 at 13:51 +0200, John Smith wrote:
 On 15/12/2010 11:39, Lennart Augustsson wrote:
  Any refutable pattern match in do would force MonadFail (or MonadPlus if 
  you prefer).  So
  1.  (MonadFail m) = a - m a,   \ a - return a
  2.  (MonadFail m) = m a,   mfail ...
  3.  (MonadFail m) = Maybe a - m a,   \ a - case a of Nothing - mfail 
  ...; Just x - return x
  4.  (Monad m) = a - b - m a,   \ a b - return a
  5.  (Monad m) = (a, b) - m a,   \ (a, b) - return a
 
  As far as type inference and desugaring goes, it seems very little would 
  have to be changed in an implementation.
 
 Is there a need for a MonadFail, as distinct from mzero? fail always seems to 
 be defined as error in ordinary monads, 
 and as mzero in MonadPlus (or left at the default error).

Not all types can implement mplus to begin with even if they can have
'zero' type. For example technically Maybe breaks the laws while still
having useful fail:

(guard . even) = (Just 1 | Just 2)
(guard . even) = Just 1
guard (even 1)
guard False
Nothing
/=
Just ()
Nothing | Just ()
guard False | guard True
(guard (even 1)) | (guard (even 2))
((guard . even) = Just 1) | ((guard . even) = Just 2)

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] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Brent Yorgey
On Wed, Dec 15, 2010 at 06:25:30PM +0100, Maciej Piechotka wrote:
 On Wed, 2010-12-15 at 13:51 +0200, John Smith wrote:
  On 15/12/2010 11:39, Lennart Augustsson wrote:
   Any refutable pattern match in do would force MonadFail (or MonadPlus if 
   you prefer).  So
   1.  (MonadFail m) = a - m a,   \ a - return a
   2.  (MonadFail m) = m a,   mfail ...
   3.  (MonadFail m) = Maybe a - m a,   \ a - case a of Nothing - mfail 
   ...; Just x - return x
   4.  (Monad m) = a - b - m a,   \ a b - return a
   5.  (Monad m) = (a, b) - m a,   \ (a, b) - return a
  
   As far as type inference and desugaring goes, it seems very little would 
   have to be changed in an implementation.
  
  Is there a need for a MonadFail, as distinct from mzero? fail always seems 
  to be defined as error in ordinary monads, 
  and as mzero in MonadPlus (or left at the default error).
 
 Not all types can implement mplus to begin with even if they can have
 'zero' type. For example technically Maybe breaks the laws while still
 having useful fail:
 
 (guard . even) = (Just 1 | Just 2)
 (guard . even) = Just 1
 guard (even 1)
 guard False
 Nothing
 /=
 Just ()
 Nothing | Just ()
 guard False | guard True
 (guard (even 1)) | (guard (even 2))
 ((guard . even) = Just 1) | ((guard . even) = Just 2)

But that depends on what laws you choose for MonadPlus.  See
http://www.haskell.org/haskellwiki/MonadPlus .

-Brent

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Conor McBride


On 15 Dec 2010, at 17:48, Brent Yorgey wrote:


On Wed, Dec 15, 2010 at 06:25:30PM +0100, Maciej Piechotka wrote:

On Wed, 2010-12-15 at 13:51 +0200, John Smith wrote:

On 15/12/2010 11:39, Lennart Augustsson wrote:
Any refutable pattern match in do would force MonadFail (or  
MonadPlus if you prefer).  So


[..]



As far as type inference and desugaring goes, it seems very  
little would have to be changed in an implementation.


Is there a need for a MonadFail, as distinct from mzero? fail  
always seems to be defined as error in ordinary monads,

and as mzero in MonadPlus (or left at the default error).


Not all types can implement mplus to begin with even if they can have
'zero' type. For example technically Maybe breaks the laws while  
still

having useful fail:


[..]



But that depends on what laws you choose for MonadPlus.  See
http://www.haskell.org/haskellwiki/MonadPlus .


What has any of this to do with monads?

Cheers

Conor


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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-14 Thread Conor McBride

[switching to cafe]

On 14 Dec 2010, at 08:59, Sittampalam, Ganesh wrote:


John Smith wrote:

I would like to formally propose that Monad become a subclass of
Applicative, with a call for consensus by 1 February.


I would prefer that we have some proposal like class aliases  
implemented

before we start fundamental restructuring of basic type classes. This
would help to limit the disruption these changes cause, which will be
substantial.


I'm inclined to agree. What's even more galling than not having
Functor and Applicative instances for Monads is having to write
them!

At the very least, can we open this particular vessel of vermicular
splendidity and verify that the inmates are still grinning with
persistence?

If I recall, the class alias proposal was rather more ambitious
than necessary to solve this problem (though that is no crime),
but still a little wrinkled in the corners. Looking at the
relevant webpages, I see the proposal has lots of attractive
motivational examples, but less by way of definition. But perhaps,
somewhere, it has been defined enough for a prototype?

It's surely worth looking at some way to define default instances
for superclasses, provided they can be overridden or switched off.

Where did this train of though leave the rails, again?

Cheers

Conor


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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-14 Thread Tillmann Rendel

Hi,

John Smith wrote:

I would like to formally propose that Monad become a subclass of
Applicative


A lot of code would break because of this change, but all problems 
should be reported at compile time, and are easy to fix. In most of the 
cases, either adding obvious Functor and Applicative instances to a 
library; or deleting such instances from a client, I would expect. This 
kind of clean-up would actually increase the quality of the library, 
however, and might therefore be acceptable.



The change is  described on the wiki at
http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal


There you write, among other things:

fail should be removed from Monad; a failed pattern match could error in the 
same way as is does for pure code.


How is this part of the proposal related to Functor and Applicative?

Since code depending on the current behavior can not be detected at 
compile time, this is a more serious change in a way: code keeps 
compiling but changes its meaning. Can you estimate how much code would 
break because of this change?


Would it be possible to keep user-defined failure handling in do 
notation without keeping fail in Monad?


  Tillmann

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-14 Thread Antoine Latter
2010/12/14 Tillmann Rendel ren...@informatik.uni-marburg.de:
 Hi,

 John Smith wrote:

 I would like to formally propose that Monad become a subclass of
 Applicative

 A lot of code would break because of this change, but all problems should be
 reported at compile time, and are easy to fix. In most of the cases, either
 adding obvious Functor and Applicative instances to a library; or deleting
 such instances from a client, I would expect. This kind of clean-up would
 actually increase the quality of the library, however, and might therefore
 be acceptable.

 The change is  described on the wiki at
 http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal

 There you write, among other things:

 fail should be removed from Monad; a failed pattern match could error in
 the same way as is does for pure code.

 How is this part of the proposal related to Functor and Applicative?

 Since code depending on the current behavior can not be detected at compile
 time, this is a more serious change in a way: code keeps compiling but
 changes its meaning. Can you estimate how much code would break because of
 this change?

 Would it be possible to keep user-defined failure handling in do notation
 without keeping fail in Monad?


When this change was made for the 'Either' monad, I remember that it
introduced sneaky runtime bugs into the, I think, HTTP library. So
your concerns are founded.

I really think that these proposals should be considered separately,
even if they would be enacted at the same time if they both passed.

Antoine

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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-14 Thread Jonathan Geddes
Fail can't just be removed. That would just break too much code. For
example, I find myself writing code like the following:

[a,b,c] - Just someList

in place of

let [a,b,c] = someList

so that pattern match failure is lifted into the maybe monad (as
long as I'm already in the maybe monad).

I would like to see a MonadFail class, with one method 'fail', such
that it is a compile-time error to try 'failable' pattern matches in a
monad that is not an instance of MonadFail.

--Jonathan

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


[Haskell-cafe] On to applicative

2010-09-04 Thread michael rice
The two myAction functions below seem to be equivalent and, for this small 
case, show an interesting economy of code, but being far from a Haskell expert, 
I have to ask, is the first function as small (code wise) as it could be?

Michael


import Control.Applicative

data Color
    = Red
    | Blue
    | Green
    | Yellow
    | Orange
    | Brown
    | Black
    | White
    deriving (Show, Read, Eq, Enum, Ord, Bounded)

-- myAction :: IO Color
-- myAction = getLine
--    = \str - return (read str :: Color)

myAction :: IO Color
myAction = read $ getLine




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


Re: [Haskell-cafe] On to applicative

2010-09-04 Thread David Menendez
On Sat, Sep 4, 2010 at 2:06 PM, michael rice nowg...@yahoo.com wrote:

 The two myAction functions below seem to be equivalent and, for this small
 case, show an interesting economy of code, but being far from a Haskell
 expert, I have to ask, is the first function as small (code wise) as it
 could be?

 Michael


 import Control.Applicative

 data Color
 = Red
 | Blue
 | Green
 | Yellow
 | Orange
 | Brown
 | Black
 | White
 deriving (Show, Read, Eq, Enum, Ord, Bounded)

 -- myAction :: IO Color
 -- myAction = getLine
 --= \str - return (read str :: Color)


First, you don't need the type annotation here. Haskell will infer it from
the annotation on myAction. (You also don't need the type on myAction, but
that's not important now.)

myAction = getLine = \str - return (read str)

Second, you have the pattern \x - f (g x), so you can replace the lambda
with function composition.

myAction = getLine = return . read

Third, there is a standard function liftM, defined in Control.Monad,
where liftM f m = m = return . f, so

myAction = liftM read getLine

Finally, we expect an instance of Monad to also be an instance of Functor,
with fmap = liftM, and we also have f $ m = fmap f m, so


 myAction :: IO Color
 myAction = read $ getLine


-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-09-04 Thread michael rice
Hi Dave,

I wrote the first one sometime last year and it seemed a suitably simple 
example for applicative-izing to cement the ideas in some of the code I've been 
going though in Learn You a Haskell ... Interesting stuff.

Onward and upward.

Thanks,

Michael

--- On Sat, 9/4/10, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, September 4, 2010, 2:23 PM

On Sat, Sep 4, 2010 at 2:06 PM, michael rice nowg...@yahoo.com wrote:

The two myAction functions below seem to be equivalent and, for this small 
case, show an interesting economy of code, but being far from a Haskell expert, 
I have to ask, is the first function as small (code wise) as it could be?


Michael


import Control.Applicative

data Color
    = Red
    | Blue
    | Green
    | Yellow
    | Orange
    | Brown
    | Black
    | White
    deriving (Show, Read, Eq, Enum, Ord, Bounded)


-- myAction :: IO Color
-- myAction = getLine
--    = \str - return (read str :: Color)

First, you don't need the type annotation here. Haskell will infer it from the 
annotation on myAction. (You also don't need the type on myAction, but that's 
not important now.)

myAction = getLine = \str - return (read str)
Second, you have the pattern \x - f (g x), so you can replace the lambda with 
function composition.

myAction = getLine = return . read
Third, there is a standard function liftM, defined in Control.Monad, 
where liftM f m = m = return . f, so
myAction = liftM read getLine

Finally, we expect an instance of Monad to also be an instance of Functor, with 
fmap = liftM, and we also have f $ m = fmap f m, so 
myAction :: IO Color
myAction = read $ getLine
-- 
Dave Menendez d...@zednenem.com

http://www.eyrie.org/~zednenem/




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


Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
Sorry, my last message got garbled. Hope this is better.

Prelude Control.Monad Control.Monad.Instances Control.Applicative let f = \x 
- x:[]
Prelude Control.Monad Control.Monad.Instances Control.Applicative :t f
f :: a - [a]
Prelude Control.Monad Control.Monad.Instances Control.Applicative let g = \x 
- Just x
Prelude Control.Monad Control.Monad.Instances Control.Applicative :t g
g :: a - Maybe a

=

Prelude Control.Monad Control.Monad.Instances Control.Applicative let z = \x 
- x+1
Prelude Control.Monad Control.Monad.Instances Control.Applicative :t z
z :: Integer - Integer

Prelude Control.Monad Control.Monad.Instances Control.Applicative.Data.Char 
let y = \x - ord x
Prelude Control.Monad Control.Monad.Instances Control.Applicative Data.Char :t 
y
y :: Char - Int


Can you think of a situation for

 \x - f x
or
 \x y z - x + ord y - head z

that would require x (y z) to have their type(s) declared (ala Pascal), or is 
it always
inferred by what appears to the right of -?

I guess what I'm asking is can an anonymous function be given a type signature?

Michael

--- On Wed, 9/1/10, Tillmann Rendel ren...@mathematik.uni-marburg.de wrote:

From: Tillmann Rendel ren...@mathematik.uni-marburg.de
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Wednesday, September 1, 2010, 5:28 PM

michael rice wrote:
 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

So to create a value of type (Maybe ...), you can use Just.

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

So to create a value of type [...], you can use (:) and [].

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

So to create a value of type (IO ...), you can use getLine.

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

So to create a value of type (Either ... ...), you can use Right.

 How can I similarly create an instance of (-) [...] ?

An instance of (-) is usually called a function. And functions are created 
by lambda abstraction:

  Prelude let f = \x - x
  Prelude :t f
  f :: t - t

So to create a value of type (... - ...), you can use \.


Just like Either, - is a binary type constructor. Just like (Either a b) is a 
type, (a - b) is a type. And very much like you can create (Either a b) values 
with Left and Right, you can create (a - b) values with \.

  Tillmann

PS. After studying how to construct values, it may be instructive to study how 
to take them apart. For example, Bool values can be taken apart by if-then-else 
expressions. What about Either, IO and - values?



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


Re: [Haskell-cafe] On to applicative

2010-09-02 Thread David Menendez
On Thu, Sep 2, 2010 at 10:45 AM, michael rice nowg...@yahoo.com wrote:


 Can you think of a situation for

  \x - f x
 or
  \x y z - x + ord y - head z

 that would require x (y z) to have their type(s) declared (ala Pascal), or
 is it always
 inferred by what appears to the right of -?


I think Haskell 98 can always infer the type of an anonymous function. There
are some extensions involving more advanced types that can't be inferred,
but you don't need to worry about them yet.


 I guess what I'm asking is can an anonymous function be given a type
 signature?


Sure. Just write (\x - x + 1) :: Int - Int. (The parentheses are
important. Without them, the type signature is given to the function body.)

I don't think I've ever needed to give a type for an anonymous function,
though. Generally, the context where the function is being used is
sufficient.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
In each case, what does the notation

show:: ...

and

undefined:: ...

accomplish?

Prelude Control.Applicative :t show::((-) Int) String
show::((-) Int) String :: Int - String
Prelude Control.Applicative :t undefined::((-) Int) String
undefined::((-) Int) String :: Int - String

Michael


--- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 4:17 PM

FmapFunc is just a test module I created with

instance Functor ((-) r) where ...

  -- ryan

On Tue, Aug 31, 2010 at 12:03 PM, michael rice nowg...@yahoo.com wrote:


Hi, Ryan and all,

Bingo! I guess my question was all right after all.

I tried creating an instance earlier but 

*Main :t (-) Int Char

interactive:1:1: parse error on input `-'


What got loaded with FmapFunc? I Hoogled it and got back nothing.

Michael

--- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:


From: Ryan Ingram ryani.s...@gmail.com

Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org

Date: Tuesday, August 31, 2010, 2:36 PM

Prelude FmapFunc let s = show :: ((-) Int) String
Prelude
 FmapFunc :t s
s :: Int - String
Prelude FmapFunc let v = fmap (hello  ++) s
Prelude FmapFunc :t v
v :: Int - String

Prelude FmapFunc v 1
hello 1

  -- ryan

On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:



I'm not sure if my terminology is correct or even if my question makes sense, 
but I can create instances of Maybe, List, IO, and Either.

Prelude Data.Either let m = Just 7
Prelude Data.Either :t m


m :: Maybe Integer

Prelude Data.Either let l = 2:[]
Prelude Data.Either :t l
l :: [Integer]

Prelude Data.Either let g = getLine
Prelude Data.Either :t g
g :: IO String

Prelude Data.Either let e = Right abc


Prelude Data.Either :t e
e :: Either a [Char]

All these instances are functors, each with its own version of fmap that can be 
applied to it.

How can I similarly create an instance of (-) so I can apply (-)'s version of 
fmap



instance Functor ((-) r) where  
    fmap f g = (\x - f (g x))

to
 it?

Michael

--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:



From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com


Cc: haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 1:50 PM

2010/8/31 michael rice nowg...@yahoo.com



 So it's a type constructor, not a type? Could you please provide a simple 
 example of its usage?

Sure, although I'm sure you've come by some already.

-- the identity function
id :: a - a


-- often, we write it like this:
-- id x = x
-- but here we see the relationship between the ananymous function
syntax and the function
 type:
id = \x - x

In fact, if you write in prefix form, it is quite familiar:
f :: (-) Int Bool
e = Either String Float

Cheers,
Thu

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:



 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com


 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:17 PM

 2010/8/31 michael rice nowg...@yahoo.com


 
  Learn You a Haskell ...  says that (-) is a type just like Either. Where 
  can I find its type definition?

 You can't define it *in* Haskell as user code. It is a built-in infix


 type constructor (Either or Maybe are type constructors too, not just
 types). In fact, if you want to implement a simple, typed functional
 language, you'll find it is the only built-in type constructor you


 have to implement (as the implementor of the language).

 Also,
   Show a = a
 is a type too, but you won't find a definition for 'a' or for '='.
 All those things are defined by the language.



 Cheers,
 Thu




  
___

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] On to applicative

2010-09-02 Thread Alexander Solla


On Sep 2, 2010, at 11:30 AM, michael rice wrote:


In each case, what does the notation

show:: ...

and

undefined:: ...

accomplish?


They're type annotations.  show is a function in many types:

Prelude :t show
show :: (Show a) = a - String

If you want to see the type of a specific show function, you need to  
find a way to determine its type.  This is a slightly different  
function, but it's equivalent in types and semantics:


Prelude :t \x - show x
\x - show x :: (Show a) = a - String

Now we have a named argument, and we can constraint its type with an  
annotation:


Prelude :t \x - show (x :: Int)
\x - show (x :: Int) :: Int - String

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


Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
Hi Alexander,

Prelude FmapFunc let s = show :: ((-) Int) String
Prelude FmapFunc :t s
s :: Int - String

The notation was throwing me, but after staring at it for a while it finally 
sunk in that show (above) is partially applied.

Thanks, all.

Michael


--- On Thu, 9/2/10, Alexander Solla a...@2piix.com wrote:

From: Alexander Solla a...@2piix.com
Subject: Re: [Haskell-cafe] On to applicative
To: 
Cc: haskell-cafe Cafe haskell-cafe@haskell.org
Date: Thursday, September 2, 2010, 2:46 PM


On Sep 2, 2010, at 11:30 AM, michael rice wrote:
In each case, what does the notation

show:: ...

and

undefined:: ...

accomplish?
They're type annotations.  show is a function in many types:
Prelude :t showshow :: (Show a) = a - String
If you want to see the type of a specific show function, you need to find a 
way to determine its type.  This is a slightly different function, but it's 
equivalent in types and semantics:
Prelude :t \x - show x\x - show x :: (Show a) = a - String
Now we have a named argument, and we can constraint its type with an annotation:
Prelude :t \x - show (x :: Int)\x - show (x :: Int) :: Int - String

-Inline Attachment Follows-

___
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] On to applicative

2010-09-02 Thread michael rice
This may be a dumb question, but here goes.

Types Maybe, Either, List, are types and also instances of Functor (and Monad).

Assuming (-) is also a type, where can I find its type definition?

Michael




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


Re: [Haskell-cafe] On to applicative

2010-09-02 Thread David Menendez
On Thu, Sep 2, 2010 at 9:16 PM, michael rice nowg...@yahoo.com wrote:

 This may be a dumb question, but here goes.

 Types Maybe, Either, List, are types and also instances of Functor (and
 Monad).

 Assuming (-) is also a type, where can I find its type definition?


(-) is a built-in type. You could say its definition is in the Haskell
Report.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-09-02 Thread michael rice
Cool, I'll go looking for it. I couldn't find anything on Hoogle.

Thanks,

Michael

--- On Thu, 9/2/10, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, September 2, 2010, 9:26 PM

On Thu, Sep 2, 2010 at 9:16 PM, michael rice nowg...@yahoo.com wrote:

This may be a dumb question, but here goes.

Types Maybe, Either, List, are types and also instances of Functor (and Monad).


Assuming (-) is also a type, where can I find its type definition?

(-) is a built-in type. You could say its definition is in the Haskell Report.


-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/




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


Re: [Haskell-cafe] On to applicative

2010-09-01 Thread Tillmann Rendel

michael rice wrote:

Prelude Data.Either let m = Just 7
Prelude Data.Either :t m
m :: Maybe Integer


So to create a value of type (Maybe ...), you can use Just.


Prelude Data.Either let l = 2:[]
Prelude Data.Either :t l
l :: [Integer]


So to create a value of type [...], you can use (:) and [].


Prelude Data.Either let g = getLine
Prelude Data.Either :t g
g :: IO String


So to create a value of type (IO ...), you can use getLine.


Prelude Data.Either let e = Right abc
Prelude Data.Either :t e
e :: Either a [Char]


So to create a value of type (Either ... ...), you can use Right.


How can I similarly create an instance of (-) [...] ?


An instance of (-) is usually called a function. And functions are 
created by lambda abstraction:


  Prelude let f = \x - x
  Prelude :t f
  f :: t - t

So to create a value of type (... - ...), you can use \.


Just like Either, - is a binary type constructor. Just like (Either a 
b) is a type, (a - b) is a type. And very much like you can create 
(Either a b) values with Left and Right, you can create (a - b) values 
with \.


  Tillmann

PS. After studying how to construct values, it may be instructive to 
study how to take them apart. For example, Bool values can be taken 
apart by if-then-else expressions. What about Either, IO and - values?

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


Re: [Haskell-cafe] On to applicative

2010-09-01 Thread michael rice
Hi Tillman,

Prelude Control.Monad Control.Monad.Instances Control.Applicative let f = \x 
- x:[]
Prelude Control.Monad Control.Monad.Instances Control.Applicative :t f
f :: a - [a]
Prelude Control.Monad Control.Monad.Instances Control.Applicative let g = \x 
- Just x
Prelude Control.Monad Control.Monad.Instances Control.Applicative :t g
g :: a - Maybe a

Prelude Control.Monad Control.Monad.Instances Control.Applicative :t z
z :: Integer - Integer

Prelude Control.Monad Control.Monad.Instances Control.Applicative Data.Char :t 
y
y :: Char - Int


Can you think of a situation for

 \x - f x

that would require x to have a declared type, or is it always inferred by the 
type of f?


Michael


--- On Wed, 9/1/10, Tillmann Rendel ren...@mathematik.uni-marburg.de wrote:

From: Tillmann Rendel ren...@mathematik.uni-marburg.de
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Wednesday, September 1, 2010, 5:28 PM

michael rice wrote:
 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

So to create a value of type (Maybe ...), you can use Just.

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

So to create a value of type [...], you can use (:) and [].

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

So to create a value of type (IO ...), you can use getLine.

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

So to create a value of type (Either ... ...), you can use Right.

 How can I similarly create an instance of (-) [...] ?

An instance of (-) is usually called a function. And functions are created 
by lambda abstraction:

  Prelude let f = \x - x
  Prelude :t f
  f :: t - t

So to create a value of type (... - ...), you can use \.


Just like Either, - is a binary type constructor. Just like (Either a b) is a 
type, (a - b) is a type. And very much like you can create (Either a b) values 
with Left and Right, you can create (a - b) values with \.

  Tillmann

PS. After studying how to construct values, it may be instructive to study how 
to take them apart. For example, Bool values can be taken apart by if-then-else 
expressions. What about Either, IO and - values?



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


[Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
Learn You a Haskell ...  says that (-) is a type just like Either. Where can 
I find its type definition?

Michael



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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice nowg...@yahoo.com

 Learn You a Haskell ...  says that (-) is a type just like Either. Where 
 can I find its type definition?

You can't define it *in* Haskell as user code. It is a built-in infix
type constructor (Either or Maybe are type constructors too, not just
types). In fact, if you want to implement a simple, typed functional
language, you'll find it is the only built-in type constructor you
have to implement (as the implementor of the language).

Also,
  Show a = a
is a type too, but you won't find a definition for 'a' or for '='.
All those things are defined by the language.

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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
So it's a type constructor, not a type? Could you please provide a simple 
example of its usage?

Michael

--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 1:17 PM

2010/8/31 michael rice nowg...@yahoo.com

 Learn You a Haskell ...  says that (-) is a type just like Either. Where 
 can I find its type definition?

You can't define it *in* Haskell as user code. It is a built-in infix
type constructor (Either or Maybe are type constructors too, not just
types). In fact, if you want to implement a simple, typed functional
language, you'll find it is the only built-in type constructor you
have to implement (as the implementor of the language).

Also,
  Show a = a
is a type too, but you won't find a definition for 'a' or for '='.
All those things are defined by the language.

Cheers,
Thu



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


Re[2]: [Haskell-cafe] On to applicative

2010-08-31 Thread Bulat Ziganshin
Hello michael,

Tuesday, August 31, 2010, 9:27:17 PM, you wrote:

f :: Int - Int

i.e. it's used when you define function types

 So it's a type constructor, not a type? Could you please provide a simple 
 example of its usage?

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:17 PM

 2010/8/31 michael rice nowg...@yahoo.com

 Learn You a Haskell ...  says that (-) is a type just like Either. Where 
 can I find its type definition?

 You can't define it *in* Haskell as user code. It is a  built-in infix
 type constructor (Either or Maybe are type constructors too, not just
 types). In fact, if you want to implement a simple, typed functional
 language, you'll find it is the only built-in type constructor you
 have to implement (as the implementor of the language).

 Also,
   Show a = a
 is a type too, but you won't find a definition for 'a' or for '='.
 All those things are defined by the language.

 Cheers,
 Thu


   


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice nowg...@yahoo.com

 So it's a type constructor, not a type? Could you please provide a simple 
 example of its usage?

Sure, although I'm sure you've come by some already.

-- the identity function
id :: a - a
-- often, we write it like this:
-- id x = x
-- but here we see the relationship between the ananymous function
syntax and the function type:
id = \x - x

In fact, if you write in prefix form, it is quite familiar:
f :: (-) Int Bool
e = Either String Float

Cheers,
Thu

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:17 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  Learn You a Haskell ...  says that (-) is a type just like Either. Where 
  can I find its type definition?

 You can't define it *in* Haskell as user code. It is a built-in infix
 type constructor (Either or Maybe are type constructors too, not just
 types). In fact, if you want to implement a simple, typed functional
 language, you'll find it is the only built-in type constructor you
 have to implement (as the implementor of the language).

 Also,
   Show a = a
 is a type too, but you won't find a definition for 'a' or for '='.
 All those things are defined by the language.

 Cheers,
 Thu

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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
I'm not sure if my terminology is correct or even if my question makes sense, 
but I can create instances of Maybe, List, IO, and Either.

Prelude Data.Either let m = Just 7
Prelude Data.Either :t m
m :: Maybe Integer

Prelude Data.Either let l = 2:[]
Prelude Data.Either :t l
l :: [Integer]

Prelude Data.Either let g = getLine
Prelude Data.Either :t g
g :: IO String

Prelude Data.Either let e = Right abc
Prelude Data.Either :t e
e :: Either a [Char]

All these instances are functors, each with its own version of fmap that can be 
applied to it.

How can I similarly create an instance of (-) so I can apply (-)'s version of 
fmap

instance Functor ((-) r) where  
    fmap f g = (\x - f (g x))

to it?

Michael

--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 1:50 PM

2010/8/31 michael rice nowg...@yahoo.com

 So it's a type constructor, not a type? Could you please provide a simple 
 example of its usage?

Sure, although I'm sure you've come by some already.

-- the identity function
id :: a - a
-- often, we write it like this:
-- id x = x
-- but here we see the relationship between the ananymous function
syntax and the function type:
id = \x - x

In fact, if you write in prefix form, it is quite familiar:
f :: (-) Int Bool
e = Either String Float

Cheers,
Thu

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:17 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  Learn You a Haskell ...  says that (-) is a type just like Either. Where 
  can I find its type definition?

 You can't define it *in* Haskell as user code. It is a built-in infix
 type constructor (Either or Maybe are type constructors too, not just
 types). In fact, if you want to implement a simple, typed functional
 language, you'll find it is the only built-in type constructor you
 have to implement (as the implementor of the language).

 Also,
   Show a = a
 is a type too, but you won't find a definition for 'a' or for '='.
 All those things are defined by the language.

 Cheers,
 Thu




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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Ryan Ingram
Prelude FmapFunc let s = show :: ((-) Int) String
Prelude FmapFunc :t s
s :: Int - String
Prelude FmapFunc let v = fmap (hello  ++) s
Prelude FmapFunc :t v
v :: Int - String
Prelude FmapFunc v 1
hello 1

  -- ryan

On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:

 I'm not sure if my terminology is correct or even if my question makes
 sense, but I can create instances of Maybe, List, IO, and Either.

 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

 All these instances are functors, each with its own version of fmap that
 can be applied to it.

 How can I similarly create an instance of (-) so I can apply (-)'s
 version of fmap

 instance Functor ((-) r) where
 fmap f g = (\x - f (g x))

 to it?


 Michael

 --- On *Tue, 8/31/10, Vo Minh Thu not...@gmail.com* wrote:


 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:50 PM


 2010/8/31 michael rice 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
 
  So it's a type constructor, not a type? Could you please provide a simple
 example of its usage?

 Sure, although I'm sure you've come by some already.

 -- the identity function
 id :: a - a
 -- often, we write it like this:
 -- id x = x
 -- but here we see the relationship between the ananymous function
 syntax and the function type:
 id = \x - x

 In fact, if you write in prefix form, it is quite familiar:
 f :: (-) Int Bool
 e = Either String Float

 Cheers,
 Thu

  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu 
  not...@gmail.comhttp://mc/compose?to=not...@gmail.com
 wrote:
 
  From: Vo Minh Thu not...@gmail.comhttp://mc/compose?to=not...@gmail.com
 
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice 
  nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
  Cc: haskell-cafe@haskell.orghttp://mc/compose?to=haskell-c...@haskell.org
  Date: Tuesday, August 31, 2010, 1:17 PM
 
  2010/8/31 michael rice 
  nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
  
   Learn You a Haskell ...  says that (-) is a type just like Either.
 Where can I find its type definition?
 
  You can't define it *in* Haskell as user code. It is a built-in infix
  type constructor (Either or Maybe are type constructors too, not just
  types). In fact, if you want to implement a simple, typed functional
  language, you'll find it is the only built-in type constructor you
  have to implement (as the implementor of the language).
 
  Also,
Show a = a
  is a type too, but you won't find a definition for 'a' or for '='.
  All those things are defined by the language.
 
  Cheers,
  Thu
 



 ___
 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] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice nowg...@yahoo.com

 I'm not sure if my terminology is correct or even if my question makes sense, 
 but I can create instances of Maybe, List, IO, and Either.

 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

We say that m has type Maybe Integer, so :: is pronounced 'has type'.
We also say that m is a value. Just is a type constructor, Maybe Int
is a type, and Just 7, like m, is a value.

So we don't talk about instance here. Informally you could say that 7
is an instance of Int, but in Haskell we use 'instance' to mean
something (precisely) else.

This pharse is correct w.r.t to the use of 'instance' in Haskell:
Maybe is an instance of the Functor class.

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

 All these instances are functors, each with its own version of fmap that can 
 be applied to it.

 How can I similarly create an instance of (-) so I can apply (-)'s version 
 of fmap

 instance Functor ((-) r) where
     fmap f g = (\x - f (g x))

 to it?

Note that for Maybe, the instance is define with
  instance Functor Maybe where ...

Note how the type argument of Maybe is not given.
But above, when you create a value, it has type Maybe Int, not only Maybe.

So for the ((-) r) case, you still want to complete it.
E.g.
m :: Maybe Int -- not just Maybe
(+) :: (-) Int Int -- and not only (-) Int

Cheers,
Thu

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:50 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  So it's a type constructor, not a type? Could you please provide a simple 
  example of its usage?

 Sure, although I'm sure you've come by some already.

 -- the identity function
 id :: a - a
 -- often, we write it like this:
 -- id x = x
 -- but here we see the relationship between the ananymous function
 syntax and the function type:
 id = \x - x

 In fact, if you write in prefix form, it is quite familiar:
 f :: (-) Int Bool
 e = Either String Float

 Cheers,
 Thu

  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
 
  From: Vo Minh Thu not...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 1:17 PM
 
  2010/8/31 michael rice nowg...@yahoo.com
  
   Learn You a Haskell ...  says that (-) is a type just like Either. 
   Where can I find its type definition?
 
  You can't define it *in* Haskell as user code. It is a built-in infix
  type constructor (Either or Maybe are type constructors too, not just
  types). In fact, if you want to implement a simple, typed functional
  language, you'll find it is the only built-in type constructor you
  have to implement (as the implementor of the language).
 
  Also,
    Show a = a
  is a type too, but you won't find a definition for 'a' or for '='.
  All those things are defined by the language.
 
  Cheers,
  Thu
 

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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
Hi, Ryan and all,

Bingo! I guess my question was all right after all.

I tried creating an instance earlier but 

*Main :t (-) Int Char

interactive:1:1: parse error on input `-'

What got loaded with FmapFunc? I Hoogled it and got back nothing.

Michael

--- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 2:36 PM

Prelude FmapFunc let s = show :: ((-) Int) String
Prelude FmapFunc :t s
s :: Int - String
Prelude FmapFunc let v = fmap (hello  ++) s
Prelude FmapFunc :t v
v :: Int - String

Prelude FmapFunc v 1
hello 1

  -- ryan

On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:


I'm not sure if my terminology is correct or even if my question makes sense, 
but I can create instances of Maybe, List, IO, and Either.

Prelude Data.Either let m = Just 7
Prelude Data.Either :t m

m :: Maybe Integer

Prelude Data.Either let l = 2:[]
Prelude Data.Either :t l
l :: [Integer]

Prelude Data.Either let g = getLine
Prelude Data.Either :t g
g :: IO String

Prelude Data.Either let e = Right abc

Prelude Data.Either :t e
e :: Either a [Char]

All these instances are functors, each with its own version of fmap that can be 
applied to it.

How can I similarly create an instance of (-) so I can apply (-)'s version of 
fmap


instance Functor ((-) r) where  
    fmap f g = (\x - f (g x))

to
 it?

Michael

--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:


From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com

Cc: haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 1:50 PM

2010/8/31 michael rice nowg...@yahoo.com


 So it's a type constructor, not a type? Could you please provide a simple 
 example of its usage?

Sure, although I'm sure you've come by some already.

-- the identity function
id :: a - a

-- often, we write it like this:
-- id x = x
-- but here we see the relationship between the ananymous function
syntax and the function
 type:
id = \x - x

In fact, if you write in prefix form, it is quite familiar:
f :: (-) Int Bool
e = Either String Float

Cheers,
Thu

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:


 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com

 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:17 PM

 2010/8/31 michael rice nowg...@yahoo.com

 
  Learn You a Haskell ...  says that (-) is a type just like Either. Where 
  can I find its type definition?

 You can't define it *in* Haskell as user code. It is a built-in infix

 type constructor (Either or Maybe are type constructors too, not just
 types). In fact, if you want to implement a simple, typed functional
 language, you'll find it is the only built-in type constructor you

 have to implement (as the implementor of the language).

 Also,
   Show a = a
 is a type too, but you won't find a definition for 'a' or for '='.
 All those things are defined by the language.


 Cheers,
 Thu




  
___

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] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice nowg...@yahoo.com

 Hi, Ryan and all,

 Bingo! I guess my question was all right after all.

 I tried creating an instance earlier but

 *Main :t (-) Int Char

 interactive:1:1: parse error on input `-'

  :t Int
does not make sense but
  :t undefined :: Int
is ok, just like
   :t undefined :: (-) Int Int

 What got loaded with FmapFunc? I Hoogled it and got back nothing.

 Michael

 --- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:

 From: Ryan Ingram ryani.s...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 2:36 PM

 Prelude FmapFunc let s = show :: ((-) Int) String
 Prelude FmapFunc :t s
 s :: Int - String
 Prelude FmapFunc let v = fmap (hello  ++) s
 Prelude FmapFunc :t v
 v :: Int - String
 Prelude FmapFunc v 1
 hello 1

   -- ryan

 On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:

 I'm not sure if my terminology is correct or even if my question makes sense, 
 but I can create instances of Maybe, List, IO, and Either.

 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

 All these instances are functors, each with its own version of fmap that can 
 be applied to it.

 How can I similarly create an instance of (-) so I can apply (-)'s version 
 of fmap

 instance Functor ((-) r) where
     fmap f g = (\x - f (g x))

 to it?

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:50 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  So it's a type constructor, not a type? Could you please provide a simple 
  example of its usage?

 Sure, although I'm sure you've come by some already.

 -- the identity function
 id :: a - a
 -- often, we write it like this:
 -- id x = x
 -- but here we see the relationship between the ananymous function
 syntax and the function type:
 id = \x - x

 In fact, if you write in prefix form, it is quite familiar:
 f :: (-) Int Bool
 e = Either String Float

 Cheers,
 Thu

  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
 
  From: Vo Minh Thu not...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 1:17 PM
 
  2010/8/31 michael rice nowg...@yahoo.com
  
   Learn You a Haskell ...  says that (-) is a type just like Either. 
   Where can I find its type definition?
 
  You can't define it *in* Haskell as user code. It is a built-in infix
  type constructor (Either or Maybe are type constructors too, not just
  types). In fact, if you want to implement a simple, typed functional
  language, you'll find it is the only built-in type constructor you
  have to implement (as the implementor of the language).
 
  Also,
    Show a = a
  is a type too, but you won't find a definition for 'a' or for '='.
  All those things are defined by the language.
 
  Cheers,
  Thu
 


 ___
 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] On to applicative

2010-08-31 Thread michael rice
Hi Vo,

Pardon, I grabbed the wrong lines.

*Main :t (-) 3 abc

interactive:1:1: parse error on input `-'

Michael

--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: Ryan Ingram ryani.s...@gmail.com, haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 3:07 PM

2010/8/31 michael rice nowg...@yahoo.com

 Hi, Ryan and all,

 Bingo! I guess my question was all right after all.

 I tried creating an instance earlier but

 *Main :t (-) Int Char

 interactive:1:1: parse error on input `-'

  :t Int
does not make sense but
  :t undefined :: Int
is ok, just like
   :t undefined :: (-) Int Int

 What got loaded with FmapFunc? I Hoogled it and got back nothing.

 Michael

 --- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:

 From: Ryan Ingram ryani.s...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 2:36 PM

 Prelude FmapFunc let s = show :: ((-) Int) String
 Prelude FmapFunc :t s
 s :: Int - String
 Prelude FmapFunc let v = fmap (hello  ++) s
 Prelude FmapFunc :t v
 v :: Int - String
 Prelude FmapFunc v 1
 hello 1

   -- ryan

 On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:

 I'm not sure if my terminology is correct or even if my question makes sense, 
 but I can create instances of Maybe, List, IO, and Either.

 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

 All these instances are functors, each with its own version of fmap that can 
 be applied to it.

 How can I similarly create an instance of (-) so I can apply (-)'s version 
 of fmap

 instance Functor ((-) r) where
     fmap f g = (\x - f (g x))

 to it?

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 1:50 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  So it's a type constructor, not a type? Could you please provide a simple 
  example of its usage?

 Sure, although I'm sure you've come by some already.

 -- the identity function
 id :: a - a
 -- often, we write it like this:
 -- id x = x
 -- but here we see the relationship between the ananymous function
 syntax and the function type:
 id = \x - x

 In fact, if you write in prefix form, it is quite familiar:
 f :: (-) Int Bool
 e = Either String Float

 Cheers,
 Thu

  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
 
  From: Vo Minh Thu not...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 1:17 PM
 
  2010/8/31 michael rice nowg...@yahoo.com
  
   Learn You a Haskell ...  says that (-) is a type just like Either. 
   Where can I find its type definition?
 
  You can't define it *in* Haskell as user code. It is a built-in infix
  type constructor (Either or Maybe are type constructors too, not just
  types). In fact, if you want to implement a simple, typed functional
  language, you'll find it is the only built-in type constructor you
  have to implement (as the implementor of the language).
 
  Also,
    Show a = a
  is a type too, but you won't find a definition for 'a' or for '='.
  All those things are defined by the language.
 
  Cheers,
  Thu
 


 ___
 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] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice nowg...@yahoo.com

 Hi Vo,

 Pardon, I grabbed the wrong lines.

 *Main :t (-) 3 abc

 interactive:1:1: parse error on input `-'

Try

*Main :t undefined :: (-) 3 abc

You can't write
  :t some type
You have to write
  :t some value

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: Ryan Ingram ryani.s...@gmail.com, haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 3:07 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  Hi, Ryan and all,
 
  Bingo! I guess my question was all right after all.
 
  I tried creating an instance earlier but
 
  *Main :t (-) Int Char
 
  interactive:1:1: parse error on input `-'

   :t Int
 does not make sense but
   :t undefined :: Int
 is ok, just like
    :t undefined :: (-) Int Int

  What got loaded with FmapFunc? I Hoogled it and got back nothing.
 
  Michael
 
  --- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:
 
  From: Ryan Ingram ryani.s...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 2:36 PM
 
  Prelude FmapFunc let s = show :: ((-) Int) String
  Prelude FmapFunc :t s
  s :: Int - String
  Prelude FmapFunc let v = fmap (hello  ++) s
  Prelude FmapFunc :t v
  v :: Int - String
  Prelude FmapFunc v 1
  hello 1
 
    -- ryan
 
  On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:
 
  I'm not sure if my terminology is correct or even if my question makes 
  sense, but I can create instances of Maybe, List, IO, and Either.
 
  Prelude Data.Either let m = Just 7
  Prelude Data.Either :t m
  m :: Maybe Integer
 
  Prelude Data.Either let l = 2:[]
  Prelude Data.Either :t l
  l :: [Integer]
 
  Prelude Data.Either let g = getLine
  Prelude Data.Either :t g
  g :: IO String
 
  Prelude Data.Either let e = Right abc
  Prelude Data.Either :t e
  e :: Either a [Char]
 
  All these instances are functors, each with its own version of fmap that 
  can be applied to it.
 
  How can I similarly create an instance of (-) so I can apply (-)'s 
  version of fmap
 
  instance Functor ((-) r) where
      fmap f g = (\x - f (g x))
 
  to it?
 
  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
 
  From: Vo Minh Thu not...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 1:50 PM
 
  2010/8/31 michael rice nowg...@yahoo.com
  
   So it's a type constructor, not a type? Could you please provide a simple 
   example of its usage?
 
  Sure, although I'm sure you've come by some already.
 
  -- the identity function
  id :: a - a
  -- often, we write it like this:
  -- id x = x
  -- but here we see the relationship between the ananymous function
  syntax and the function type:
  id = \x - x
 
  In fact, if you write in prefix form, it is quite familiar:
  f :: (-) Int Bool
  e = Either String Float
 
  Cheers,
  Thu
 
   Michael
  
   --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
  
   From: Vo Minh Thu not...@gmail.com
   Subject: Re: [Haskell-cafe] On to applicative
   To: michael rice nowg...@yahoo.com
   Cc: haskell-cafe@haskell.org
   Date: Tuesday, August 31, 2010, 1:17 PM
  
   2010/8/31 michael rice nowg...@yahoo.com
   
Learn You a Haskell ...  says that (-) is a type just like Either. 
Where can I find its type definition?
  
   You can't define it *in* Haskell as user code. It is a built-in infix
   type constructor (Either or Maybe are type constructors too, not just
   types). In fact, if you want to implement a simple, typed functional
   language, you'll find it is the only built-in type constructor you
   have to implement (as the implementor of the language).
  
   Also,
     Show a = a
   is a type too, but you won't find a definition for 'a' or for '='.
   All those things are defined by the language.
  
   Cheers,
   Thu
  
 
 
  ___
  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] On to applicative

2010-08-31 Thread Alexander Solla


On Aug 31, 2010, at 12:03 PM, michael rice wrote:


I tried creating an instance earlier but

*Main :t (-) Int Char

interactive:1:1: parse error on input `-'


Try:

Prelude :info (-)
data (-) a b-- Defined in GHC.Prim

If you want type-information about values, use :t.  If you want  
information about types (and the type-level language), use :info.  
This includes stuff like class definitions and instances in scope.   
For example, if I include Control.Monad:


Prelude Control.Monad.Instances :info (-)
data (-) a b-- Defined in GHC.Prim
instance Monad ((-) r) -- Defined in Control.Monad.Instances
instance Functor ((-) r) -- Defined in Control.Monad.Instances

:info is pretty cool:

Prelude Control.Monad.Instances :info Monad
class Monad m where
  (=) :: m a - (a - m b) - m b
  () :: m a - m b - m b
  return :: a - m a
  fail :: String - m a
-- Defined in GHC.Base
instance Monad ((-) r) -- Defined in Control.Monad.Instances
instance Monad Maybe -- Defined in Data.Maybe
instance Monad [] -- Defined in GHC.Base
instance Monad IO -- Defined in GHC.Base

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


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
You most certainly meant

Prelude Data.Either :t undefined :: (-) Int String
undefined :: (-) Int String :: Int - String

though it is confusing. Constructors usually take values, but here the values 
(-) takes are types.

Michael


--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: Ryan Ingram ryani.s...@gmail.com, haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 3:23 PM

2010/8/31 michael rice nowg...@yahoo.com

 Hi Vo,

 Pardon, I grabbed the wrong lines.

 *Main :t (-) 3 abc

 interactive:1:1: parse error on input `-'

Try

*Main :t undefined :: (-) 3 abc

You can't write
  :t some type
You have to write
  :t some value

 Michael

 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: Ryan Ingram ryani.s...@gmail.com, haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 3:07 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  Hi, Ryan and all,
 
  Bingo! I guess my question was all right after all.
 
  I tried creating an instance earlier but
 
  *Main :t (-) Int Char
 
  interactive:1:1: parse error on input `-'

   :t Int
 does not make sense but
   :t undefined :: Int
 is ok, just like
    :t undefined :: (-) Int Int

  What got loaded with FmapFunc? I Hoogled it and got back nothing.
 
  Michael
 
  --- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:
 
  From: Ryan Ingram ryani.s...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 2:36 PM
 
  Prelude FmapFunc let s = show :: ((-) Int) String
  Prelude FmapFunc :t s
  s :: Int - String
  Prelude FmapFunc let v = fmap (hello  ++) s
  Prelude FmapFunc :t v
  v :: Int - String
  Prelude FmapFunc v 1
  hello 1
 
    -- ryan
 
  On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:
 
  I'm not sure if my terminology is correct or even if my question makes 
  sense, but I can create instances of Maybe, List, IO, and Either.
 
  Prelude Data.Either let m = Just 7
  Prelude Data.Either :t m
  m :: Maybe Integer
 
  Prelude Data.Either let l = 2:[]
  Prelude Data.Either :t l
  l :: [Integer]
 
  Prelude Data.Either let g = getLine
  Prelude Data.Either :t g
  g :: IO String
 
  Prelude Data.Either let e = Right abc
  Prelude Data.Either :t e
  e :: Either a [Char]
 
  All these instances are functors, each with its own version of fmap that 
  can be applied to it.
 
  How can I similarly create an instance of (-) so I can apply (-)'s 
  version of fmap
 
  instance Functor ((-) r) where
      fmap f g = (\x - f (g x))
 
  to it?
 
  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
 
  From: Vo Minh Thu not...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 1:50 PM
 
  2010/8/31 michael rice nowg...@yahoo.com
  
   So it's a type constructor, not a type? Could you please provide a simple 
   example of its usage?
 
  Sure, although I'm sure you've come by some already.
 
  -- the identity function
  id :: a - a
  -- often, we write it like this:
  -- id x = x
  -- but here we see the relationship between the ananymous function
  syntax and the function type:
  id = \x - x
 
  In fact, if you write in prefix form, it is quite familiar:
  f :: (-) Int Bool
  e = Either String Float
 
  Cheers,
  Thu
 
   Michael
  
   --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
  
   From: Vo Minh Thu not...@gmail.com
   Subject: Re: [Haskell-cafe] On to applicative
   To: michael rice nowg...@yahoo.com
   Cc: haskell-cafe@haskell.org
   Date: Tuesday, August 31, 2010, 1:17 PM
  
   2010/8/31 michael rice nowg...@yahoo.com
   
Learn You a Haskell ...  says that (-) is a type just like Either. 
Where can I find its type definition?
  
   You can't define it *in* Haskell as user code. It is a built-in infix
   type constructor (Either or Maybe are type constructors too, not just
   types). In fact, if you want to implement a simple, typed functional
   language, you'll find it is the only built-in type constructor you
   have to implement (as the implementor of the language).
  
   Also,
     Show a = a
   is a type too, but you won't find a definition for 'a' or for '='.
   All those things are defined by the language.
  
   Cheers,
   Thu
  
 
 
  ___
  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] On to applicative

2010-08-31 Thread Vo Minh Thu
2010/8/31 michael rice nowg...@yahoo.com

 You most certainly meant

 Prelude Data.Either :t undefined :: (-) Int String
 undefined :: (-) Int String :: Int - String

 though it is confusing. Constructors usually take values, but here the values 
 (-) takes are types.

Either and (-) are *type* constructors.
Just is a (value) constructor.

This makes sense:

Just 7 is a value, so Just surely constructs a value. Nothing doesn't
take an argument but is called a constructor too.
Maybe Int is a type, so Maybe surely constructs a type.

 Michael


 --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:

 From: Vo Minh Thu not...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: Ryan Ingram ryani.s...@gmail.com, haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 3:23 PM

 2010/8/31 michael rice nowg...@yahoo.com
 
  Hi Vo,
 
  Pardon, I grabbed the wrong lines.
 
  *Main :t (-) 3 abc
 
  interactive:1:1: parse error on input `-'

 Try

 *Main :t undefined :: (-) 3 abc

 You can't write
   :t some type
 You have to write
   :t some value

  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
 
  From: Vo Minh Thu not...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: Ryan Ingram ryani.s...@gmail.com, haskell-cafe@haskell.org
  Date: Tuesday, August 31, 2010, 3:07 PM
 
  2010/8/31 michael rice nowg...@yahoo.com
  
   Hi, Ryan and all,
  
   Bingo! I guess my question was all right after all.
  
   I tried creating an instance earlier but
  
   *Main :t (-) Int Char
  
   interactive:1:1: parse error on input `-'
 
    :t Int
  does not make sense but
    :t undefined :: Int
  is ok, just like
     :t undefined :: (-) Int Int
 
   What got loaded with FmapFunc? I Hoogled it and got back nothing.
  
   Michael
  
   --- On Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com wrote:
  
   From: Ryan Ingram ryani.s...@gmail.com
   Subject: Re: [Haskell-cafe] On to applicative
   To: michael rice nowg...@yahoo.com
   Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
   Date: Tuesday, August 31, 2010, 2:36 PM
  
   Prelude FmapFunc let s = show :: ((-) Int) String
   Prelude FmapFunc :t s
   s :: Int - String
   Prelude FmapFunc let v = fmap (hello  ++) s
   Prelude FmapFunc :t v
   v :: Int - String
   Prelude FmapFunc v 1
   hello 1
  
     -- ryan
  
   On Tue, Aug 31, 2010 at 11:28 AM, michael rice nowg...@yahoo.com wrote:
  
   I'm not sure if my terminology is correct or even if my question makes 
   sense, but I can create instances of Maybe, List, IO, and Either.
  
   Prelude Data.Either let m = Just 7
   Prelude Data.Either :t m
   m :: Maybe Integer
  
   Prelude Data.Either let l = 2:[]
   Prelude Data.Either :t l
   l :: [Integer]
  
   Prelude Data.Either let g = getLine
   Prelude Data.Either :t g
   g :: IO String
  
   Prelude Data.Either let e = Right abc
   Prelude Data.Either :t e
   e :: Either a [Char]
  
   All these instances are functors, each with its own version of fmap that 
   can be applied to it.
  
   How can I similarly create an instance of (-) so I can apply (-)'s 
   version of fmap
  
   instance Functor ((-) r) where
       fmap f g = (\x - f (g x))
  
   to it?
  
   Michael
  
   --- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
  
   From: Vo Minh Thu not...@gmail.com
   Subject: Re: [Haskell-cafe] On to applicative
   To: michael rice nowg...@yahoo.com
   Cc: haskell-cafe@haskell.org
   Date: Tuesday, August 31, 2010, 1:50 PM
  
   2010/8/31 michael rice nowg...@yahoo.com
   
So it's a type constructor, not a type? Could you please provide a 
simple example of its usage?
  
   Sure, although I'm sure you've come by some already.
  
   -- the identity function
   id :: a - a
   -- often, we write it like this:
   -- id x = x
   -- but here we see the relationship between the ananymous function
   syntax and the function type:
   id = \x - x
  
   In fact, if you write in prefix form, it is quite familiar:
   f :: (-) Int Bool
   e = Either String Float
  
   Cheers,
   Thu
  
Michael
   
--- On Tue, 8/31/10, Vo Minh Thu not...@gmail.com wrote:
   
From: Vo Minh Thu not...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 1:17 PM
   
2010/8/31 michael rice nowg...@yahoo.com

 Learn You a Haskell ...  says that (-) is a type just like Either. 
 Where can I find its type definition?
   
You can't define it *in* Haskell as user code. It is a built-in infix
type constructor (Either or Maybe are type constructors too, not just
types). In fact, if you want to implement a simple, typed functional
language, you'll find it is the only built-in type constructor you
have to implement (as the implementor of the language).
   
Also,
  Show a = a
is a type too, but you won't

Re: [Haskell-cafe] On to applicative

2010-08-31 Thread Ryan Ingram
FmapFunc is just a test module I created with

instance Functor ((-) r) where ...

  -- ryan

On Tue, Aug 31, 2010 at 12:03 PM, michael rice nowg...@yahoo.com wrote:

 Hi, Ryan and all,

 Bingo! I guess my question was all right after all.

 I tried creating an instance earlier but

 *Main :t (-) Int Char

 interactive:1:1: parse error on input `-'

 What got loaded with FmapFunc? I Hoogled it and got back nothing.

 Michael

 --- On *Tue, 8/31/10, Ryan Ingram ryani.s...@gmail.com* wrote:


 From: Ryan Ingram ryani.s...@gmail.com

 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: Vo Minh Thu not...@gmail.com, haskell-cafe@haskell.org
 Date: Tuesday, August 31, 2010, 2:36 PM


 Prelude FmapFunc let s = show :: ((-) Int) String
 Prelude FmapFunc :t s
 s :: Int - String
 Prelude FmapFunc let v = fmap (hello  ++) s
 Prelude FmapFunc :t v
 v :: Int - String
 Prelude FmapFunc v 1
 hello 1

   -- ryan

 On Tue, Aug 31, 2010 at 11:28 AM, michael rice 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
  wrote:

 I'm not sure if my terminology is correct or even if my question makes
 sense, but I can create instances of Maybe, List, IO, and Either.

 Prelude Data.Either let m = Just 7
 Prelude Data.Either :t m
 m :: Maybe Integer

 Prelude Data.Either let l = 2:[]
 Prelude Data.Either :t l
 l :: [Integer]

 Prelude Data.Either let g = getLine
 Prelude Data.Either :t g
 g :: IO String

 Prelude Data.Either let e = Right abc
 Prelude Data.Either :t e
 e :: Either a [Char]

 All these instances are functors, each with its own version of fmap that
 can be applied to it.

 How can I similarly create an instance of (-) so I can apply (-)'s
 version of fmap

 instance Functor ((-) r) where
 fmap f g = (\x - f (g x))

 to it?


 Michael

 --- On *Tue, 8/31/10, Vo Minh Thu 
 not...@gmail.comhttp://mc/compose?to=not...@gmail.com
 * wrote:


 From: Vo Minh Thu not...@gmail.comhttp://mc/compose?to=not...@gmail.com
 
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
 Cc: haskell-cafe@haskell.orghttp://mc/compose?to=haskell-c...@haskell.org
 Date: Tuesday, August 31, 2010, 1:50 PM


 2010/8/31 michael rice 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
 
  So it's a type constructor, not a type? Could you please provide a simple
 example of its usage?

 Sure, although I'm sure you've come by some already.

 -- the identity function
 id :: a - a
 -- often, we write it like this:
 -- id x = x
 -- but here we see the relationship between the ananymous function
 syntax and the function type:
 id = \x - x

 In fact, if you write in prefix form, it is quite familiar:
 f :: (-) Int Bool
 e = Either String Float

 Cheers,
 Thu

  Michael
 
  --- On Tue, 8/31/10, Vo Minh Thu 
  not...@gmail.comhttp://mc/compose?to=not...@gmail.com
 wrote:
 
  From: Vo Minh Thu not...@gmail.comhttp://mc/compose?to=not...@gmail.com
 
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice 
  nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
  Cc: haskell-cafe@haskell.orghttp://mc/compose?to=haskell-c...@haskell.org
  Date: Tuesday, August 31, 2010, 1:17 PM
 
  2010/8/31 michael rice 
  nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
 
  
   Learn You a Haskell ...  says that (-) is a type just like Either.
 Where can I find its type definition?
 
  You can't define it *in* Haskell as user code. It is a built-in infix
  type constructor (Either or Maybe are type constructors too, not just
  types). In fact, if you want to implement a simple, typed functional
  language, you'll find it is the only built-in type constructor you
  have to implement (as the implementor of the language).
 
  Also,
Show a = a
  is a type too, but you won't find a definition for 'a' or for '='.
  All those things are defined by the language.
 
  Cheers,
  Thu
 



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org http://mc/compose?to=haskell-c...@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] On to applicative

2010-08-31 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/31/10 13:27 , michael rice wrote:
 So it's a type constructor, not a type? Could you please provide a simple
 example of its usage?

Assuming you don't mean the trivial use in defining functions, see
Control.Monad.Instances:

 instance Functor ((-) r) where
 fmap = (.)
 
 instance Monad ((-) r) where
 return = const
 f = k = \ r - k (f r) r

(The above is the primitive reader functor/monad, see Control.Monad.Reader
for more information.)

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx9Z4EACgkQIn7hlCsL25WgrwCgvFQlObavv1fNOaKDjB/qbk8t
8+IAoLUrenXFzZFfJoYYvSy00uPctnaE
=ljiY
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-31 Thread michael rice
Thanks, Brandon, but Ryan gave me what I was looking for.

Michael

--- On Tue, 8/31/10, Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

From: Brandon S Allbery KF8NH allb...@ece.cmu.edu
Subject: Re: [Haskell-cafe] On to applicative
To: haskell-cafe@haskell.org
Date: Tuesday, August 31, 2010, 4:35 PM

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/31/10 13:27 , michael rice wrote:
 So it's a type constructor, not a type? Could you please provide a simple
 example of its usage?

Assuming you don't mean the trivial use in defining functions, see
Control.Monad.Instances:

 instance Functor ((-) r) where
         fmap = (.)
 
 instance Monad ((-) r) where
         return = const
         f = k = \ r - k (f r) r

(The above is the primitive reader functor/monad, see Control.Monad.Reader
for more information.)

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx9Z4EACgkQIn7hlCsL25WgrwCgvFQlObavv1fNOaKDjB/qbk8t
8+IAoLUrenXFzZFfJoYYvSy00uPctnaE
=ljiY
-END PGP SIGNATURE-
___
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] On to applicative

2010-08-29 Thread Stephen Tetley
On 29 August 2010 02:06, Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:
 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1

 On 8/28/10 20:43 , michael rice wrote:

 Historical accident, to wit:  Haskell 98 minimally defined Either in the
 Prelude, so in practice we get the basic definitions (Either itself and its
 Functor and Monad instances) from the Prelude and other utility functions
 from Data.Either.



One might also say its a historical accident that Either isn't an
instance of Bifunctor - Equal rights for Lefts!, but that's another
story...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-29 Thread Ivan Lazar Miljenovic
On 29 August 2010 16:51, Stephen Tetley stephen.tet...@gmail.com wrote:
 One might also say its a historical accident that Either isn't an
 instance of Bifunctor - Equal rights for Lefts!, but that's another
 story...

One might also say that that's because there is no BiFunctor in the
report, standard library, etc.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-29 Thread Stephen Tetley
On 29 August 2010 07:58, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:

 One might also say that that's because there is no BiFunctor in the
 report, standard library, etc.

Yep - that's where the historical accident comes in.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-29 Thread michael rice
Looks like the fmap definition for the Either functor matches what's given in 
Learn You A Haskell ...

instance Functor (Either a) where  
   fmap f (Right x) = Right (f x)  
   fmap f (Left x) = Left x

but Hoogle couldn't find Control.Monad.Instances

How else can I look at the code?

Michael

[mich...@localhost ~]$ ghci
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude :m + Control.Monad.Instances
Prelude Control.Monad.Instances :m + Data.Either
Prelude Control.Monad.Instances Data.Either let l = Left 5
Prelude Control.Monad.Instances Data.Either fmap (*2) l
Left 5
Prelude Control.Monad.Instances Data.Either let r = Right five
Prelude Control.Monad.Instances Data.Either fmap length r
Right 4


--- On Sat, 8/28/10, Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

From: Brandon S Allbery KF8NH allb...@ece.cmu.edu
Subject: Re: [Haskell-cafe] On to applicative
To: haskell-cafe@haskell.org
Date: Saturday, August 28, 2010, 9:06 PM

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/28/10 20:43 , michael rice wrote:
 I'm looking at a discussion of Either (as functor) here:
 
 http://learnyouahaskell.com/making-our-own-types-and-typeclasses#the-functor-typeclass
 
 instance Functor (Either a) where  
     fmap f (Right x) = Right (f x)  
     fmap f (Left x) = Left x
 
 And this line in Data.Either
 
 Functor (Either a)
 
 but no fmap defined here.
 
 How come?

Historical accident, to wit:  Haskell 98 minimally defined Either in the
Prelude, so in practice we get the basic definitions (Either itself and its
Functor and Monad instances) from the Prelude and other utility functions
from Data.Either.

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx5sq4ACgkQIn7hlCsL25WA+QCeKUOuNN4kUpci9fH6BcFZ5WqG
bX8AoIBImpWLoxVz7kcwVIuHycYR/v5G
=EaIs
-END PGP SIGNATURE-
___
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] On to applicative

2010-08-29 Thread Ivan Lazar Miljenovic
On 30 August 2010 14:25, michael rice nowg...@yahoo.com wrote:

 Looks like the fmap definition for the Either functor matches what's given in 
 Learn You A Haskell ...

 instance Functor (Either a) where
    fmap f (Right x) = Right (f x)
    fmap f (Left x) = Left x

 but Hoogle couldn't find Control.Monad.Instances

 How else can I look at the code?

http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Control-Monad-Instances.html

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-29 Thread michael rice
Hi Ivan,

I already looked there and didn't find anything, but went back and noticed the 
Source Code at the top right of the page and found it there. Why are there 
two source codes, the one at the top and the ones down the right margin (all 
the same from what I can tell).

Michael

--- On Mon, 8/30/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org, Brandon S Allbery KF8NH allb...@ece.cmu.edu
Date: Monday, August 30, 2010, 12:36 AM

On 30 August 2010 14:25, michael rice nowg...@yahoo.com wrote:

 Looks like the fmap definition for the Either functor matches what's given in 
 Learn You A Haskell ...

 instance Functor (Either a) where
    fmap f (Right x) = Right (f x)
    fmap f (Left x) = Left x

 but Hoogle couldn't find Control.Monad.Instances

 How else can I look at the code?

http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Control-Monad-Instances.html

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



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


Re: [Haskell-cafe] On to applicative

2010-08-29 Thread Ivan Lazar Miljenovic
On 30 August 2010 14:50, michael rice nowg...@yahoo.com wrote:

 Hi Ivan,

 I already looked there and didn't find anything, but went back and noticed 
 the Source Code at the top right of the page and found it there. Why are 
 there two source codes, the one at the top and the ones down the right margin 
 (all the same from what I can tell).

The ones on the side are direct links to the sources for a particular
function/value/etc.; the top one just links to the file.

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] On to applicative

2010-08-28 Thread michael rice
I'm looking at a discussion of Either (as functor) here:

http://learnyouahaskell.com/making-our-own-types-and-typeclasses#the-functor-typeclass

instance Functor (Either a) where  
    fmap f (Right x) = Right (f x)  
    fmap f (Left x) = Left x



And this line in Data.Either

Functor (Either a)

but no fmap defined here.


How come?

Michael




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


Re: [Haskell-cafe] On to applicative

2010-08-28 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/28/10 20:43 , michael rice wrote:
 I'm looking at a discussion of Either (as functor) here:
 
 http://learnyouahaskell.com/making-our-own-types-and-typeclasses#the-functor-typeclass
 
 instance Functor (Either a) where  
 fmap f (Right x) = Right (f x)  
 fmap f (Left x) = Left x
 
 And this line in Data.Either
 
 Functor (Either a)
 
 but no fmap defined here.
 
 How come?

Historical accident, to wit:  Haskell 98 minimally defined Either in the
Prelude, so in practice we get the basic definitions (Either itself and its
Functor and Monad instances) from the Prelude and other utility functions
from Data.Either.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx5sq4ACgkQIn7hlCsL25WA+QCeKUOuNN4kUpci9fH6BcFZ5WqG
bX8AoIBImpWLoxVz7kcwVIuHycYR/v5G
=EaIs
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-28 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/28/10 22:15 , michael rice wrote:
 Prelude fmap (*2) l
 
 interactive:1:0:
 No instance for (Functor (Either Integer))
   arising from a use of `fmap' at interactive:1:0-10
 Possible fix:
   add an instance declaration for (Functor (Either Integer))
 In the expression: fmap (* 2) l
 In the definition of `it': it = fmap (* 2) l
 Prelude

Huh.  I understood it to be defined in the Prelude, but didn't check.

Looks like it's now in Control.Monad.Instances (a relatively new module).
Confusing

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx5yW0ACgkQIn7hlCsL25VpMACeJR2GVmy1XvOMLtze7s0z3jaZ
t5sAnirMJhfh4ZYdMzJBdPbdUs8s166L
=OXTs
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-28 Thread michael rice
Thanks, Brandon.

Michael

--- On Sat, 8/28/10, Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

From: Brandon S Allbery KF8NH allb...@ece.cmu.edu
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, August 28, 2010, 10:43 PM

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/28/10 22:15 , michael rice wrote:
 Prelude fmap (*2) l
 
 interactive:1:0:
     No instance for (Functor (Either Integer))
       arising from a use of `fmap' at interactive:1:0-10
     Possible fix:
       add an instance declaration for (Functor (Either Integer))
     In the expression: fmap (* 2) l
     In the definition of `it': it = fmap (* 2) l
 Prelude

Huh.  I understood it to be defined in the Prelude, but didn't check.

Looks like it's now in Control.Monad.Instances (a relatively new module).
Confusing

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx5yW0ACgkQIn7hlCsL25VpMACeJR2GVmy1XvOMLtze7s0z3jaZ
t5sAnirMJhfh4ZYdMzJBdPbdUs8s166L
=OXTs
-END PGP SIGNATURE-



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


[Haskell-cafe] On to applicative

2010-08-27 Thread michael rice
fmap seems oddly named because no mapping takes place, except in the fourth 
example, where the map is passed in. Just sayin'.

Michael

1)
Prelude Control.Monad Control.Applicative fmap (++ abc) getLine
xyz
xyzabc

2)
Prelude Control.Monad Control.Applicative Data.Char Data.String fmap (splitAt 
3) getLine
qwertyuio
(qwe,rtyuio)

3)
Prelude Control.Monad Control.Applicative Data.Char fmap toUpper getLine

interactive:1:13:
    Couldn't match expected type `Char' against inferred type `[Char]'
  Expected type: IO Char
  Inferred type: IO String
    In the second argument of `fmap', namely `getLine'
    In the expression: fmap toUpper getLine

4)
Prelude Control.Monad Control.Applicative Data.Char Data.String fmap (map 
toUpper) getLine
qwertyuio
QWERTYUIO






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


Re: [Haskell-cafe] On to applicative

2010-08-27 Thread Ivan Lazar Miljenovic
On 28 August 2010 10:38, michael rice nowg...@yahoo.com wrote:

 fmap seems oddly named because no mapping takes place, except in the fourth 
 example, where the map is passed in. Just sayin'.

*ahem* http://en.wikipedia.org/wiki/Map_%28mathematics%29

 Prelude Control.Monad Control.Applicative Data.Char fmap toUpper getLine

 interactive:1:13:
     Couldn't match expected type `Char' against inferred type `[Char]'
   Expected type: IO Char
   Inferred type: IO String
     In the second argument of `fmap', namely `getLine'
     In the expression: fmap toUpper getLine

Right; this is because the fmap only gets the Char - Char function
inside the IO; but since it's IO String rather than IO Char, this
doesn't type-check.

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-27 Thread michael rice
A map can be a function (applied to a (single) value).

Got it.

Thanks,

Michael


--- On Fri, 8/27/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Friday, August 27, 2010, 8:46 PM

On 28 August 2010 10:38, michael rice nowg...@yahoo.com wrote:

 fmap seems oddly named because no mapping takes place, except in the fourth 
 example, where the map is passed in. Just sayin'.

*ahem* http://en.wikipedia.org/wiki/Map_%28mathematics%29

 Prelude Control.Monad Control.Applicative Data.Char fmap toUpper getLine

 interactive:1:13:
     Couldn't match expected type `Char' against inferred type `[Char]'
   Expected type: IO Char
   Inferred type: IO String
     In the second argument of `fmap', namely `getLine'
     In the expression: fmap toUpper getLine

Right; this is because the fmap only gets the Char - Char function
inside the IO; but since it's IO String rather than IO Char, this
doesn't type-check.

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



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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Ivan Lazar Miljenovic
On 26 August 2010 15:56, michael rice nowg...@yahoo.com wrote:

 From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors

 =
 import Control.Applicative

 f :: (a - b - c)
 fmap :: Functor f = (d - e) - f d - f e
 fmap f :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
 (b - c)

 sumsqr :: Int - Int - Int    -- my f
 sumsqr i j = i*i+j*j
 =

The line with the error is the one beginning with fmap f :: ...; you
can't provide a variable/parameter on the left hand side of the ::

Also, why are you trying to re-define fmap?

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Vo Minh Thu
2010/8/26 michael rice nowg...@yahoo.com

 From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors

 =
 import Control.Applicative

 f :: (a - b - c)
 fmap :: Functor f = (d - e) - f d - f e
 fmap f :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
 (b - c)

 sumsqr :: Int - Int - Int    -- my f
 sumsqr i j = i*i+j*j
 =

 I'm trying to understand how the above works but...

 [mich...@localhost ~]$ ghci
 GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Prelude :l bozo.hs
 [1 of 1] Compiling Main ( bozo.hs, interpreted )

 bozo.hs:5:0: Invalid type signature
 Failed, modules loaded: none.
 Prelude

Hi,

The fifth line has the form

  x y :: ...

instead of

  x :: ...

This is not a legal type signature.

Furthermore, you can't give fmap two signatures in the same source file.

The reason this is given on the page you linked is for demonstration
purpose (well, I guess, I haven't read it).

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
Yeah, I figured as much, but the code is copied right off the referenced page.

Michael


--- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 2:02 AM

On 26 August 2010 15:56, michael rice nowg...@yahoo.com wrote:

 From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors

 =
 import Control.Applicative

 f :: (a - b - c)
 fmap :: Functor f = (d - e) - f d - f e
 fmap f :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
 (b - c)

 sumsqr :: Int - Int - Int    -- my f
 sumsqr i j = i*i+j*j
 =

The line with the error is the one beginning with fmap f :: ...; you
can't provide a variable/parameter on the left hand side of the ::

Also, why are you trying to re-define fmap?

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



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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Ivan Lazar Miljenovic
On 26 August 2010 16:09, michael rice nowg...@yahoo.com wrote:

 Yeah, I figured as much, but the code is copied right off the referenced page.

Because as Vo Minh Thu says, it was there as a demonstration; in this
instance they were doing algebraic manipulation of the code and
corresponding type signatures.  Admittedly, the wording could have
been improved...

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
Can you recommend an example that works?

Michael

--- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 2:13 AM

On 26 August 2010 16:09, michael rice nowg...@yahoo.com wrote:

 Yeah, I figured as much, but the code is copied right off the referenced page.

Because as Vo Minh Thu says, it was there as a demonstration; in this
instance they were doing algebraic manipulation of the code and
corresponding type signatures.  Admittedly, the wording could have
been improved...

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



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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Ivan Lazar Miljenovic
On 26 August 2010 16:29, michael rice nowg...@yahoo.com wrote:

 Can you recommend an example that works?

An example of what?

The definitions of fmap2, etc. on that page look like they're correct.

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
OK, fmap2 works, but not fmap3. What am I not understanding?

Michael

import Control.Applicative

-- f :: (a - b - c)
-- fmap :: Functor f = (d - e) - f d - f e

sumsqr :: Int - Int - Int
sumsqr i j = i*i+j*j

-- fmap :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
(b - c)


fmap2 f a b = f `fmap` a * b
fmap3 f a b c = f `fmap` a * b * c
fmap4 f a b c d = f `fmap` a * b * c * d


-- fmap2 f a b = f $ a * b
-- fmap3 f a b c = f $ a * b * c
-- fmap4 f a b c d = f $ a * b * c * d


*Main fmap2 sumsqr (Just 3) (Just 4)
Just 25
*Main fmap3 sumsqr (Just 3) (Just 4) (Just 5)

interactive:1:6:
    Couldn't match expected type `a2 - b' against inferred type `Int'
    In the first argument of `fmap3', namely `sumsqr'
    In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5)
    In the definition of `it':
    it = fmap3 sumsqr (Just 3) (Just 4) (Just 5)
*Main 


--- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 2:33 AM

On 26 August 2010 16:29, michael rice nowg...@yahoo.com wrote:

 Can you recommend an example that works?

An example of what?

The definitions of fmap2, etc. on that page look like they're correct.

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



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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Ivan Lazar Miljenovic
On 26 August 2010 16:47, michael rice nowg...@yahoo.com wrote:

 OK, fmap2 works, but not fmap3. What am I not understanding?

 Michael

 import Control.Applicative

 -- f :: (a - b - c)
 -- fmap :: Functor f = (d - e) - f d - f e

 sumsqr :: Int - Int - Int
 sumsqr i j = i*i+j*j

 -- fmap :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
 (b - c)


 fmap2 f a b = f `fmap` a * b
 fmap3 f a b c = f `fmap` a * b * c
 fmap4 f a b c d = f `fmap` a * b * c * d


 -- fmap2 f a b = f $ a * b
 -- fmap3 f a b c = f $ a * b * c
 -- fmap4 f a b c d = f $ a * b * c * d


 *Main fmap2 sumsqr (Just 3) (Just 4)
 Just 25
 *Main fmap3 sumsqr (Just 3) (Just 4) (Just 5)

 interactive:1:6:
     Couldn't match expected type `a2 - b' against inferred type `Int'
     In the first argument of `fmap3', namely `sumsqr'
     In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5)
     In the definition of `it':
     it = fmap3 sumsqr (Just 3) (Just 4) (Just 5)
 *Main

sumsqr takes three arguments; fmap3 has type:

fmap3 :: (a - b - c - d) - Maybe a - Maybe b - Maybe c - Maybe d

i.e. the function you pass it needs to take 3 arguments.

fmap3 (\ x y z - z * y + z) (Just 1) (Just 2) (Just 3)



 --- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Thursday, August 26, 2010, 2:33 AM

 On 26 August 2010 16:29, michael rice nowg...@yahoo.com wrote:
 
  Can you recommend an example that works?

 An example of what?

 The definitions of fmap2, etc. on that page look like they're correct.

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




--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Vo Minh Thu
I think it works well :)

But sumsqr has type Int - Int - Int, not Int - Int - Int - Int.

I.e. it does take only two arguments while fmap3 takes a function of
three arguments.

2010/8/26 michael rice nowg...@yahoo.com

 OK, fmap2 works, but not fmap3. What am I not understanding?

 Michael

 import Control.Applicative

 -- f :: (a - b - c)
 -- fmap :: Functor f = (d - e) - f d - f e

 sumsqr :: Int - Int - Int
 sumsqr i j = i*i+j*j

 -- fmap :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
 (b - c)


 fmap2 f a b = f `fmap` a * b
 fmap3 f a b c = f `fmap` a * b * c
 fmap4 f a b c d = f `fmap` a * b * c * d


 -- fmap2 f a b = f $ a * b
 -- fmap3 f a b c = f $ a * b * c
 -- fmap4 f a b c d = f $ a * b * c * d


 *Main fmap2 sumsqr (Just 3) (Just 4)
 Just 25
 *Main fmap3 sumsqr (Just 3) (Just 4) (Just 5)

 interactive:1:6:
     Couldn't match expected type `a2 - b' against inferred type `Int'
     In the first argument of `fmap3', namely `sumsqr'
     In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5)
     In the definition of `it':
     it = fmap3 sumsqr (Just 3) (Just 4) (Just 5)
 *Main


 --- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Thursday, August 26, 2010, 2:33 AM

 On 26 August 2010 16:29, michael rice nowg...@yahoo.com wrote:
 
  Can you recommend an example that works?

 An example of what?

 The definitions of fmap2, etc. on that page look like they're correct.

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


 ___
 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] On to applicative

2010-08-26 Thread michael rice
Hmm... it was my understanding that the example was showing how to *avoid* 
having to create a  lot of functions that do the same thing but have different 
numbers of arguments.

From the Wiki page:

Anytime you feel the need to define different higher order functions to 
accommodate for function-arguments with a different number of arguments,
 think about how defining a proper instance of Applicative can make your life 
easier.

Not so?

Michael



--- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 2:50 AM

On 26 August 2010 16:47, michael rice nowg...@yahoo.com wrote:

 OK, fmap2 works, but not fmap3. What am I not understanding?

 Michael

 import Control.Applicative

 -- f :: (a - b - c)
 -- fmap :: Functor f = (d - e) - f d - f e

 sumsqr :: Int - Int - Int
 sumsqr i j = i*i+j*j

 -- fmap :: Functor f = f a - f (b - c)    -- Identify d with a, and e with 
 (b - c)


 fmap2 f a b = f `fmap` a * b
 fmap3 f a b c = f `fmap` a * b * c
 fmap4 f a b c d = f `fmap` a * b * c * d


 -- fmap2 f a b = f $ a * b
 -- fmap3 f a b c = f $ a * b * c
 -- fmap4 f a b c d = f $ a * b * c * d


 *Main fmap2 sumsqr (Just 3) (Just 4)
 Just 25
 *Main fmap3 sumsqr (Just 3) (Just 4) (Just 5)

 interactive:1:6:
     Couldn't match expected type `a2 - b' against inferred type `Int'
     In the first argument of `fmap3', namely `sumsqr'
     In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5)
     In the definition of `it':
     it = fmap3 sumsqr (Just 3) (Just 4) (Just 5)
 *Main

sumsqr takes three arguments; fmap3 has type:

fmap3 :: (a - b - c - d) - Maybe a - Maybe b - Maybe c - Maybe d

i.e. the function you pass it needs to take 3 arguments.

fmap3 (\ x y z - z * y + z) (Just 1) (Just 2) (Just 3)



 --- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Thursday, August 26, 2010, 2:33 AM

 On 26 August 2010 16:29, michael rice nowg...@yahoo.com wrote:
 
  Can you recommend an example that works?

 An example of what?

 The definitions of fmap2, etc. on that page look like they're correct.

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




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



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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Vo Minh Thu
This is indeed the case: if you want to apply your sumsqr function or
Ivan's (\ x y z - z * y + z), to some Functor (Maybe in this case),
you don't have to redefine them, or even to use fmap2 or fmap3: you
just have to use $ and *.

E.g.:

(\ a b c - a + b + c) $ Just 1 * Just 2 * Just 3

2010/8/26 michael rice nowg...@yahoo.com

 Hmm... it was my understanding that the example was showing how to *avoid* 
 having to create a  lot of functions that do the same thing but have 
 different numbers of arguments.

 From the Wiki page:

 Anytime you feel the need to define different higher order functions to 
 accommodate for function-arguments with a different number of arguments, 
 think about how defining a proper instance of Applicative can make your life 
 easier.

 Not so?

 Michael



 --- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
 Subject: Re: [Haskell-cafe] On to applicative
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Thursday, August 26, 2010, 2:50 AM

 On 26 August 2010 16:47, michael rice nowg...@yahoo.com wrote:
 
  OK, fmap2 works, but not fmap3. What am I not understanding?
 
  Michael
 
  import Control.Applicative
 
  -- f :: (a - b - c)
  -- fmap :: Functor f = (d - e) - f d - f e
 
  sumsqr :: Int - Int - Int
  sumsqr i j = i*i+j*j
 
  -- fmap :: Functor f = f a - f (b - c)    -- Identify d with a, and e 
  with (b - c)
 
 
  fmap2 f a b = f `fmap` a * b
  fmap3 f a b c = f `fmap` a * b * c
  fmap4 f a b c d = f `fmap` a * b * c * d
 
 
  -- fmap2 f a b = f $ a * b
  -- fmap3 f a b c = f $ a * b * c
  -- fmap4 f a b c d = f $ a * b * c * d
 
 
  *Main fmap2 sumsqr (Just 3) (Just 4)
  Just 25
  *Main fmap3 sumsqr (Just 3) (Just 4) (Just 5)
 
  interactive:1:6:
      Couldn't match expected type `a2 - b' against inferred type `Int'
      In the first argument of `fmap3', namely `sumsqr'
      In the expression: fmap3 sumsqr (Just 3) (Just 4) (Just 5)
      In the definition of `it':
      it = fmap3 sumsqr (Just 3) (Just 4) (Just 5)
  *Main

 sumsqr takes three arguments; fmap3 has type:

 fmap3 :: (a - b - c - d) - Maybe a - Maybe b - Maybe c - Maybe d

 i.e. the function you pass it needs to take 3 arguments.

 fmap3 (\ x y z - z * y + z) (Just 1) (Just 2) (Just 3)

 
 
  --- On Thu, 8/26/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com 
  wrote:
 
  From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
  Subject: Re: [Haskell-cafe] On to applicative
  To: michael rice nowg...@yahoo.com
  Cc: haskell-cafe@haskell.org
  Date: Thursday, August 26, 2010, 2:33 AM
 
  On 26 August 2010 16:29, michael rice nowg...@yahoo.com wrote:
  
   Can you recommend an example that works?
 
  An example of what?
 
  The definitions of fmap2, etc. on that page look like they're correct.
 
  --
  Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com
  IvanMiljenovic.wordpress.com
 



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


 ___
 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] On to applicative

2010-08-26 Thread Thomas Davie

On 26 Aug 2010, at 08:01, michael rice wrote:

 Hmm... it was my understanding that the example was showing how to *avoid* 
 having to create a  lot of functions that do the same thing but have 
 different numbers of arguments.
 
 From the Wiki page:
 
 Anytime you feel the need to define different higher order functions to 
 accommodate for function-arguments with a different number of arguments, 
 think about how defining a proper instance of Applicative can make your life 
 easier.
 
 Not so?
 
 
Very much so – instead of defining liftA2, liftA3 etc like this, just use pure 
to get things into the applicative, and write * instead of ' ' to apply 
applicatives and you're done.

Don't write
liftA3 sumsq (Just 3) (Just 4) (Just 5)

Write
(pure sumsq) * (pure 3) * (pure 4) * (pure 5)

or you can get rid of that first pure with a quick fmap:
sumsq $ (pure 3) * (pure 4) * (pure 5)

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
A lot of stuff to get one's head around. Was aware of liftM2, liftM3, etc., but 
not liftA2, liftA3, etc.

So, the statement was true, but not the way that was shown in the example, 
i.e., with fmap2, fmap3, etc., which required different functions for each of 
the fmaps.

Thanks. Appreciate the patience.

Michael

--- On Thu, 8/26/10, Thomas Davie tom.da...@gmail.com wrote:

From: Thomas Davie tom.da...@gmail.com
Subject: Re: [Haskell-cafe] On to applicative
To: michael rice nowg...@yahoo.com
Cc: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com, 
haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 3:10 AM


On 26 Aug 2010, at 08:01, michael rice wrote:
Hmm... it was my understanding that the example was showing how to *avoid* 
having to create a  lot of functions that do the same thing but have different 
numbers of arguments.

From the Wiki page:

Anytime you feel the need to define different higher order functions to 
accommodate for function-arguments with a different number of arguments,
 think about how defining a proper instance of Applicative can make your life 
easier.

Not so?


Very much so – instead of defining liftA2, liftA3 etc like this, just use pure 
to get things into the applicative, and write * instead of ' ' to apply 
applicatives and you're done.
Don't writeliftA3 sumsq (Just 3) (Just 4) (Just 5)
Write(pure sumsq) * (pure 3) * (pure 4) * (pure 5)
or you can get rid of that first pure with a quick fmap:sumsq $ (pure 3) * 
(pure 4) * (pure 5)
Bob


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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla


On Aug 26, 2010, at 12:34 AM, michael rice wrote:

A lot of stuff to get one's head around. Was aware of liftM2,  
liftM3, etc., but not liftA2, liftA3, etc.




liftM and liftA are essentially equivalent (and are both essentially  
equivalent to fmap)  Same for the liftAn = liftMn functions (where n  
is an integer).  Applicative functors are more general than monads, so  
it makes sense for them to have their own functions.  It is a matter  
of history that liftM was defined before liftA.


So, the statement was true, but not the way that was shown in the  
example, i.e., with fmap2, fmap3, etc., which required different  
functions for each of the fmaps.


Strictly speaking, fmap will work with a function in more than one  
argument, as long as it is properly typed.  This is what makes  
applicative functors work.


Consider that a function f :: a - b - c also has the type f :: a -  
(b - c).   If you feed it an a, (resulting in a value of the form f  
a), you get a function g :: (b - c).  In other words, every function  
is a function in one argument.  Some functions just happen to map to  
other functions.


$ is flip fmap.  f $ functor = fmap f functor

Consider what happens if f :: a - b.  (f $ functor) means pull an  
a out of the functor, apply f, and return a functor over some b.   
That is to say, lift f into the functor and apply it.


Now consider what happens if f :: a - (b - c).  By analogy, this  
means pull an a out of the functor object, apply f, and return a  
functor object (f g)  :: f (b - c)  (In other words, a functor  
object that contains a function g :: b - c).  In order to get a c  
value out of this, you need to apply g to something.  But note that  
we're not just dealing with g.  It is in the functor already, and so  
doesn't need lifting.  So some smart guy wrote a function called


* :: (Functor f) = f (b - c) - f b - f c

that does just that.  This is one of the defining functions for an  
applicative functor.  (And part of the reason for the name.  If the  
functor contains a function, you can apply the functor to properly  
typed functor objects.)


The other function is pure :: (a - b) - f (a - b).  It takes a  
function and lifts it into the functor, without applying it to  
anything.  In other words, given an f :: a - b,


pure f * functor = f $ functor

If f has a bigger type (say, a - b - c - d), you can do things like:

f $ functor_on_a * functor_on_b * functor_on_c

Every monad is an applicative functor.  If we have a monad action  
m_f :: m (a - b), and another one m_a :: (m a), we can get a monad  
action in type (m b) by pulling the function f :: a - b out of the  
first one and applying it to the b in the second one:


m_f = (\f - liftM f m_a)

or... m_f = (flip liftM) m_a

In fact, there is a function called ap :: m (a - b) - m a - m b  
which does just that, and is essentially equivalent to *.  Of  
course, running return on a function f is equivalent to running pure  
on f.

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Alexander Solla


On Aug 26, 2010, at 1:29 AM, Alexander Solla wrote:

The other function is pure :: (a - b) - f (a - b).  It takes a  
function and lifts it into the functor, without applying it to  
anything.  In other words, given an f :: a - b,


My mistake, though if you got the rest of it, it should come as no  
surprise that pure :: a - f a and is essentially equivalent to a  
monad's return.

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread Brent Yorgey
On Thu, Aug 26, 2010 at 01:29:16AM -0700, Alexander Solla wrote:
 
 
 $ is flip fmap.  f $ functor = fmap f functor
 

Just a quick correction: $ is fmap, not flip fmap.

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
Hi Alexander,

Didn't get to sleep till 4 AM and it took me a while to go though your post.

So far...

--- On Thu, 8/26/10, Alexander Solla a...@2piix.com wrote:

From: Alexander Solla a...@2piix.com
Subject: Re: [Haskell-cafe] On to applicative
To: 
Cc: haskell-cafe Cafe haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 4:29 AM


On Aug 26, 2010, at 12:34 AM, michael rice wrote:

 A lot of stuff to get one's head around. Was aware of liftM2, liftM3, etc., 
 but not liftA2, liftA3, etc.
 

liftM and liftA are essentially equivalent (and are both essentially equivalent 
to fmap)  Same for the liftAn = liftMn functions (where n is an integer).  
Applicative functors are more general than monads, so it makes sense for them 
to have their own functions.  It is a matter of history that liftM was defined 
before liftA.

 So, the statement was true, but not the way that was shown in the example, 
 i.e., with fmap2, fmap3, etc., which required different functions for each of 
 the fmaps.

Strictly speaking, fmap will work with a function in more than one argument, as 
long as it is properly typed.  This is what makes applicative functors work.

Consider that a function f :: a - b - c also has the type f :: a - (b - 
c).   If you feed it an a, (resulting in a value of the form f a), you get a 
function g :: (b - c).  In other words, every function is a function in one 
argument.  

### Knew that fact, but it needed to be dusted off.

Some functions just happen to map to other functions.

$ is flip fmap.  f $ functor = fmap f functor   Brent Yorgey's post 
noted.

 map to? Take as arguments?

Consider what happens if f :: a - b.  (f $ functor) means pull an a out of 
the functor, apply f, and return a functor over some b.  That is to say, 
lift f into the functor and apply it.

 OK.

 Prelude Control.Applicative let double x = x+x
 Prelude Control.Applicative (double $ (Just 7))
 Just 14


Now consider what happens if f :: a - (b - c).  By analogy, this means pull 
an a out of the functor object, apply f, and return a functor object (f g)  :: 
f (b - c)  (In other words, a functor object that contains a function g :: 
b - c).  In order to get a c value out of this, you need to apply g to 
something.  But note that we're not just dealing with g.  It is in the 
functor already, and so doesn't need lifting.  So some smart guy wrote a 
function called

* :: (Functor f) = f (b - c) - f b - f c

 Prelude Control.Applicative let plus x y = x+y
 Prelude Control.Applicative let f = (plus $ (Just 3))
 Prelude Control.Applicative f (Just 4)

 interactive:1:0:
     Couldn't match expected type `Maybe t1 - t'
    against inferred type `Maybe (Integer - Integer)'
     In the expression: f (Just 4)
     In the definition of `it': it = f (Just 4)
 Prelude Control.Applicative f * (Just 4)
 Just 7

 OK. Partial evaluation with functors?


that does just that.  This is one of the defining functions for an applicative 
functor.  (And part of the reason for the name.  If the functor contains a 
function, you can apply the functor to properly typed functor objects.)

The other function is pure :: (a - b) - f (a - b).  It takes a function and 
lifts it into the functor, without applying it to anything.  In other words, 
given an f :: a - b,

pure f * functor = f $ functor

 Prelude Control.Applicative pure double * (Just 5)
 Just 10

 Not so, the f got applied or where did we get the 10? Not sure, is this 
the  mistake you point out in your second post?

 Two ways of doing the same thing?

 1)
 Prelude Control.Applicative (double $ (Just 7))
 Just 14

 2)
 Prelude Control.Applicative pure double * (Just 7)
 Just 14


 Still looking at rest of your post.

If f has a bigger type (say, a - b - c - d), you can do things like:

f $ functor_on_a * functor_on_b * functor_on_c

Every monad is an applicative functor.  If we have a monad action m_f :: m (a 
- b), and another one m_a :: (m a), we can get a monad action in type (m b) by 
pulling the function f :: a - b out of the first one and applying it to the b 
in the second one:

m_f = (\f - liftM f m_a)

or... m_f = (flip liftM) m_a

In fact, there is a function called ap :: m (a - b) - m a - m b which does 
just that, and is essentially equivalent to *.  Of course, running return 
on a function f is equivalent to running pure on f.
___
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] On to applicative

2010-08-26 Thread Alexander Solla


On Aug 26, 2010, at 9:27 AM, michael rice wrote:

Some functions just happen to map to other functions.

$ is flip fmap.  f $ functor = fmap f functor   Brent  
Yorgey's post noted.


 map to? Take as arguments?


maps to as in outputs.


pure f * functor = f $ functor

 Prelude Control.Applicative pure double * (Just 5)
 Just 10

 Not so, the f got applied or where did we get the 10? Not sure,  
is this the  mistake you point out in your second post?



double is getting applied in that expression, but it isn't because of  
pure.  The * operator is pulling double out of pure double (which  
equals Just double in this case), and applying it to Just 5.


My correction was to point out that pure's type is more general than I  
had said.   Instead of
pure :: (a - b) - f (a - b), it is pure :: a - f a -- which  
includes (a - b) - f (a - b) as a special case.  In fact, pure and  
return are essentially equivalent in form.  So you could write out  
your verification case as


(pure double * pure 5) :: Just Int

to further decouple your code from the particular functor you're  
working with.  (You need the type annotation to run it in GHCi)




 Two ways of doing the same thing?

 1)
 Prelude Control.Applicative (double $ (Just 7))
 Just 14

 2)
 Prelude Control.Applicative pure double * (Just 7)
 Just 14


Indeed. 
 
___

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


Re: [Haskell-cafe] On to applicative

2010-08-26 Thread michael rice
When I began looking into applicative, I googled haskell applicative and 
grabbed the first one on the list, the wikipage. I think a better choice would 
have been the Learn You a Haskell section on functors/applicative, the second 
one on the list. I'm going to spend some time there but will no doubt be back 
before long with another question.

Thanks all,

Michael

--- On Thu, 8/26/10, Alexander Solla a...@2piix.com wrote:

From: Alexander Solla a...@2piix.com
Subject: Re: [Haskell-cafe] On to applicative
To: 
Cc: haskell-cafe Cafe haskell-cafe@haskell.org
Date: Thursday, August 26, 2010, 2:15 PM


On Aug 26, 2010, at 9:27 AM, michael rice wrote:
 Some functions just happen to map to other functions.
 
 $ is flip fmap.  f $ functor = fmap f functor   Brent Yorgey's post 
 noted.
 
  map to? Take as arguments?

maps to as in outputs.

 pure f * functor = f $ functor
 
  Prelude Control.Applicative pure double * (Just 5)
  Just 10
 
  Not so, the f got applied or where did we get the 10? Not sure, is this 
 the  mistake you point out in your second post?


double is getting applied in that expression, but it isn't because of pure.  
The * operator is pulling double out of pure double (which equals Just double 
in this case), and applying it to Just 5.

My correction was to point out that pure's type is more general than I had 
said.   Instead of
pure :: (a - b) - f (a - b), it is pure :: a - f a -- which includes (a - 
b) - f (a - b) as a special case.  In fact, pure and return are essentially 
equivalent in form.  So you could write out your verification case as

(pure double * pure 5) :: Just Int

to further decouple your code from the particular functor you're working with.  
(You need the type annotation to run it in GHCi)

 
  Two ways of doing the same thing?
 
  1)
  Prelude Control.Applicative (double $ (Just 7))
  Just 14
 
  2)
  Prelude Control.Applicative pure double * (Just 7)
  Just 14

Indeed.___
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] On to applicative

2010-08-25 Thread michael rice
From: http://en.wikibooks.org/wiki/Haskell/Applicative_Functors

=
import Control.Applicative

f :: (a - b - c)
fmap :: Functor f = (d - e) - f d - f e
fmap f :: Functor f = f a - f (b - c)    -- Identify d with a, and e with (b 
- c)

sumsqr :: Int - Int - Int    -- my f
sumsqr i j = i*i+j*j
=

I'm trying to understand how the above works but... 

[mich...@localhost ~]$ ghci
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude :l bozo.hs
[1 of 1] Compiling Main ( bozo.hs, interpreted )

bozo.hs:5:0: Invalid type signature
Failed, modules loaded: none.
Prelude 


Michael




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


Re: [Haskell-cafe] ** for nested applicative functors?

2009-10-13 Thread Conal Elliott
Hi Kim-Ee,

This pattern shows up in Applicative programming with effects in showing
that the composition of applicatives is applicative: (*) = liftA2 (*),
and pure = pure.pure .  (Really, you have to manage newtype wrappers as
well.  See the TypeCompose library.)

   - Conal

On Mon, Oct 12, 2009 at 9:52 AM, Kim-Ee Yeoh a.biurvo...@asuhan.com wrote:


 That's it: liftA2 (*), so obvious in hindsight.

 Mustn't ... code ... when ... drained 

 Thanks to Jeremy and Josef.


 Jeremy Shaw-3 wrote:
 
  This looks like what is described in Section 4 to me:
 
 
 http://www.haskell.org/haskellwiki/Applicative_functor#Applicative_transfomers
 
  - jeremy
 
  On Oct 12, 2009, at 11:22 AM, Kim-Ee Yeoh wrote:
 
  ** :: (Applicative m, Applicative n) =
  m (n (a-b)) - m (n a) - m (n b)
 

 --
 View this message in context:
 http://www.nabble.com/%3C**%3E-for-nested-applicative-functors--tp25858792p25859274.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

 ___
 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] ** for nested applicative functors?

2009-10-12 Thread Kim-Ee Yeoh

Does anyone know if it's possible to write the following:

** :: (Applicative m, Applicative n) =
m (n (a-b)) - m (n a) - m (n b)

Clearly, if m and n were monads, it would be trivial.

Rereading the original paper, I didn't see much discussion
about such nested app. functors. 

Any help appreciated.

-- 
View this message in context: 
http://www.nabble.com/%3C**%3E-for-nested-applicative-functors--tp25858792p25858792.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] ** for nested applicative functors?

2009-10-12 Thread Josef Svenningsson
On Mon, Oct 12, 2009 at 6:22 PM, Kim-Ee Yeoh a.biurvo...@asuhan.com wrote:

 Does anyone know if it's possible to write the following:

 ** :: (Applicative m, Applicative n) =
 m (n (a-b)) - m (n a) - m (n b)

 Clearly, if m and n were monads, it would be trivial.

 Rereading the original paper, I didn't see much discussion
 about such nested app. functors.

 Any help appreciated.

How about

m ** n = pure (*) * m * n

Hth,

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


Re: [Haskell-cafe] ** for nested applicative functors?

2009-10-12 Thread Jeremy Shaw

This looks like what is described in Section 4 to me:

http://www.haskell.org/haskellwiki/Applicative_functor#Applicative_transfomers

- jeremy

On Oct 12, 2009, at 11:22 AM, Kim-Ee Yeoh wrote:


** :: (Applicative m, Applicative n) =
m (n (a-b)) - m (n a) - m (n b)


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


Re: [Haskell-cafe] ** for nested applicative functors?

2009-10-12 Thread Kim-Ee Yeoh

That's it: liftA2 (*), so obvious in hindsight.

Mustn't ... code ... when ... drained 

Thanks to Jeremy and Josef.


Jeremy Shaw-3 wrote:
 
 This looks like what is described in Section 4 to me:
 
 http://www.haskell.org/haskellwiki/Applicative_functor#Applicative_transfomers
 
 - jeremy
 
 On Oct 12, 2009, at 11:22 AM, Kim-Ee Yeoh wrote:
 
 ** :: (Applicative m, Applicative n) =
 m (n (a-b)) - m (n a) - m (n b)
 

-- 
View this message in context: 
http://www.nabble.com/%3C**%3E-for-nested-applicative-functors--tp25858792p25859274.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


  1   2   >