Re: [Haskell-cafe] mapFst and mapSnd

2013-05-30 Thread Shachaf Ben-Kiki
On Tue, May 28, 2013 at 1:54 AM, Dominique Devriese
dominique.devri...@cs.kuleuven.be wrote:
 Hi all,

 I often find myself needing the following definitions:

   mapPair :: (a - b) - (c - d) - (a,c) - (b,d)
   mapPair f g (x,y) = (f x, g y)

   mapFst :: (a - b) - (a,c) - (b,c)
   mapFst f = mapPair f id

   mapSnd :: (b - c) - (a,b) - (a,c)
   mapSnd = mapPair id

 But they seem missing from the prelude and Hoogle or Hayoo only turn
 up versions of them in packages like scion or fgl.  Has anyone else
 felt the need for these functions?  Am I missing some generalisation
 of them perhaps?


One generalization of them is to lenses. For example `lens` has
both, _1, _2, such that mapPair = over both, mapFst = over
_1, etc., but you can also get fst = view _1, set _2 = \y' (x,_)
- (x,y'), and so on. (Since both refers to two elements, you end
up with view both = \(x,y) - mappend x y.) The types you end up
with are simple generalizations of mapFoo, with just an extra Functor
or Applicative (think mapMFoo):

both :: Applicative f = (a - f b) - (a,a) - f (b,b)
both f (x,y) = (,) $ f x * g y

_2 :: Functor f = (a - f b) - (e,a) - f (e,b)
_2 f (x,y) = (,) x $ f y

With an appropriate choice of f you can get many useful functions.

Shachaf

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


Re: [Haskell-cafe] mapFst and mapSnd

2013-05-30 Thread Shachaf Ben-Kiki
On Thu, May 30, 2013 at 7:12 PM, Shachaf Ben-Kiki shac...@gmail.com wrote:
 One generalization of them is to lenses. For example `lens` has
 both, _1, _2, such that mapPair = over both, mapFst = over
 _1, etc., but you can also get fst = view _1, set _2 = \y' (x,_)
 - (x,y'), and so on. (Since both refers to two elements, you end
 up with view both = \(x,y) - mappend x y.) The types you end up
 with are simple generalizations of mapFoo, with just an extra Functor
 or Applicative (think mapMFoo):

 both :: Applicative f = (a - f b) - (a,a) - f (b,b)
 both f (x,y) = (,) $ f x * g y

 _2 :: Functor f = (a - f b) - (e,a) - f (e,b)
 _2 f (x,y) = (,) x $ f y

 With an appropriate choice of f you can get many useful functions.


I spoke too quickly -- your mapPair is something different. Indeed
bimap (or (***), if you prefer base) is the place to find it -- lenses
don't really fit here. My both is for mapping one function over both
elements.

Shachaf

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


[Haskell-cafe] Haskell + RankNTypes + (forall p. p Char - p Bool) sound?

2013-03-05 Thread Shachaf Ben-Kiki
I was trying to figure out a way to write absurd :: (forall p. p Char
- p Bool) - Void using only rank-n types. Someone suggested that
Haskell with RankNTypes and a magic primitive of type (forall p. p
Char - p Bool) might be sound (disregarding the normal ways to get ⊥,
of course).

Is that true? Given either TypeFamilies or GADTs, you can write
absurd. But it doesn't seem like you can write it with just
RankNTypes. (This is related to GeneralizedNewtypeDeriving, which is
more or less a version of that magic primitive.)

This seems like something that GADTs (/TypeFamilies) give you over
Leibniz equality: You can write

  data Foo a where
FooA :: Foo Char
FooB :: Void - Foo Bool

  foo :: Foo Bool - Void
  foo (FooB x) = x

Without any warnings. On the other hand

  data Bar a = BarA (Is a Char) | BarB (Is a Bool) Void

  bar :: Bar Bool - Void
  bar (BarB _ x) = x
  bar (BarA w) = -- ???

Doesn't seem possible. If it's indeed impossible, what's the minimal
extension you would need to add on top of RankNTypes to make it work?
GADTs seems way too big.

Shachaf

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


Re: [Haskell-cafe] quotRem and divMod

2013-01-28 Thread Shachaf Ben-Kiki
On Mon, Jan 28, 2013 at 4:27 PM, Artyom Kazak artyom.ka...@gmail.com wrote:
 Hi!

 I’ve always thought that `quotRem` is faster than `quot` + `rem`, since both
 `quot` and `rem` are just wrappers that compute both the quotient and the
 remainder and then just throw one out. However, today I looked into the
 implementation of `quotRem` for `Int32` and found out that it’s not true:

 quotRem x@(I32# x#) y@(I32# y#)
 | y == 0 = divZeroError
 | x == minBound  y == (-1) = overflowError
 | otherwise  = (I32# (narrow32Int# (x# `quotInt#`
 y#)),
 I32# (narrow32Int# (x# `remInt#`
 y#)))

 Why? The `DIV` instruction computes both, doesn’t it? And yet it’s being
 performed twice here. Couldn’t one of the experts clarify this bit?


That code is from base 4.5. Here's base 4.6:

quotRem x@(I32# x#) y@(I32# y#)
| y == 0 = divZeroError
  -- Note [Order of tests]
| y == (-1)  x == minBound = (overflowError, 0)
| otherwise  = case x# `quotRemInt#` y# of
   (# q, r #) -
   (I32# (narrow32Int# q),
I32# (narrow32Int# r))

So it looks like it was improved in GHC 7.6. In particular, by this
commit: http://www.haskell.org/pipermail/cvs-libraries/2012-February/014880.html

Shachaf

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


[Haskell-cafe] Taking over ghc-core

2012-11-10 Thread Shachaf Ben-Kiki
With Don Stewart's blessing
(https://twitter.com/donsbot/status/267060717843279872), I'll be
taking over maintainership of ghc-core, which hasn't been updated
since 2010. I'll release a version with support for GHC 7.6 later
today.

Shachaf

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


Re: [Haskell-cafe] Smarter do notation

2011-09-04 Thread Shachaf Ben-Kiki
On Sat, Sep 3, 2011 at 19:34, Daniel Peebles pumpkin...@gmail.com wrote:
...
 Of course, the fact that the return method is explicitly mentioned in my
 example suggests that unless we do some real voodoo, Applicative would have
 to be a superclass of Monad for this to make sense. But with the new default
 superclass instances people are talking about in GHC, that doesn't seem too
 unlikely in the near future.
...

One way to avoid explicitly mentioning return would be to use monad
comprehension syntax, which uses return implicitly, instead of do
notation. This also has the advantage of being new in GHC 7.2,
rather than officially being part of Haskell 98/2010, and therefore
being more amenable to various extensions (e.g. there are already
extensions that use MonadPlus/MonadZip/MonadGroup). Applicative would
probably still have to be a superclass of Monad, but the translation
of this syntax is simpler.

Shachaf

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


Re: [Haskell-cafe] Interactive chatbot

2009-11-04 Thread Shachaf Ben-Kiki
On Wed, Nov 4, 2009 at 3:14 PM, Jason Dagit da...@codersbase.com wrote:


 On Wed, Nov 4, 2009 at 2:21 PM, Torsten Otto t-otto-n...@gmx.de wrote:

 Hi!

 My students have the task to program an interactive chatbot. We have run
 into a problem that I can't solve either:

 When we read the user's input through
    t - getLine
 it is not possible to delete typos before hitting enter and thereby
 sending the input off to the system (at least in OS X, bash). I didn't find
 that terribly problematic, but of course it is a bit of a show stopper from
 their point of view.

 Is it possible that you need to tweak the input buffering settings?
 http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html#v:hSetBuffering
 You probably want to look at 'interact' also.
 Or just switch to readline as others have suggested.
 Jason

Another possibility (perhaps simpler) is to use an external program
such as rlwrap to handle input.

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


[Haskell-cafe] LinuxFest Northwest 2009

2009-01-19 Thread Shachaf Ben-Kiki
LFNW 2009 (http://linuxfestnorthwest.org/) is going to be at the end of
April, and I was wondering if anyone here is going to be there, or possibly a
Haskell-related presentation.

Last year I met ac from #haskell there, but it would be nice if more people
came, especially with the (relatively) big group in Oregon and such. Perhaps
someone here has plans already?

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


Re: [Haskell-cafe] Sequencing Parsers: a Simple Example

2007-12-01 Thread Shachaf Ben-Kiki
 Hi
 (=) :: Parser a - Parser b - Parser b
 p = f = \inp -
case p inp of
  [] - []
  [(v, out)] - parse (f v) out
 based on a lot of guesswork, after the mess created by the OCR, I
 managed to get the above example to work syntactically but is it
 semantically correct?
 Thanks, Paul

You probably want:

(=) :: Parser a - (a - Parser b) - Parser b
p = f = \inp - case parse p inp of
[] - []
[(v,out)] - parse (f v) out

Assuming that you're following Graham Hutton's book.

Note that this definition won't actually compile; you probably need a
Monad instance and a newtype to get this to work properly (see
http://www.cs.nott.ac.uk/~gmh/Parsing.lhs for a working version of the
same code).

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


Re: [Haskell-cafe] Best way to format a number

2007-11-20 Thread Shachaf Ben-Kiki
On Nov 20, 2007 7:07 PM, Don Stewart [EMAIL PROTECTED] wrote:
 You can work around it for now with:

 Prelude Text.Printf printf %02d\n 3  return ()
 03

It may be simpler to specify the type explicitly:

Prelude Text.Printf printf %02d\n 3 :: IO ()
03

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


Re: [Haskell-cafe] What is the role of $!?

2007-11-14 Thread Shachaf Ben-Kiki
On Nov 14, 2007 4:27 PM, Justin Bailey [EMAIL PROTECTED] wrote:
 It's:

   f $! x = x `seq` f x

 That is, the argument to the right of $! is forced to evaluate, and
 then that value is passed to the function on the left. The function
 itself is not strictly evaluated (i.e., f x) I don't believe.

Unless you mean f -- which I still don't think would do much -- it
wouldn't make sense to evaluate (f x) strictly.
(x `seq` x) is equivalent to (x), for any x (including (f x)).

(Right?)

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


Re: [Haskell-cafe] Type inference problem with division (/)

2007-10-30 Thread Shachaf Ben-Kiki
On 10/30/07, Tim Chevalier [EMAIL PROTECTED] wrote:
 On 10/30/07, noa [EMAIL PROTECTED] wrote:
 
  Hi!
 
  I have the following function:
 
  theRemainder :: [String] - [String] - Double
  theRemainder xs xt = sum( map additional (unique xs) )
  where
  additional x = poccur * (inf [ppos,pneg]) --inf takes [Double]
  where
  xsxt = zip xs xt
  pi = countPos xr -- countPos returns an Int
  ni = (length xr) - pi
  len = length xs
  len2 = length xr
  ppos = pi/len2 -- THESE ARE THE PROBLEM
  pneg = ni/len2 -- THESE ARE THE PROBLEM
  poccur = (pi+ni)/len
  xr = (filter ((\y - (fst y)==x)) (xsxt))
 
  And I am getting this error message with ghc:
 
  matrix.hs:54:31:
  Couldn't match expected type `Double' against inferred type `Int'
  In the expression: ppos
  In the first argument of `inf', namely `[ppos, pneg]'
  In the second argument of `(*)', namely `(inf [ppos, pneg])'
 
  How can I change the declaration of ppos nad pneg so they are treated as
  Double for the inf function?
 

 ppos = pi/len2; pi and len2 are both Ints, so dividing them gives you
 an Int. To convert to a Double, write ppos = fromIntegral (pi/len2).
 (Type :t fromIntegral in ghci to see what else fromIntegral can be
 used for.)

You can't divide Ints with (/) at all -- they aren't Fractional.
You'll probably want to either fromIntegral both pi and len2 or use
div for integer division.

(Also, pi is a bit of a confusing name; you may want to consider using
another one.)

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


Re: [Haskell-cafe] Defining new operators

2007-08-10 Thread Shachaf Ben-Kiki
 Hi all,

 Given the follwing function:

  owner :: Step - Scenario
  owner (Step id scenario action state response) = scenario

 Is it possible to define the owner function in such way that I can write 
 x.owner (returning the scenario related with the Step x)?

Some people use (|), which looks like an arrow:

 (|) :: a - (a - b) - b
 x | f = f x

Then you can use step | owner.

Also consider using:

 data Step = Step { ..., scenario :: Scenario, ... }

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


Re: [Haskell-cafe] Getting lambdabot to work with 6.6.1

2007-07-17 Thread Shachaf Ben-Kiki

I also commented out arrows as a dependency in the .cabal, I think.
Was that not a good idea? it seemed to work.

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


Re: [Haskell-cafe] Is this haskelly enough?

2007-07-17 Thread Shachaf Ben-Kiki

on, which will appear in Data.Function in the next release of base,
is defined thusly:

on :: (b - b - c) - (a - b) - a - a - c
(*) `on` f = \x y - f x * f y


You can also use Data.Ord.comparing, in this case -- comparing is just
(compare `on`).


From Ord.hs:


-- |
--  comparing p x y = compare (p x) (p y)
--
-- Useful combinator for use in conjunction with the @xxxBy@ family
-- of functions from Data.List, for example:
--
--... sortBy (comparing fst) ...
comparing :: (Ord a) = (b - a) - b - b - Ordering
comparing p x y = compare (p x) (p y)

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


Re: [Haskell-cafe] Is this haskelly enough?

2007-07-17 Thread Shachaf Ben-Kiki

For the monadically-challenged, this is equivalent, yes-no?

maxsubarrays = maximumBy (compare `on` sum) . concat . (map tails) .
inits


Or: maxsubarrays = maximumBy (compare `on` sum) . concatMap tails . inits
(=) for lists is just (flip concatMap).

Also, this is working with lists, not arrays -- maxsubarrays is
probably a misleading name.

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