Re: [Haskell] ANN: Yi 0.6.3

2011-03-29 Thread Nicolas Pouillard
On Mon, 28 Mar 2011 14:40:21 -0500, Jeff Wheeler  wrote:
> On Mon, Mar 28, 2011 at 7:33 AM, Edward Amsden  wrote:
> >>  * mention alex in the cabal file (I don't remember the syntax but there is
> >>    a way to specify tools needed to build).
> > build-tools: alex
> >
> > in the library/executable section
> 
> Oh, my bad. I removed this because alex is included in the Platform,
> so it seemed like it'd always be available. I'll add it back.
> 
> I originally pulled pointedlist from Yi, but since switched from
> data-accessor to fclabels per suggestions by a few people. I also put
> the repo on github, it's on the yi-editor account page. Do we want to
> do the same switch on Yi? (I'll readily admit that I don't really know
> the advantages of data-accessor vs. fclabels.)

I would suggest going to fclabels for Yi itself as well.

> I don't know about rose-zipper, but I'll look at that.

I think releasing the constraint is enough for rose-zipper.

-- 
Nicolas Pouillard
http://nicolaspouillard.fr

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


Re: [Haskell] ANN: Yi 0.6.3

2011-03-28 Thread Nicolas Pouillard
On Fri, 25 Mar 2011 01:23:46 -0500, Jeff Wheeler  wrote:
> Hi all,
> 
> I'm very excited to announce the first release of Yi since last
> summer. It is relatively light on new features, but it finally should
> compile nicely on friendly machines. This means, for the most part,
> machines with the latest Haskell Platform installed. (Windows,
> unfortunately, has not been tested all that much. See details below,
> though, for install info.)

Great work. Pardon me complaining again but it would be much more easier to
integrate into ArchLinux if the following changes where made:
  * mention alex in the cabal file (I don't remember the syntax but there is
a way to specify tools needed to build).
  * depends on latest version of dependencies: pointedlist, rose-zipper

Cheers,

-- 
Nicolas Pouillard
http://nicolaspouillard.fr

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


[Haskell] Re: ANNOUNCE: countable-1.0

2010-09-06 Thread Nicolas Pouillard
On Mon, 06 Sep 2010 03:46:18 -0700, Ashley Yakeley  wrote:
> countable: Countable, Searchable, Finite, Empty classes.
> 
>class Countable, for countable types
>class AtLeastOneCountable, for countable types that have at least one 
> value
>class InfiniteCountable, for infinite countable types
>class Searchable, for types that can be searched over
>class Finite, for finite types
>class Empty, for empty types
>data Nothing, an empty type
> 
> Also includes these orphan instances:
> 
>instance (Searchable a,Eq b) => Eq (a -> b)
>instance (Finite a) => Foldable ((->) a)
>instance (Finite a) => Traversable ((->) a)
>instance (Show a,Finite a,Show b) => Show (a -> b)

Could you put these instances in a dedicated module?
In the same vein I would like to have a newtype wrapper over
functions were intention is to be used extensionally.

Nice package BTW!

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: [Haskell-cafe] ANN: hsparql, a SPARQL query generator/DSL and client

2009-07-09 Thread Nicolas Pouillard
Excerpts from Jeff Wheeler's message of Thu Jul 09 00:27:51 +0200 2009:
> I'm excited to announce the first version of hsparql. HSparql makes it
> easy to query SPARQL-compliant servers using a relatively intuitive DSL
> and very simple client.

I've looked at your DSL and it looks really neat. While reading I was
wondering if GADTs could help having an even nicer query language.

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-18 Thread Nicolas Pouillard
Excerpts from Jason Dusek's message of Sun May 17 15:45:25 +0200 2009:
>   From the documentation:
> 
>  "  LI could be a strict monad and a strict applicative functor.
> However it is not a lazy monad nor a lazy applicative
> functor as required Haskell. Hopefully it is a lazy
> (pointed) functor at least.

The type I would need for bind is this one:

  (>>=) :: NFData sa => LI sa -> (sa -> LI b) -> LI b

And because of the NFData constraint this type bind is less general than the
required one.

BTW this operator is exported as (!>>=) by System.IO.Lazy.Input.Extra.

By using the rmonad we could add this NFData constraint, but that's not like
having a Monad instance directly.

Best regards,

-- 
Nicolas Pouillard
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] [ANN] Safe Lazy IO in Haskell

2009-03-20 Thread Nicolas Pouillard
System.IO", and strict 'IORef''s.

One can now introduce a function in lines of 'mapHandleContents':

> withHandleContents :: NFData sa => Handle -> (String -> SIO sa) -> IO sa
> withHandleContents h f = do
>   s <- hGetContents h
>   SIO.run (f s) `finally` hClose h

One can then rewrite 'lowerText' as follow:

> lowerText = withHandleContents stdin (SIO.putStr . map toLower)

Until there one can deal quite nicely with single input, many outputs
processing. Currently the only requirement is to delimit a scope where
the resource will be used to return a strict value.

Dealing with multiple inputs will lead us to our final design of lazy
inputs.

== Introducing 'LI', Lazy Inputs ==

We first introduce a type for these lazy inputs namely 'LI'.
This type is abstract and we will progressively introduce functions
to build, combine and run them.

The 'LI' type is a pointed functor, but not necessarily a monad nor
an applicative functor.

Therefore one exports the 'pure' function as 'pureLI'. Building primitives
allow to read files or handles:

> LI.pureLI :: a -> LI a
> LI.hGetContents :: Handle -> LI String
> LI.getContents :: LI String
> LI.readFile :: FilePath -> LI String
> LI.getChanContents :: Chan a -> LI [a]

Being a functor is important: it allows to wholly transform the underlying
input lazily using standard functions about lists for instance:

> length <$> LI.readFile "foo"
> words <$> LI.readFile "foo"

Extracting a final value of a lazy input ('LI' type) is a matter of using:

> LI.run :: (NFData sa) => LI sa -> IO sa
Or
> LI.run' :: (NFData sa) => LI (SIO a) -> IO sa

One can therefore re-write our examples using lazy inputs:

> -- embedded printing
> countWords = LI.run' (SIO.print . length . words <$> LI.getContents)
> -- external printing
> maxLineLen = print =<< LI.run (maximum . map length . lines <$> 
> LI.getContents)
> lowerText  = LI.run' (SIO.putStr . map toLower <$> LI.getContents)

== Combining inputs ==

Finally we come to managing multiple inputs. To get both laziness and
precise resource management we will provide dedicated combinators.
The first one is as simple as appending.

> LI.append :: NFData sa => LI [sa] -> LI [sa] -> LI [sa]

This one produces a single stream out that sequences the two given streams.
It also sequences the usage of resources: the first resource is closed and
then the second one is opened.

Note that this combinator is still quite general since one can process each
input beforehand:

> -- one can drop parts of the inputs
> (take 100 <$> i1) `LI.append` (drop 100 <$> i2)
> -- one can tag each input to know where they come from
> Left <$> i1 `LI.append` Right <$> i2

The second one is 'LI.zipWith' which opens the two resources and joins the items
into a single stream. Again, since 'LI' is a functor one can join not only
characters but also words, lines, chunks... A problem with zipping is that it
stops on the shorter input (loosing a part of the other), hopefully one can
prolongate them:

> zipMaybesWith :: (NFData sa, NFData sb) -> (Maybe sa -> Maybe sb -> c) -> LI 
> [sa] -> LI [sb] -> LI [c]
> zipMaybesWith f xs ys =
> map (uncurry f) . takeWhile someJust <$> zip (prolongate <$> xs) 
> (prolongate <$> ys)
>   where someJust (Nothing, Nothing) = False
> someJust  _ = True
> prolongate :: [a] -> [Maybe a]
> prolongate zs = map Just zs ++ repeat Nothing

The last one is 'LI.interleave':

> LI.interleave ::  (NFData sa) -> LI [sa] -> LI [sa] -> LI [sa]

This function is currently left biased, moreover each resource is closed as soon
as we reach its end. However since the inputs are mixed up together one 
generally
prefers a tagged version trivially build upon this one:

> interleaveEither :: (NFData sa, NFData sb) => LI [sa] -> LI [sb] -> LI 
> [Either sa sb]
> interleaveEither a b = interleave (map Left <$> a) (map Right <$> b)

Here are some final programs that scale well with the number of files.

> -- number of words in the given files
> main = print =<< LI.run . fmap (length . words) . LI.concat . map LI.readFile 
> =<< getArgs

> -- almost the same thing but counts words independently in each file
> main =   print
>  =<< LI.run . fmap sum . LI.sequence . map (fmap (length . words) . 
> LI.readFile)
>  =<< getArgs

> -- prints to stdout swap-cased concatenation of all input files
> main = LI.run' . (fmap (SIO.putStr . fmap swapCase) . LI.concat . map 
> LI.readFile) =<< getArgs
>   where swapCase c | isUpper c = toLower c
>| otherwise = toUpper c

> -- sums character code points of inputs
> main = print =<< LI.run . fmap (sum . map (toInteger . ord)) . LI.concat . 
> map LI.readFile =<< getArgs

Our solution is from now widely available as an Hackage package named 
"safe-lazy-io" [4].

We hope you will freely enjoy using Lazy/IO again!

As usual, criticisms, comments, and help are expected!

Finally, I would like to thank Benoit Montagu and Francois Pottier for helping
me out to polish this work!

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/safe-lazy-io
[2]: http://okmij.org/ftp/Streams.html
[3]: http://www.haskell.org/pipermail/haskell/2009-March/021064.html
[4]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/strict-io

-- 
Nicolas Pouillard
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] ANNOUNCE: htags-1.0

2008-11-03 Thread Nicolas Pouillard
Excerpts from David Sankel's message of Mon Nov 03 19:25:23 +0100 2008:
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/htags
> 
> htags is a tag file generator to enable extra functionality in editors
> like vim. It expands upon hasktags by using a full Haskell 98 parser
> and options for recursion.

Hi,

I've just tried to install it and the build fails here (GHC 6.8.3)

$ cabal update
$ cabal install htags   

   ──(Mon,Nov03)─┘
Resolving dependencies...
Downloading htags-1.0...
Configuring htags-1.0...
Preprocessing executables for htags-1.0...
Building htags-1.0...

src/htags.hs:8:7:
Could not find module `GenTags':
  Use -v to see a list of the files searched for.
cabal: Error: some packages failed to install:
htags-1.0 failed during the building phase. The exception was:
exit: ExitFailure 1

Best regards,

-- 
Nicolas Pouillard aka Ertai
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell