[Haskell-cafe] Haskell-Cafe Digest, Vol 120, Issue 35

althainz althainz at gmail.com
Fri Aug 23 22:56:22 CEST 2013




Von Samsung Mobile gesendet

-------- Ursprüngliche Nachricht --------
Von: haskell-cafe-request at haskell.org 
Datum: 23.08.2013  11:36  (GMT+01:00) 
An: haskell-cafe at haskell.org 
Betreff: Haskell-Cafe Digest, Vol 120, Issue 35 
 
Send Haskell-Cafe mailing list submissions to
haskell-cafe at haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/haskell-cafe
or, via email, send a message with subject or body 'help' to
haskell-cafe-request at haskell.org

You can reach the person managing the list at
haskell-cafe-owner at haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Haskell-Cafe digest..."


Today's Topics:

   1. Re: Yet Another Forkable Class (John ExFalso)
   2. Re: Yet Another Forkable Class (suhorng Y)
   3. Lifting strictness to types (Thiago Negri)
   4. Re: Lifting strictness to types (Tom Ellis)
   5. Re: Lifting strictness to types (Thiago Negri)
   6. instance Alternative ZipList (Stefan Mehner)
   7. Re: Lifting strictness to types (Bardur Arantsson)
   8. Hoogle vs Hayoo (jabolopes at google.com)
   9. Re: Hoogle vs Hayoo (Mateusz Kowalczyk)
  10. Re: monoids induced by
      Applicative/Alternative/Monad/MonadPlus? (Petr Pudl?k)
  11. Re: Hoogle vs Hayoo (Johannes Waldmann)
  12. Re: Yet Another Forkable Class (oleg at okmij.org)
  13. Re: Hoogle vs Hayoo (Erik Hesselink)
  14. Conduit : is it possible to write this function?
      (Erik de Castro Lopo)
  15. Re: Hoogle vs Hayoo (Daniel Trstenjak)
  16. Re: Conduit : is it possible to write this function?
      (Michael Snoyman)
  17. typeclass constraints (TP)
  18. Re: typeclass constraints (Adam Gundry)


----------------------------------------------------------------------

Message: 1
Date: Thu, 22 Aug 2013 15:50:23 +0100
From: John ExFalso <0slemi0 at gmail.com>
To: "Alberto G. Corona" <agocorona at gmail.com>
Cc: "oleg at okmij.org" <oleg at okmij.org>, haskell-cafe
<Haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Yet Another Forkable Class
Message-ID:
<CAJEmqMj8Y7KoNVPS7x6zvvtkAmYheax9oigTPLLHDchfHde_pA at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

To be honest I'm not so sure about these "effects"... Simply the fact that
the Member class needs -XOverlappingInstances means that we cannot have
duplicate or polymorphic effects. It will arbitrarily pick the first match
in the former and fail to compile in the latter case.

Furthermore I don't really understand the way open sums are implemented.
These unions should be disjoint, but the way they're implemented in the
paper they try to be "true" unions which cannot be done as that would need
type equality (-XOverlappingInstances is a hack around this)

A correct disjoint open sum would behave well with duplicate and
polymorphic types in the type list. For example we should be able to
project the open sum equivalent of Either String String into the second
String but we cannot with the implementation in the paper. This means we
need to ~index~ the type list instead of picking the result type and
"trying for equality" with each entry. Something like this:
http://lpaste.net/92069

Of course this is very inconvenient and simply replaces the monad
transformers' lifts with a static index into the "effect" list.
In general I think there is no convenient way of stacking effects that is
also type safe. At some point we have to disambiguate which effect we are
trying to use one way or the other. The implementation in the paper simply
picks a heuristic and chooses the first effect that seems to match and
discards the others.



On 22 August 2013 12:15, Alberto G. Corona <agocorona at gmail.com> wrote:

> The paper is very interesting:
>
> http://www.cs.indiana.edu/~sabry/papers/exteff.pdf
>
> It seems that the approach is mature enough and it is better in every way
> than monad transformers, while at the same time the syntax may become
> almost identical to MTL for many uses.
>
> I only expect to see the library in Hackage with all the blessings, and
> with all the instances of the MTL classes in order to make the transition
> form monad transformers  to ExtEff as transparent as possible
>
>
> 2013/8/22 <oleg at okmij.org>
>
>
>> Perhaps effect libraries (there are several to choose from) could be a
>> better answer to Fork effects than monad transformers. One lesson from
>> the recent research in effects is that we should start thinking what
>> effect we want to achieve rather than which monad transformer to
>> use. Using ReaderT or StateT or something else is an implementation
>> detail. Once we know what effect to achieve we can write a handler, or
>> interpreter, to implement the desired operation on the World, obeying
>> the desired equations. And we are done.
>>
>> For example, with ExtEff library with which I'm more familiar, the
>> Fork effect would take as an argument a computation that cannot throw
>> any requests. That means that the parent has to provide interpreters
>> for all child effects. It becomes trivially to implement:
>>
>> > Another example would be a child that should not be able to throw
>> errors as
>> > opposed to the parent thread.
>> It is possible to specify which errors will be allowed for the child
>> thread (the ones that the parent will be willing to reflect and
>> interpret). The rest of errors will be statically prohibited then.
>>
>> > instance (Protocol p) => Forkable (WebSockets p) (ReaderT (Sink p) IO)
>> where
>> >     fork (ReaderT f) = liftIO . forkIO . f =<< getSink
>>
>> This is a good illustration of too much implementation detail. Why do we
>> need to know of (Sink p) as a Reader layer? Would it be clearer to
>> define an Effect of sending to the socket? Computation's type will
>> make it patent the computation is sending to the socket.
>> The parent thread, before forking, has to provide a handler for that
>> effect (and the handler will probably need a socket).
>>
>> Defining a new class for each effect is possible but not needed at
>> all. With monad transformers, a class per effect is meant to hide the
>> ordering of transformer layers in a monad transformer stack. Effect
>> libraries abstract over the implementation details out of the
>> box. Crutches -- extra classes -- are unnecessary. We can start by
>> writing handlers on a case-by-case basis. Generalization, if any,
>> we'll be easier to see. From my experience, generalizing from concrete
>> cases is easier than trying to write a (too) general code at the
>> outset. Way too often, as I read and saw, code that is meant to be
>> reusable ends up hardly usable.
>>
>>
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Alberto.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/2dbf1548/attachment-0001.html>

------------------------------

Message: 2
Date: Thu, 22 Aug 2013 23:32:47 +0800
From: suhorng Y <suhorng at gmail.com>
To: haskell-cafe <Haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Yet Another Forkable Class
Message-ID:
<CA+w6aq+5mOta71CS2QyH+9K6hUH-pEmERWTi22w1PFn-zYpWWg at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

For the open union used in extensible effects, apart from using the
Typeable mechanism, is there a more protected way to implement
the open sum type?

I managed to modified the Member class given in the paper, but
ended up having to use the vague OverlappingInstance. That's not
quite what I hope. I'm not even sure whether the instance `Member t (t :>
r)`
is more specific than `Member t (t' :> r)`.

--
suhorng

{-# LANGUAGE KindSignatures, TypeOperators, GADTs, FlexibleInstances,
             FlexibleContexts, MultiParamTypeClasses, OverlappingInstances
#-}
-- FlexibleContexts is for Show instance of Union

import Data.Functor
import Control.Applicative -- for several functor instances

-- open union
infixr 2 :>
data (a :: * -> *) :> b

data Union r v where
  Elsewhere :: Functor t' => Union r v -> Union (t' :> r) v
  Here :: Functor t => t v -> Union (t :> r) v

class Member t r where
  inj :: Functor t => t v -> Union r v
  prj :: Functor t => Union r v -> Maybe (t v)

instance Member t (t :> r) where
  inj tv = Here tv
  prj (Here tv)     = Just tv
  prj (Elsewhere _) = Nothing

-- Note: overlapped by letting t' = t
instance (Functor t', Member t r) => Member t (t' :> r) where
  inj tv = Elsewhere (inj tv)
  prj (Here _)      = Nothing
  prj (Elsewhere u) = prj u

decomp :: Functor t => Union (t :> r) v -> Either (Union r v) (t v)
decomp (Here tv)     = Right tv
decomp (Elsewhere u) = Left u

-- Auxiliary definitions for tests
data Void
newtype Func a = Func a

instance Show (Union Void a) where
  show _ = undefined

instance (Show (t v), Show (Union r v)) => Show (Union (t :> r) v) where
  show (Here tv)     = "Here " ++ show tv
  show (Elsewhere u) = "Elsewhere " ++ show u

instance Functor Func where
  fmap f (Func x) = Func (f x)

instance Show a => Show (Func a) where
  show (Func a) = show a

type Stk = Maybe :> Either Char :> Func :> Void
type Stk' = Either Char :> Func :> Void -- used in `deTrue`, `deFalse`

unTrue :: Union Stk Bool
unTrue = inj (Func True)

unFalse :: Union Stk Bool
unFalse = inj (Just False)

-- `Func` is repeated
un5 :: Union (Maybe :> Func :> Either Char :> Func :> Void) Int
un5 = inj (Func 5)

maybe2 :: Maybe (Func Int)
maybe2 = prj un5

maybeTrue :: Maybe (Func Bool)
maybeTrue = prj unTrue

maybeFalse1 :: Maybe (Func Bool)
maybeFalse1 = prj unFalse

maybeFalse2 :: Maybe (Maybe Bool)
maybeFalse2 = prj unFalse

deTrue :: Either (Union Stk' Bool) (Maybe Bool)
deTrue = decomp unTrue

deFalse :: Either (Union Stk' Bool) (Maybe Bool)
deFalse = decomp unFalse



2013/8/22 Alberto G. Corona <agocorona at gmail.com>

> The paper is very interesting:
>
> http://www.cs.indiana.edu/~sabry/papers/exteff.pdf
>
> It seems that the approach is mature enough and it is better in every way
> than monad transformers, while at the same time the syntax may become
> almost identical to MTL for many uses.
>
> I only expect to see the library in Hackage with all the blessings, and
> with all the instances of the MTL classes in order to make the transition
> form monad transformers  to ExtEff as transparent as possible
>
>
> 2013/8/22 <oleg at okmij.org>
>
>
>> Perhaps effect libraries (there are several to choose from) could be a
>> better answer to Fork effects than monad transformers. One lesson from
>> the recent research in effects is that we should start thinking what
>> effect we want to achieve rather than which monad transformer to
>> use. Using ReaderT or StateT or something else is an implementation
>> detail. Once we know what effect to achieve we can write a handler, or
>> interpreter, to implement the desired operation on the World, obeying
>> the desired equations. And we are done.
>>
>> For example, with ExtEff library with which I'm more familiar, the
>> Fork effect would take as an argument a computation that cannot throw
>> any requests. That means that the parent has to provide interpreters
>> for all child effects. It becomes trivially to implement:
>>
>> > Another example would be a child that should not be able to throw
>> errors as
>> > opposed to the parent thread.
>> It is possible to specify which errors will be allowed for the child
>> thread (the ones that the parent will be willing to reflect and
>> interpret). The rest of errors will be statically prohibited then.
>>
>> > instance (Protocol p) => Forkable (WebSockets p) (ReaderT (Sink p) IO)
>> where
>> >     fork (ReaderT f) = liftIO . forkIO . f =<< getSink
>>
>> This is a good illustration of too much implementation detail. Why do we
>> need to know of (Sink p) as a Reader layer? Would it be clearer to
>> define an Effect of sending to the socket? Computation's type will
>> make it patent the computation is sending to the socket.
>> The parent thread, before forking, has to provide a handler for that
>> effect (and the handler will probably need a socket).
>>
>> Defining a new class for each effect is possible but not needed at
>> all. With monad transformers, a class per effect is meant to hide the
>> ordering of transformer layers in a monad transformer stack. Effect
>> libraries abstract over the implementation details out of the
>> box. Crutches -- extra classes -- are unnecessary. We can start by
>> writing handlers on a case-by-case basis. Generalization, if any,
>> we'll be easier to see. From my experience, generalizing from concrete
>> cases is easier than trying to write a (too) general code at the
>> outset. Way too often, as I read and saw, code that is meant to be
>> reusable ends up hardly usable.
>>
>>
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Alberto.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/a6c3d334/attachment-0001.html>

------------------------------

Message: 3
Date: Thu, 22 Aug 2013 12:51:24 -0300
From: Thiago Negri <evohunz at gmail.com>
To: Haskell-Cafe <haskell-cafe at haskell.org>
Subject: [Haskell-cafe] Lifting strictness to types
Message-ID:
<CABLneZtLgGZ-K6EHPTqp8RCf617t4Xh6=qDpZwP0K6VNCZVEJg at mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I've just read the post "Destroying Performance with Strictness" by Neil
Mitchell [1].

One of the comments from an Anonymous says:

How hard would it be to lift strictness annotations to type-level? E.g.
instead of
f :: Int -> Int
f !x = x + 1
write
f :: !Int -> Int
f x = x + 1
which would have the same effect. At least it would be transparent to the
developer using a particular function.
The problem I see with this approach is on type classes, as it would be
impossible to declare a type instance with strict implementation to a type
class that used lazy types.

Is this a real problem? Is it the only one?

[1]
http://neilmitchell.blogspot.ru/2013/08/destroying-performance-with-strictness.html
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/1d60d343/attachment-0001.html>

------------------------------

Message: 4
Date: Thu, 22 Aug 2013 17:10:13 +0100
From: Tom Ellis <tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk>
To: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Lifting strictness to types
Message-ID: <20130822161013.GH28714 at weber>
Content-Type: text/plain; charset=us-ascii

On Thu, Aug 22, 2013 at 12:51:24PM -0300, Thiago Negri wrote:
> How hard would it be to lift strictness annotations to type-level? E.g.
> instead of
> f :: Int -> Int
> f !x = x + 1
> write
> f :: !Int -> Int
> f x = x + 1
> which would have the same effect. At least it would be transparent to the
> developer using a particular function.

See also the recent Reddit thread

    http://www.reddit.com/r/haskell/comments/1ksu0v/reasoning_about_space_leaks_with_space_invariants/cbsac5m

where I and others considered the possibility of a strict language with
explicit thunk datatype.  NB OCaml essentially already has this

    http://caml.inria.fr/pub/docs/manual-ocaml/libref/Lazy.html

but I think Haskellers would do it better because we have a lot of
experience with purity, laziness and monad and comonad transformers.

Tom



------------------------------

Message: 5
Date: Thu, 22 Aug 2013 13:19:49 -0300
From: Thiago Negri <evohunz at gmail.com>
To: Tom Ellis <tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk>,
Haskell-Cafe <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Lifting strictness to types
Message-ID:
<CABLneZt7fk-3RbQQk9GQp1ewCTgpOmcYksPcUgBeX+V5qrM7mg at mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I think Scala has this optional laziness too.
The problem with default-strictness is that libraries that are built with
no laziness in mind turn up to be too strict.
Going from lazy to strict is possible in the client side, but the other way
is impossible.



2013/8/22 Tom Ellis <tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk>

> On Thu, Aug 22, 2013 at 12:51:24PM -0300, Thiago Negri wrote:
> > How hard would it be to lift strictness annotations to type-level? E.g.
> > instead of
> > f :: Int -> Int
> > f !x = x + 1
> > write
> > f :: !Int -> Int
> > f x = x + 1
> > which would have the same effect. At least it would be transparent to the
> > developer using a particular function.
>
> See also the recent Reddit thread
>
>
> http://www.reddit.com/r/haskell/comments/1ksu0v/reasoning_about_space_leaks_with_space_invariants/cbsac5m
>
> where I and others considered the possibility of a strict language with
> explicit thunk datatype.  NB OCaml essentially already has this
>
>     http://caml.inria.fr/pub/docs/manual-ocaml/libref/Lazy.html
>
> but I think Haskellers would do it better because we have a lot of
> experience with purity, laziness and monad and comonad transformers.
>
> Tom
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/a3554dd1/attachment-0001.html>

------------------------------

Message: 6
Date: Thu, 22 Aug 2013 18:38:38 +0200
From: Stefan Mehner <mehner at iai.uni-bonn.de>
To: haskell-cafe at haskell.org
Subject: [Haskell-cafe] instance Alternative ZipList
Message-ID:
<CAN+5uto+hRW2Omd1M+HRiMP=oyQz0etrhPggz+rXowMC44chmw at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I had an idea for |instance Alternative ZipList|, which doesn't seem to
exist so far. Maybe there just is no need for it. Please tell me what you
think.

After giving the instance definition I will add some intuition on why this
might be useful. Then some words on laws and other conceivable instances.

This appeared on stackoverflow before to make sure it is new
(
http://stackoverflow.com/questions/18210765/instance-alternative-ziplist-in-haskell
).
J. Abrahamson proposed to move this to the list, so here it is.

The only thing I found so far is by AndrewC on stackoverflow:

  There are two sensible choices for Zip [1,3,4] <|> Zip [10,20,30,40]:
  Zip [1,3,4] because it's first - consistent with Maybe
  Zip [10,20,30,40] because it's longest - consistent with Zip [] being
discarded

(Here Zip is basically ZipList with the known Applicative instance.)

Proposed instance
=================

I think the answer should be Zip [1,3,4,40]. Let's see an instance:

> instance Aternative Zip where
>   empty = Zip []
>   Zip xs <|> Zip ys = Zip (go xs ys) where
>     go []     ys     = ys
>     go xs     []     = xs
>     go (x:xs) (_:ys) = x : go xs ys

The only Zip a we can produce without knowing the type argument a is Zip
[] :: Zip a, so there is little choice for empty. If the empty list is the
neutral element of the monoid, we might be tempted to use list
concatenation as the monoid operation. However, go is not (++), since
every time we use one entry of the first argument list, we drop one of the
second. Thus we have a kind of overlay: The left argument list hides the
beginning of the right one (or all of it).

[ 1, 3, 4,40]   [10,20,30,40]   [ 1, 3, 4]   [ 1, 3, 4]
  ^  ^  ^  ^      ^  ^  ^  ^      ^  ^  ^      ^ ^  ^
  |  |  |  |      |  |  |  |      |  |  |      |  |  |
[ 1, 3, 4] |    [10,20,30,40]   []|  |  |    [ 1, 3, 4]
[10,20,30,40]   [ 1, 3, 4]      [ 1, 3, 4]   []

(use monospace for ascii-art)

For the some/many methods I'd guess

> some (Zip z) = Zip (map repeat z)
> many (Zip z) = Zip (map repeat z ++ repeat [])

where some takes a ziplist and replaces every entry x by repeat x and many
does the same but additionally extends the ziplist with empty lists.

Probably not particularly usefull, but that's what the recursive
definition of some and many gives.

What is it good for?
====================

One intuition behind ziplists is processes: A finite or infinite stream of
results. When zipping, we combine streams, which is reflected by the
Applicative instance. When the end of the list is reached, the stream
doesn't produce further elements. This is where the Alternative instance
comes in handy: We can name a replacement, taking over as soon as the
default process terminates.

For example we could write

< fmap Just foo <|> pure Nothing

to wrap every element of the ziplist foo into a Just and continue with
Nothing afterwards. The resulting ziplist is infinite, reverting to a
default value after all (actual) values have been used up. This could of
course be done by hand by appending an infinite list inside the Zip
constructor. Yet the above is more elegant and does not assume knowledge
of constructors, leading to higher code reusability.

Another intuition one might have of zipLists is partial functions on
naturals. Using this analogy, <|> behaves like the Monoid instance of Map
and IntMap.

Lawfulness
==========

The definition of <|> given above is associative and the empty list really
is the empty element. We also have

< Zip [] <*> xs = fs <*> Zip [] = Zip []
< (fs <|> gs) <*> xs = fs <*> xs <|> gs <*> xs
< fs <*> (xs <|> ys) = fs <*> xs <|> fs <*> ys

so all the laws you could ask for are satisfied (which is not true for
list concatenation by the way).

This instance is consistent with the one for Maybe: Choice is biased to
the left, yet when the left argument is unable to produce a value, the
right argument takes over. The functions

> zipToMaybe :: Zip a -> Maybe a
> zipToMaybe (Zip []) = Nothing
> zipToMaybe (Zip (x:_)) = Just x

> maybeToZip :: Maybe a -> Zip a
> maybeToZip Nothing = Zip []
> maybeToZip (Just x) = pure x

are morphisms of alternatives (meaning psi x <|> psi y = psi (x <|> y) and
psi x <*> psi y = psi (x <*> y)).

Other options
=============

Before putting this up to discussion I have to say this was conceived in
an armchair: Until now I don't really know of any concrete uses for this
instance. Might be there are none.

Some words on AndrewC's instances (none of which has been put forward as a
serious suggestion).

Picking the longer list has a number of problems to it. When it comes to
infinite lists (which are introduced by pure), we get undefined values.
Also it's not very lazy: We have to evaluate both arguments until the
shorter list ends just to get the first entry of the result. When both
lists are of equal length we probably pick the left one, which defies the
laws (distributivity in particular). Finally, you could just write

> maximumBy (compare `on` length) [ys,xs]

which is surprisingly readable (and biassed to the right).

Picking the first nonempty list also feels strange: The 100-th entry of xs
<|> ys should only depend on the 100-th entry of xs and ys or their
absence. This is reasonable since processes shouldn't care to much about
what happend 100 steps earlier. Yet if we only check for empty lists at
the very beginning, the choice is permanent. Again, if you insist on doing
so, just use

> maximumBy (compare `on` not . null) [ys,xs]

The overlaying instance given above introduces some non-trivial behaviour
by allowing to mix lists together (instead of just returning one of the
arguments). I can't think of any way to build this by combining four
existing functions (avoiding length and drop). It satisfies all the laws
and I can image it might at least be of some use.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/84c4837b/attachment-0001.html>

------------------------------

Message: 7
Date: Thu, 22 Aug 2013 18:57:50 +0200
From: Bardur Arantsson <spam at scientician.net>
To: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Lifting strictness to types
Message-ID: <kv5fu7$4gf$1 at ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1

On 2013-08-22 18:19, Thiago Negri wrote:
> I think Scala has this optional laziness too.

Indeed, but it's _not_ apparent in types (which can be an issue).

Due to the somewhat weird constructor semantics of the JVM it also means
you can have immutable values which start out(!) as null and end up
being non-null.

Regards,




------------------------------

Message: 8
Date: Thu, 22 Aug 2013 14:30:45 -0400
From: jabolopes at google.com
To: haskell-cafe at haskell.org
Subject: [Haskell-cafe] Hoogle vs Hayoo
Message-ID: <20130822183045.GB3130 at google.com>
Content-Type: text/plain; charset=us-ascii

Hi,

I noticed Hayoo appears as a link in the toolbox of
http://hackage.haskell.org and also that Hayoo seems to display better
results than Hoogle.  For example, if you search for 'PublicKey' in
Hayoo, you will get several results from Hackage libraries, such as,
'crypto-pubkey' and 'crypto-api'.  However, the same query in Hoogle
displays no results.

Is Hayoo the default Hackage search engine ?
Is Hoogle deprecated ?
What the status ?

Thank you,
Jose



------------------------------

Message: 9
Date: Thu, 22 Aug 2013 20:23:39 +0100
From: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
To: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Hoogle vs Hayoo
Message-ID: <5216653B.8010902 at fuuzetsu.co.uk>
Content-Type: text/plain; charset=ISO-8859-1

On 22/08/13 19:30, jabolopes at google.com wrote:
> Hi,
> 
> I noticed Hayoo appears as a link in the toolbox of
> http://hackage.haskell.org and also that Hayoo seems to display better
> results than Hoogle.  For example, if you search for 'PublicKey' in
> Hayoo, you will get several results from Hackage libraries, such as,
> 'crypto-pubkey' and 'crypto-api'.  However, the same query in Hoogle
> displays no results.
> 
> Is Hayoo the default Hackage search engine ?
> Is Hoogle deprecated ?
> What the status ?
> 
> Thank you,
> Jose
> 

You could also try the Hoogle hosted by FPComplete guys, it indexes more
stuff. It's at [1].

I hear that Hayoo actually does a better job getting the relevant
results but I am unsure how much truth there is to it. I always thought
it was just Hoogle with more indexed docs.


[1] - https://www.fpcomplete.com/hoogle


-- 
Mateusz K.



------------------------------

Message: 10
Date: Thu, 22 Aug 2013 22:04:27 +0200
From: Petr Pudl?k <petr.mvd at gmail.com>
To: haskell-cafe <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] monoids induced by
Applicative/Alternative/Monad/MonadPlus?
Message-ID: <52166ECB.1090309 at gmail.com>
Content-Type: text/plain; charset="iso-8859-1"; Format="flowed"

Or, if there are no such definitions, where would be a good place to add 
them?

Petr

Dne 08/20/2013 06:55 PM, Petr Pudl?k napsal(a):
>
> Dear Haskellers,
>
> are these monoids defined somewhere?
>
> |import  Control.Applicative
> import  Data.Monoid
>
> newtype  AppMonoid  m a =AppMonoid  (m  a)
> instance  (Monoid  a,Applicative  m) =>Monoid  (AppMonoid  m a)where
>      mempty =AppMonoid  $ pure mempty
>      mappend (AppMonoid  x) (AppMonoid  y) =AppMonoid  $ mappend <$> x <*> y
> -- With the () monoid for `a` this becames the monoid of effects.
>
> newtype  AltMonoid  m a =AltMonoid  (m  a)
> instance  Alternative  m =>Monoid  (AltMonoid  m a)where
>      mempty =AltMonoid  empty
>      mappend (AltMonoid  x) (AltMonoid  y) =AltMonoid  $ x <|> y|
>
> (and similarly for Monad/MonadPlus, until they become subclasses of 
> Applicative?)
>
> Best regards,
> Petr
>

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/4bad214e/attachment-0001.html>

------------------------------

Message: 11
Date: Fri, 23 Aug 2013 07:35:23 +0000 (UTC)
From: Johannes Waldmann <waldmann at imn.htwk-leipzig.de>
To: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Hoogle vs Hayoo
Message-ID: <loom.20130823T092534-520 at post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Mateusz Kowalczyk <fuuzetsu <at> fuuzetsu.co.uk> writes:

> I always thought [hayoo] was just Hoogle with more indexed docs.

Wait - there's a semantic difference:

hoogle does understand type signatures
(e.g., it can specialize them, or flip arguments of functions)
while hayoo just treats signatures as strings (it seems).

Example: search for [a] -> [a] 

hoogle: will also return  Data.Text.transpose :: [Text] -> [Text]
(note: instantiated  a  to Text)

hayoo: will also return Data.List.isInfixOf :: [a] -> [a] -> Bool
(note:  the type is [a] -> ([a] -> Bool), 
so it does actually not contain the type from the query)

I much prefer hoogle's query semantics.

- J.W.

PS: but hoogle also returns   inits :: [a] -> [[a]]
which is not an instance of the query. Why is this?





------------------------------

Message: 12
Date: 23 Aug 2013 08:06:08 -0000
From: oleg at okmij.org
To: 0slemi0 at gmail.com
Cc: Haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Yet Another Forkable Class
Message-ID: <20130823080608.45461.qmail at www1.g3.pair.com>


I must stress that OpenUnion1.hs described (briefly) in the paper
is only one implementation of open unions, out of many possible.
For example, I have two more implementations. A year-old version of
the code implemented open unions *WITHOUT* overlapping instances or
Typeable.
        http://okmij.org/ftp/Haskell/extensible/TList.hs

The implementation in the paper is essentially the one described in
the full HList paper, Appendix C. The one difference is that the HList
version precluded duplicate summands. Adding the duplication check to
OpenUnion1 takes three lines of code. I didn't add them because it
didn't seem necessary, or even desired.

I should further stress, OverlappingInstances are enabled only
within one module, OpenUnion1.hs. The latter is an internal, closed
module, not meant to be modified by a user. No user program needs to
declare OverlappingInstances in its LANGUAGES pragma. Second,
OverlappingInstances are used only within the closed type class
Member. This type class is not intended to be user-extensible; the
programmer need not and should not define any more instances for
it. The type class is meant to be closed. So Member emulates closed
type families implemented in the recent version of GHC. With the
closed type families, no overlapping instances are needed.

> Simply the fact that the Member class needs -XOverlappingInstances
> means that we cannot have duplicate or polymorphic effects. It will
> arbitrarily pick the first match in the former and fail to compile in
> the latter case.
Of course we can have duplicate layers. In that case, the dynamically closest
handler wins -- which sounds about right (think of reset in delimited
control). The file Eff.hs even has a test case for that, tdup.
BTW, I'm not sure of the word 'pick' -- the Member class is
a purely compile-time constraint. It doesn't do any picking -- it doesn't
do anything at all at run-time. 

> For example we should be able to project the open sum equivalent of
> Either String String into the second String but we cannot with the
> implementation in the paper.
You inject a String or a String, and you will certainly 
project a String (the one your have injected). What is the problem
then? You can always project what you have injected. Member merely
keeps track of what types could possibly be injected/projected. 
So, String + String indeed should be String.


By polymorphic effects you must mean first-class polymorphism (because
the already implemented Reader effect is polymorphic in the
environment). First of all, there are workarounds. Second, I'm not
sure what would be a good example of polymorphic effect (aside from 
ST-monad-like).

> To be honest I'm not so sure about these "effects"...
Haskell Symposium will have a panel on effect libraries in Haskell.
It seems plausible that effects, one way or the other, will end ip in
Haskell. Come to Haskell Symposium, tell us your doubts and
concerns. We want to hear them.





------------------------------

Message: 13
Date: Fri, 23 Aug 2013 10:12:27 +0200
From: Erik Hesselink <hesselink at gmail.com>
To: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
Cc: haskell <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Hoogle vs Hayoo
Message-ID:
<CAPeieQG8waubz3xtS=e6pyNyJRVvcXES14eCofxdKZ7Nhr=N4g at mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Thu, Aug 22, 2013 at 9:23 PM, Mateusz Kowalczyk
<fuuzetsu at fuuzetsu.co.uk> wrote:
> On 22/08/13 19:30, jabolopes at google.com wrote:
>> Hi,
>>
>> I noticed Hayoo appears as a link in the toolbox of
>> http://hackage.haskell.org and also that Hayoo seems to display better
>> results than Hoogle.  For example, if you search for 'PublicKey' in
>> Hayoo, you will get several results from Hackage libraries, such as,
>> 'crypto-pubkey' and 'crypto-api'.  However, the same query in Hoogle
>> displays no results.
>>
>> Is Hayoo the default Hackage search engine ?
>> Is Hoogle deprecated ?
>> What the status ?
>
> You could also try the Hoogle hosted by FPComplete guys, it indexes more
> stuff.

Note that the 'normal' hoogle indexes all (?) of hackage. But by
default it only searches the haskell platform. You can add a package
with '+' to search in that package. E.g. "PublicKey +crypto-api".

Regards,

Erik



------------------------------

Message: 14
Date: Fri, 23 Aug 2013 18:32:03 +1000
From: Erik de Castro Lopo <mle+hs at mega-nerd.com>
To: haskell-cafe at haskell.org
Subject: [Haskell-cafe] Conduit : is it possible to write this
function?
Message-ID: <20130823183203.4ad9e831fffb2f54c1a44647 at mega-nerd.com>
Content-Type: text/plain; charset=US-ASCII

Hi all

Using the Conduit library is it possible to write the function:

   eitherSrc :: MonadResource m
             => Source m a -> Source m b -> Source m (Either a b)

which combines two sources into new output source such that data being
produced aysnchronously by the original two sources will be returned
as either a Left or Right of tne new source?

If so, how?

Cheers,
Erik
-- 
----------------------------------------------------------------------
Erik de Castro Lopo
http://www.mega-nerd.com/



------------------------------

Message: 15
Date: Fri, 23 Aug 2013 10:33:50 +0200
From: Daniel Trstenjak <daniel.trstenjak at gmail.com>
To: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Hoogle vs Hayoo
Message-ID: <20130823083350.GA3100 at machine>
Content-Type: text/plain; charset=us-ascii


On Fri, Aug 23, 2013 at 10:12:27AM +0200, Erik Hesselink wrote:
> Note that the 'normal' hoogle indexes all (?) of hackage. But by
> default it only searches the haskell platform. You can add a package
> with '+' to search in that package. E.g. "PublicKey +crypto-api".

If the idea behind this, that the haskell platform packages should
be the first place to look at, than this could be also achieved by
sorting the search results.

It's a bit pointless, if I have to know the package, where I want to
search in. 


Greetings,
Daniel



------------------------------

Message: 16
Date: Fri, 23 Aug 2013 12:14:22 +0300
From: Michael Snoyman <michael at snoyman.com>
To: Haskell Cafe <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Conduit : is it possible to write this
function?
Message-ID:
<CAKA2JgJnQTwqexjS-_1e9abpp32_POyYxAvs7JERhTk_FgzJgw at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

You can build this up using the >=< operator[1] in stm-conduit, something
like:

eitherSrc :: MonadResourceBase m
             => Source (ResourceT m) a -> Source (ResourceT m) b -> Source
(ResourceT m) (Either a b)
eitherSrc src1 src2 = do
    join $ lift $ Data.Conduit.mapOutput Left src1 >=<
Data.Conduit.mapOutput Right src2

I think this can be generalized to work with more base monads with some
tweaks to (>=<).

[1]
http://haddocks.fpcomplete.com/fp/7.4.2/20130704-120/stm-conduit/Data-Conduit-TMChan.html#v:-62--61--60-


On Fri, Aug 23, 2013 at 11:32 AM, Erik de Castro Lopo
<mle+hs at mega-nerd.com>wrote:

> Hi all
>
> Using the Conduit library is it possible to write the function:
>
>    eitherSrc :: MonadResource m
>              => Source m a -> Source m b -> Source m (Either a b)
>
> which combines two sources into new output source such that data being
> produced aysnchronously by the original two sources will be returned
> as either a Left or Right of tne new source?
>
> If so, how?
>
> Cheers,
> Erik
> --
> ----------------------------------------------------------------------
> Erik de Castro Lopo
> http://www.mega-nerd.com/
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130823/872b06be/attachment-0001.html>

------------------------------

Message: 17
Date: Fri, 23 Aug 2013 11:23:24 +0200
From: TP <paratribulations at free.fr>
To: haskell-cafe at haskell.org
Subject: [Haskell-cafe] typeclass constraints
Message-ID: <c9mjea-bl2.ln1 at rama.universe>
Content-Type: text/plain; charset="ISO-8859-1"

Hi everybody,


There is something I do not understand in the way typeclass constraints are 
inferred.


1/ Take the following function definition:

sum' [] = []
sum' (x:xs) = x + sum' xs

GHCI correctly gives:

> :t sum'
sum' :: Num [a] => [[a]] -> [a]

So it has inferred that the type list has to be an instance of Num for sum' 
to be able to work. It will give an error if we try to use sum' without 
implementing the instance.


2/ Now, take the following definition:

------------------------
{-# LANGUAGE TemplateHaskell #-}

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

p :: a -> ExpQ
p n = [| show n |]
------------------------

We obtain an error if we try to load it in GHCI:

    No instance for (Lift a) arising from a use of `n'
    Possible fix:
      add (Lift a) to the context of
        the type signature for p :: a -> ExpQ
    In the first argument of `show', namely `n'
    In the Template Haskell quotation [| show n |]
    In the expression: [| show n |]

And indeed, if we use instead:

------------------------
{-# LANGUAGE TemplateHaskell #-}

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

p :: Lift a => a -> ExpQ
p n = [| show n |]
------------------------

it works correctly.


Why GHC is able to infer the typeclass constraint (Num a) in 1/, but not 
(Lift a) in 2/?


Thanks in advance,

TP




------------------------------

Message: 18
Date: Fri, 23 Aug 2013 10:36:04 +0100
From: Adam Gundry <adam.gundry at strath.ac.uk>
To: TP <paratribulations at free.fr>
Cc: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] typeclass constraints
Message-ID: <52172D04.60401 at strath.ac.uk>
Content-Type: text/plain; charset=ISO-8859-1

Hi TP,

The difference is that in your second example, you have specified the
type signature

p :: a -> ExpQ

so GHC checks whether p has this type, and correctly objects that it
doesn't. If you leave off the type signature, as you did for sum', the
right thing will be inferred.

Hope this helps,

Adam


On 23/08/13 10:23, TP wrote:
> Hi everybody,
> 
> 
> There is something I do not understand in the way typeclass constraints are 
> inferred.
> 
> 
> 1/ Take the following function definition:
> 
> sum' [] = []
> sum' (x:xs) = x + sum' xs
> 
> GHCI correctly gives:
> 
>> :t sum'
> sum' :: Num [a] => [[a]] -> [a]
> 
> So it has inferred that the type list has to be an instance of Num for sum' 
> to be able to work. It will give an error if we try to use sum' without 
> implementing the instance.
> 
> 
> 2/ Now, take the following definition:
> 
> ------------------------
> {-# LANGUAGE TemplateHaskell #-}
> 
> import Language.Haskell.TH
> import Language.Haskell.TH.Syntax
> 
> p :: a -> ExpQ
> p n = [| show n |]
> ------------------------
> 
> We obtain an error if we try to load it in GHCI:
> 
>     No instance for (Lift a) arising from a use of `n'
>     Possible fix:
>       add (Lift a) to the context of
>         the type signature for p :: a -> ExpQ
>     In the first argument of `show', namely `n'
>     In the Template Haskell quotation [| show n |]
>     In the expression: [| show n |]
> 
> And indeed, if we use instead:
> 
> ------------------------
> {-# LANGUAGE TemplateHaskell #-}
> 
> import Language.Haskell.TH
> import Language.Haskell.TH.Syntax
> 
> p :: Lift a => a -> ExpQ
> p n = [| show n |]
> ------------------------
> 
> it works correctly.
> 
> 
> Why GHC is able to infer the typeclass constraint (Num a) in 1/, but not 
> (Lift a) in 2/?
> 
> 
> Thanks in advance,
> 
> TP
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 




------------------------------

Subject: Digest Footer

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe at haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


------------------------------

End of Haskell-Cafe Digest, Vol 120, Issue 35
*********************************************
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130823/18c55f37/attachment.htm>


More information about the Haskell-Cafe mailing list