[Haskell-cafe] progress reporting in a backtracking algorithm

2012-09-21 Thread Harald Bögeholz
Dear Haskell Cafe,


I am playing around with a backtracking algorithm that can take quite a
while to compute all solutions to a problem.

I'd like to use Debug.Trace.trace to provisionally output something that
lets me estimate the total time it might take. But I just can't wrap my
head around it.

This is how I think I'd write it in a C-like language:

backtrack(int level, double position, double stepsize, misc...)
{
   // with variations = number of variations to try on this level
   double part = stepsize / variations // split time on this level

   for (i=0; ivariations; ++i)
   {
  double current = position + part*i
  // do the actual work
  backtrack(level+1, current, part);
  if (level  not_too_much_detail)
 printf(progress: %f%%\n, current);
   }
}

and start with backtrack(1, 0.0, 100.0).

And now for something completely Haskell:

I have a function

step :: State - Index - [State]

that on a certain level tries all allowable varaiants and returns a list
of those that can be further pursued on deeper levels.

Then solving the problem involves applying the step on all levels
(whicht are indexed by some array indices here):

solve :: Problem - [State]
solve problem = foldM step start grid
where start = stateFromProblem problem
  grid = indices (sLines start)

I am totally at loss at how I could accomplish some kind of progress
reporting in this lazily evaluated (I hope) backtracking scheme.

If anybody would like to review the full code (about 80 lines total vor
the solver, not counting I/O), this is where I am right now:

https://github.com/ctbo/slitherlink/tree/c8951ca1eaf83ce9de43f0483740ce339f4134ae

and this is the branch I am working on right now:

https://github.com/ctbo/slitherlink/tree/2lines

Or is there maybe a totally different and better way to approach this
kind of tree search in Haskell? I'm eager to learn.


Thanks for your attention
Harald

-- 
Harald Bögeholzb...@ct.de (PGP key available from servers)
Redaktion c't  Tel.: +49 511 5352-300  Fax: +49 511 5352-417
   http://www.ct.de/

   int f[9814],b,c=9814,g,i;long a=1e4,d,e,h;
   main(){for(;b=c,c-=14;i=printf(%04d,e+d/a),e=d%a)
   while(g=--b*2)d=h*b+a*(i?f[b]:a/5),h=d/--g,f[b]=d%g;}
  (Arndt/Haenel)

   Affe Apfel Vergaser

/* Heise Zeitschriften Verlag GmbH  Co. KG * Karl-Wiechert-Allee 10 *
   30625 Hannover * Registergericht: Amtsgericht Hannover HRA 26709 *
   Persönlich haftende Gesellschafterin: Heise Zeitschriften Verlag *
   Geschäftsführung GmbH * Registergericht: Amtsgericht Hannover, HRB
   60405 * Geschäftsführer: Ansgar Heise, Dr. Alfons Schräder */

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


Re: [Haskell-cafe] An easy way to represent and modify graphs?

2012-09-21 Thread Takayuki Muranushi
Yes Pointers. I've forgotten that. I have once dealt with structures,
with lots of IORefs.  It was smooth and fast. Thank you for reminding
me!

On the other hand, use of pointers means that our values are not
algebraic data type any more. We have to derive operations such as
map, fold, serialize by ourselves. I can do that, but am I right? Or
is there some systematic way to derive such operations?

Best regards,

Takayuki

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


Re: [Haskell-cafe] simple servers

2012-09-21 Thread Roman Cheplyaka
* Kazu Yamamoto k...@iij.ad.jp [2012-09-21 10:29:22+0900]
 Hello,
 
  Non-threaded RTS would block FFI to C code. But it does not block file
  descriptors and sockets because the scheduler uses select(). To my
  experience, *simple* network programming with non-threaded RTS also
  works well except the case where we reach the limit of file
  descriptors for the process.
 
 I need to correct the last sentence. It should be we reach the limit
 of select(), 1,024 file descriptors.

Most of the modern systems provide a better alternative to select
(epoll, kqueue etc.) which is used by the IO manager instead.
They don't have such a low limit.

Roman

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


Re: [Haskell-cafe] ANNOUNCE: uuid-1.2.6

2012-09-21 Thread Antoine Latter
On Fri, Sep 21, 2012 at 12:30 AM, David Fox dds...@gmail.com wrote:
 I was wondering about this:

   -- My goal with this instance was to make it work just enough to do what
   -- I want when used with the HStringTemplate library.
   instance Data UUID where
   toConstr uu  = mkConstr uuidType (show uu) [] (error fixity)
   gunfold _ _  = error gunfold
   dataTypeOf _ = uuidType

 Is there any reason not to just say deriving Data in the type declaration?


I didn't want my 'Data' instance to leak the details of the
constructor. Also I don't know much about how 'Data' works.

I think a similar conversation is going on about the Data declarations
in the 'containers' library.

Antoine

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


[Haskell-cafe] Question about type inference of a GADT term

2012-09-21 Thread Florian Lorenzen
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Hello cafe,

I have the following GADT definitions capturing the simply typed
lambda calculus with de Bruijn indices for variables and explicitly
annotated types for variables:


{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}

- -- Typing contexts
data Ctx = CtxNil
 | CtxCons Ctx Type

- -- Types
data Type = TyInt
  | TyArrow Type Type

- -- Variable indices
data Ix (ctx :: Ctx) (ty :: Type) where
  IxZero :: Ix ctx ty
  IxSucc :: Ix ctx ty1 - Ix (CtxCons ctx ty2) ty1

- -- Type representations
data TyRep (ty :: Type) where
  TyRepInt :: TyRep TyInt
  TyRepArrow :: TyRep ty1 - TyRep ty2 - TyRep (TyArrow ty1 ty2)

- -- Terms
data Term (ctx :: Ctx) (ty :: Type) where
  TmInt :: Integer - Term ctx TyInt
  TmVar :: Ix ctx ty - Term ctx ty
  TmAdd :: Term ctx TyInt - Term ctx TyInt - Term ctx TyInt
  TmApp :: Term ctx (TyArrow ty1 ty2) - Term ctx ty1 - Term ctx ty2
  TmAbs :: TyRep ty1 - Term (CtxCons ctx ty1) ty2
   - Term ctx (TyArrow ty1 ty2)

For the following definition

test1 = TmAbs TyRepInt (TmVar IxZero)

GHCi infers the type

test1 :: Term ctx (TyArrow 'TyInt ty2)

I was a bit puzzled because I expected

Term ctx (TyArrow TyInt TyInt)

Of course, this more special type is an instance of the inferred one,
so I can assign it by a type signature.

Can someone explain why the inferred type is more general?

Terms like

test2 = TmAbs TyRepInt (TmAdd (TmVar IxZero) (TmInt 5))

have the type I expected:

test2 :: Term ctx (TyArrow 'TyInt 'TyInt)


Thank you and best regards,

Florian


- -- 
Florian Lorenzen

Technische Universität Berlin
Fakultät IV - Elektrotechnik und Informatik
Übersetzerbau und Programmiersprachen

Sekr. TEL12-2, Ernst-Reuter-Platz 7, D-10587 Berlin

Tel.:   +49 (30) 314-24618
E-Mail: florian.loren...@tu-berlin.de
WWW:http://www.user.tu-berlin.de/florenz/
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://www.enigmail.net/

iEYEARECAAYFAlBcXs4ACgkQvjzICpVvX7b1WQCePiL+SFNj9X+U0V2fnykuatLX
pIcAn1VDNRiSR18s7UgctdPeNzFgStbi
=LBGb
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] [Snap] Argument Substitution in Heist Templates with Splices

2012-09-21 Thread MightyByte
This is one of the more subtle corner cases of Heist.  My default, splices
are recursively processed.  So when testSplice is executed for the test
tag, the results are fed back into splice processing.  I think this is the
right thing to do because it makes behavior less sensitive to evaluation
order.  Obviously this can lead to infinite recursion, so Heist limits the
splice call stack to a depth of 50.  If this limit is exceeded, then Heist
simply stops recursing and returns the nodes unprocessed.  I also think
this is the right thing to do because it is happening as we're serving a
page to the end user, so there's an argument for failing quietly instead of
going up in a ball of flames.

In your case, you are returning the same node that was spliced in, so you
are hitting the recursion limit and splice processing just stops.  I
discuss this issue in my blog post about splice subtleties (
http://softwaresimply.blogspot.com/2011/04/splice-subtleties.html).  Since
you're writing a filter splice, you need to call stopRecursion.  But if you
do that, then the child arg / tag won't be processed.  So what you need
to do is use the runChildren function to process the child nodes, then
return them in whatever your constructed node is.

I think the easiest solution to your problem is to not write it as a filter
splice.  Bind your testSplice function to the mytest tag and return a
test tag.  This avoids the infinite recursion and will work the way you
want without needing stopRecursion.

On Thu, Sep 20, 2012 at 3:00 PM, Sebastian Fischer m...@sebfisch.de wrote:

 Hello,

 the following program demonstrates that arguments in Heist templates
 are sometimes not substituted in presence of splices:

 {-# LANGUAGE OverloadedStrings #-}

 import   Blaze.ByteString.Builder (toByteString)
 import qualified Data.ByteString.Char8as BS
 import   Data.Functor (($))
 import   Data.Maybe   (fromJust)
 import   Text.Templating.Heist

 -- just return input node unchanged
 testSplice :: Splice IO
 testSplice = (:[]) $ getParamNode

 main = do
 writeFile test.tpl arg /test attr='${arg}'arg //test
 state - either error id $ loadTemplates . defaultHeistState

 (builder,_) - fromJust $ renderWithArgs [(arg,42)] state test
 BS.putStrLn $ toByteString builder
 -- 42test attr='42'42/test

 let state' = bindSplices [(test,testSplice)] state
 (builder',_) - fromJust $ renderWithArgs [(arg,42)] state'
 test
 BS.putStrLn $ toByteString builder'
 -- 42test attr='42'arg/arg/test

 Without using splices, all occurrences of 'arg' in the template are
 substituted. When using a splice, 'arg' is not substituted underneath
 the input node of the splice. It is substituted in an attribute of the
 input node.

 Is this intentional? How can I ensure substitution also underneath the
 input node?

 Best,
 Sebastian

 ___
 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] Passing CString array to Haskell shared library

2012-09-21 Thread Alexander Mumme
Hello everyone! Long time reader, first time poster.

Was wondering if someone could give me some direction or hints on how I 
might go about passing a CString array into an exported Haskell function.

What I'm trying to do is augment the RecordLinkage package from R using 
Haskell. Seems pretty straight forward. With some help from Neil Mitchell's 
excellent blog post on the subject (
http://neilmitchell.blogspot.com/2011/10/calling-haskell-from-r.html) I've 
managed to make calls into Haskell and utilize the Text.EditDistance 
package.

This is working rather well, except that I'm trying to calculate the edit 
distance from each of 3000 strings to each of 780,000 strings. Since I'm 
calling Haskell from R once for every comparison (and allocating a result 
record in R for each return) I find myself running out of memory rather 
quickly. What I'd like to do is send both complete string lists into 
Haskell to process, and have it pass me back a result vector.

Below is how I'm currently making the call using individual strings. I've 
tried looking through the GHC User's Guide, through the Wiki on usingthe 
FFI, and a number of other resources, but I seem to have come to an 
impasse. Could anyone lend some assistance?

- Code start -
{-# LANGUAGE ForeignFunctionInterface #-}
module Levenshtein where

import Foreign.C.Types
import Foreign.C.String
import Foreign.Ptr
import Foreign.Storable

import Text.EditDistance

levenshteinWeight :: Ptr Int - Ptr Int - Ptr Int - Ptr CString - 
Ptr CString - Ptr Int - IO ()
levenshteinWeight del ins subs str1 str2 result = do
del - peek del
ins - peek ins
subs - peek subs   
str1' - peekCString = peek str1
str2' - peekCString = peek str2
poke result $ levenshteinDistance EditCosts { deletionCosts = 
ConstantCost del, insertionCosts = ConstantCost ins, substitutionCosts = 
ConstantCost subs, transpositionCosts = ConstantCost 1} str1' str2'

foreign export ccall levenshteinWeight :: Ptr Int - Ptr Int - Ptr Int 
- Ptr CString - Ptr CString - Ptr Int - IO ()

- Code end   -

Thanks in Advance!
Alex___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Question about type inference of a GADT term

2012-09-21 Thread Daniel Peebles
Shouldn't you have

IxZero :: Ix (CtxCons ty ctx) ty

instead of

IxZero :: Ix ctx ty


On Fri, Sep 21, 2012 at 8:34 AM, Florian Lorenzen 
florian.loren...@tu-berlin.de wrote:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1

 Hello cafe,

 I have the following GADT definitions capturing the simply typed
 lambda calculus with de Bruijn indices for variables and explicitly
 annotated types for variables:


 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE DataKinds #-}

 - -- Typing contexts
 data Ctx = CtxNil
  | CtxCons Ctx Type

 - -- Types
 data Type = TyInt
   | TyArrow Type Type

 - -- Variable indices
 data Ix (ctx :: Ctx) (ty :: Type) where
   IxZero :: Ix ctx ty
   IxSucc :: Ix ctx ty1 - Ix (CtxCons ctx ty2) ty1

 - -- Type representations
 data TyRep (ty :: Type) where
   TyRepInt :: TyRep TyInt
   TyRepArrow :: TyRep ty1 - TyRep ty2 - TyRep (TyArrow ty1 ty2)

 - -- Terms
 data Term (ctx :: Ctx) (ty :: Type) where
   TmInt :: Integer - Term ctx TyInt
   TmVar :: Ix ctx ty - Term ctx ty
   TmAdd :: Term ctx TyInt - Term ctx TyInt - Term ctx TyInt
   TmApp :: Term ctx (TyArrow ty1 ty2) - Term ctx ty1 - Term ctx ty2
   TmAbs :: TyRep ty1 - Term (CtxCons ctx ty1) ty2
- Term ctx (TyArrow ty1 ty2)

 For the following definition

 test1 = TmAbs TyRepInt (TmVar IxZero)

 GHCi infers the type

 test1 :: Term ctx (TyArrow 'TyInt ty2)

 I was a bit puzzled because I expected

 Term ctx (TyArrow TyInt TyInt)

 Of course, this more special type is an instance of the inferred one,
 so I can assign it by a type signature.

 Can someone explain why the inferred type is more general?

 Terms like

 test2 = TmAbs TyRepInt (TmAdd (TmVar IxZero) (TmInt 5))

 have the type I expected:

 test2 :: Term ctx (TyArrow 'TyInt 'TyInt)


 Thank you and best regards,

 Florian


 - --
 Florian Lorenzen

 Technische Universität Berlin
 Fakultät IV - Elektrotechnik und Informatik
 Übersetzerbau und Programmiersprachen

 Sekr. TEL12-2, Ernst-Reuter-Platz 7, D-10587 Berlin

 Tel.:   +49 (30) 314-24618
 E-Mail: florian.loren...@tu-berlin.de
 WWW:http://www.user.tu-berlin.de/florenz/
 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.11 (GNU/Linux)
 Comment: Using GnuPG with Mozilla - http://www.enigmail.net/

 iEYEARECAAYFAlBcXs4ACgkQvjzICpVvX7b1WQCePiL+SFNj9X+U0V2fnykuatLX
 pIcAn1VDNRiSR18s7UgctdPeNzFgStbi
 =LBGb
 -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