[Haskell-cafe] ANNOUNCE: plat

2012-10-31 Thread Miguel Mitrofanov
My current project at work has a web interface. Therefore I needed an HTML 
templating library. I've tried several and found them all unsatisfactory. Most 
of them generate Haskell code from templates (with Template Haskell or a 
separate utility), and I don't like metaprogramming; and recompiling the 
program every time you make a small change in the template kinda defeats the 
purpose. Other libraries make it PITA to implement basic things, like iterating 
over an array. So, I'm proud to announce the first release of another template 
library: plat-0.1.0.1 (http://hackage.haskell.org/package/plat).

An example of what it does. If your data looks like

do name =: Mac's tools
   staff =: [
do index =: 1
   name =: Alice
,
do name =: Bob
   index =: 2
   bad =: True
,
do index =: 3
   name =: Nicolás
]

and your template is

List of employees at @name:
@staff[person
@person.index@.. @person.name@{@!person.bad (going to be fired)@|@}@
@]@# There won't be an empty line in the result

Then the result you get would be this:

List of employees at Mac's tools:
1. Alice
2. Bob (going to be fired)
3. Nicolás

Keep in mind, that it's actually a string template library, and the resulting 
string doesn't have to be valid HTML, or any HTML at all.

I haven't benchmarked this library - since I intended to use it for web 
interface in an program which won't be released outside, speed was not in my 
priorities; but I'll work on that in future versions.

Also, templates are supposed to be in UTF-8, as I've successfully forgot all 
about other encodings. So, if you want binary templates, I'm afraid, this 
library is not for you.

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


Re: [Haskell-cafe] ANNOUNCE: btree-concurrent

2012-10-31 Thread Johan Brinch
On Tue, Oct 30, 2012 at 10:09 PM, Alberto G. Corona agocor...@gmail.com wrote:
 how the IO and STM is managed?

STM and IO works in cooperation in a safe manner using the error
monad. Something like ErrorT (IO ()) STM, which means that either the
STM action will result in an IO action that needs to run (like reading
a node and storing it in the cache), or it will succeed with the
requested result (after some btree operation).

When the result is an error (with an IO action), the IO action is run
and the STM operation is retried, thus retrying the btree operation
until it has everything it needs and can succeed.


 The serialization- deserialization is
 automatic  or programmer must write the cached blocks?  (i suppose that the
 block reads are automatic on data requests).


The cereal package is used to automatic serialize and deserialize keys
and values. This makes for an easy-to-use API (just dump data in
there), but it also takes up performance, and requires a lot of memory
(pointers everywhere!).

I've considered changing the API to require bytestring keys and values
for simplicity.


 The state in the disk is coherent at every moment?. I mean, if there is a
 program failure, the state in the btree in the file would be coherent?

 For example, if I write two TVars in two different blocks within the same
 STM transaction, do I have the guarantee that either both updated values
 will be in the file storage or none of them  will be?

Well, STM is used internally, but it's not exposed. Thus, simple
operations (lookup, insert, modify) will run atomically and in
isolation, but they are not composable. They cannot be composed with
other STM operations or with each other. Saving to persistent storage
is done buttom-up to ensure integrity in case of a crash (the parent
is stored /after/ the nodes it is referencing).

I don't know whether composing tree-operations is possible somehow by
rewriting the operations, but composing with arbitrary STM operations
likely isn't due to the need for IO actions (if the node isn't in the
cache, it needs to be fetched from the external persistent storage).

Composing non-modifying or idempotent operations are theoretically
composable (like ensuring two keys are both present at the same time),
but non-idempotent operations are more difficult if not impossible due
to retrying.

-- 
Johan Brinch

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


[Haskell-cafe] Haskell User Group Hamburg (Germany) - Meeting Thursday November 8th 2012

2012-10-31 Thread Stefan Schmidt
Hello cafe,

there's an upcomming meeting of the Haskell user group Hamburg next week on
Thursday, November 8th.

We'll start 19:00 at the fortytools GmbH in Hamburg (Georgsplatz 10, 20099
Hamburg).

We don't have a program or talk yet. Maybe we'll discuss our experiences
from the last ICFP and the Haskell Symposium.

If you are interested to join us, have a look at our doodle (only in german)
http://www.doodle.com/gvdsbsyfz7a7427g

Be careful: the Google Maps link in the Doodle may direct you to the old
address. Georgsplatz 10, 20099 Hamburg is the new one.

Further announcements will be made via Twitter, so you may want to follow
https://twitter.com/hug_hh.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Looking for advice on modelling a 3-way merge (with varying strategies)

2012-10-31 Thread Oliver Charles
Hello,

I'm currently trying to implement a way 3 way merge, that is dispatched
on type. Essentially, I want to be able to say I have this large data
type which is a product of various other types - here's how to merge
it.

By 3 way merge, I mean that I have a 'new' value, a 'current' value and
a 'common ancestor' value. So far I have:

  import Control.Applicative
  import Data.Monoid

  newtype Merge a = Merge { runMerge :: Either [String] a }

  instance Functor Merge where
fmap f a = Merge $ fmap f $ runMerge a

  instance Applicative Merge where
pure = Merge . Right
(Merge (Right f)) * (Merge (Right a)) = Merge $ Right $ f a
(Merge (Right _)) * (Merge (Left c))  = Merge $ Left $ c
(Merge (Left c)) * (Merge (Left c'))  = Merge $ Left $ c  c'
(Merge (Left c)) * _  = Merge $ Left $ c

  ok :: a - Merge a
  ok = pure

  failMerge :: String - Merge a
  failMerge x = Merge $ Left [x]


So far so good, so I can add my first merge strategy:

  mergeEq :: Eq a = String - a - a - a - Merge a
  mergeEq lbl new current ancestor | current == new  = ok new
   | current == ancestor = ok new
   | new == ancestor = ok current
   | otherwise   = failMerge lbl


And we can make use of this to build more complicated merge strategies:

  data Person = Person { name :: String, surname :: String }
deriving (Show)

  mergeEqOn :: Eq a = (b - a) - String - b - b - b - Merge a
  mergeEqOn l lbl n c a = mergeEq lbl (l n) (l c) (l a)

  mergePerson :: Person - Person - Person - Merge Person
  mergePerson new current ancestor =
Person $ mergeEqOn name name new current ancestor
   * mergeEqOn surname surname new current ancestor


   runMerge $ mergePerson Person { name=Steve, surname=Bobman }
 Person { name=Joe,   surname=Obman }
 Person { name=oe,surname=Obman }
  Left [name]

   runMerge $ mergePerson Person { name=Steve, surname=Bobman }
 Person { name=Joe, surname=Obman }
 Person { name=Joe, surname=Obman }
  Right (Person {name = Steve, surname = Bobman})


Everything does exactly what I want, but it doesn't smell as good as I
expect from Haskell. Firstly, all my primitives or operations take 3
arguments that have to be threaded in a very specific pattern. If I
accidently call mergeEq ancestor current new, I've ran things in the
wrong order and I'm Gonna Have a Bad Time. So that's no good.

Secondly, is there a better way of labelled parts of a merge? I suspect
not, as at some point I need a human readable display, but I did wonder
about using a lens as a label, and then mapping lenses to human readable
names later -- but that will require a bit of newtyping in order to
provide the Eq instance, or maybe i make a HumanLens type which is a
lens and a name?).

Finally, I'm currently a little obsessed with the idea of building
applicatives from the composition or product of other applicatives - can
I use this trick here? I initially used 'Compose ((,) [String]) Maybe a'
but this means it's possible to have
([Conflicts], Just But success!), which is nonsense.

I'd love to hear your thoughts!

- ocharles

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


[Haskell-cafe] How to handle exceptions in conduit?

2012-10-31 Thread Hiromi ISHII
Hi, there

I'm writing a program communicating with external process, which can be 
sometimes fail, using conduit and process-conduit package.

Consider the following example, which reads paths from the config file, and 
passes their contents to external process, and output the results:

```exc.hs
module Main where
import qualified Data.ByteString.Char8 as BS
import   Data.Conduit
import qualified Data.Conduit.Binary   as BC
import qualified Data.Conduit.List as LC
import   Data.Conduit.Process

main :: IO ()
main = runResourceT $
  BC.sourceFile paths.dat $$ BC.lines =$= myConduit =$= LC.mapM_ 
(unsafeLiftIO . BS.putStrLn)

myConduit :: MonadResource m = Conduit BS.ByteString m BS.ByteString
myConduit = awaitForever $ \path -
  BC.sourceFile (BS.unpack path) =$= conduitCmd ./sometimes-fail
```

```sometimes-fail.hs
module Main where
import System.Random

main :: IO ()
main = do
  b - randomRIO (1,10 :: Int)
  if b  9 then interact id else error error!
```

```paths.dat
txt/a.dat
txt/b.dat
txt/c.dat
...bra, bra, bra...
```

As you can see, `sometimes-fail` is a simple echoing program, but sometimes 
fail at random.

Successful result is below:

```
$ ./exc
this is a!

this is b!

this is c!

this was d!

this was e!

and this is f.
```

but if `sometimes-fail` fails in some place, `exc` exits with exception like 
below:

```
$ ./exc
this is a!

this is b!

this is c!
sometimes-fail: error!
```

But I want to write the program acts like below:

```
$ ./exc
this is a!

this is b!

this is c!
sometimes-fail: error!
this was e!

and this is f.
```

that is, ignore the exception and continue to process remaining streams.

So, the question is: how to handle the exception in `myConduit` and proceed to 
remaining works?

In `conduit` package, `Pipe` type is not an instance of `MonadBaseControl IO` 
so it cannot handle exceptions within it.
I think this is necessary to make `ResourceT` release resources correctly.

So, how to write the Conduit that ignores some kind of exceptions and proceed 
to remaining works?
One sometimes want to ignore the invalid input and/or output and just continue 
to process the remaining stream.

One solution is that libraries using conduit provide failure-ignore version 
for all the `Pipe`s included in the library, but I think it is too heavy 
solution. It is ideal that `conduit` can package provides combinator that makes 
exsiting `Pipe`s failure-ignore.


-- Hiromi ISHII
konn.ji...@gmail.com




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