Re: [Haskell-cafe] hoogle command line program on Linux

2011-01-09 Thread Neil Mitchell
Hi Erik,

> The next problem is that hoogle installed as a Debian package would
> install as root as /usr/bin/hoogle. Then, when I run "hoogle data" it
> wants to install the database at /usr/share/hoogle/hoogle-4.1.3/databases
> which fails because I'm not running as root. So, to install the databases
> I need to run "sudo hoogle data" (which is acceptable), but then an
> unprivelidge user can't run hoogle because they don't have read permission
> on the database.
>
> The solution would be to set the umask before writing the databases.
> Something like (untested):
>
>    import System.Posx
>
>
>    -- Set umask to world read/execute. Save old umask for
>    -- restoration later.
>    oldumask <- setFileCreationMask 0o022

Should all files created by hoogle data always have world
read/execute? I'm not sure what the Unix conventions are - would that
be reasonable? If so, I'll make a new release that just changes the
file creation mask to the above during hoogle data (and sets it back
after).

Thanks, Neil

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


[Haskell-cafe] Draw K-ary forest in dot script

2011-01-09 Thread larry.liuxinyu
Hi,

I wrote a Haskell program to parse K-ary forest and convert it to dot script 
(Graphviz).

Here is the literate program.

-- First is some stuff imported:
module Main where

import System.Environment (getArgs)
import Text.ParserCombinators.Parsec
import Control.Monad (mapM_)
import Data.List (concatMap, intercalate)
import System.IO (writeFile)
import Data.Char (isSpace)

-- For each tree in the forest, it is described in pre-order.
-- Example description string of a forest of CLRS[1] Figure 19.5(a):
--   (12), (7, (25)), (15, (28, (41)), (33))

-- Definition of K-ary node
data Node a = Node { root :: a 
   , children :: [Node a]} deriving (Eq, Show)

-- Definition of Forest
type Forest a = [Node a]


-- parsers

-- a forest is a list of trees separate by ','
forest = do 
  ts <- node `sepBy` (char ',')
  return ts

-- a node contains a key then followed by a children forest or nothing (leaf 
case)
node = do
  char '('
  elem <- key
  ts <- (try (char ',')>>forest) <|> return []
  char ')'
  return (Node elem ts)

-- a key is just a plain literate string.
key = many (noneOf ",()")

-- Command line arguments handling
parseArgs :: [String] -> (String, String)
parseArgs [fname, s] = (fname, s)
parseArgs _ = error "wrong usage\nexample:\nfr2dot output.dot \"(12), (7, 
(25)), (15, ((28, (41)), 33))\""


-- A simplified function to generate dot script from parsed result.
toDot f = forestToDot f "t" True

-- a handy function to convert children of a K-ary tree to dot script
treesToDot ts prefix = forestToDot ts prefix False

-- convert a forest to dot script
forestToDot []  _ _ = ""
forestToDot [t] prefix _ = nodeToDot t prefix
forestToDot ts@(_:_:_) prefix lnk = 
(concatMap (\t->nodeToDot t prefix) ts) ++ consRoot
where
  consRoot = "{rank=same " ++ ns ++ vis ++ "}\n" 
  ns = intercalate "->" $ map (\t -> prefix ++ root t) ts
  vis = if lnk then "" else "[style=invis]"


-- convert a node to dot script
nodeToDot (Node x ts) prefix = 
prefix'++"[label=\""++x++"\"];\n" ++
(treesToDot ts prefix') ++
(defCons ts prefix')
where prefix' = prefix ++ x

-- define connections among nodes in dot format
defCons ts prefix = concatMap f ts where
f (Node x _) = prefix++"->"++prefix++x++";\n"

-- generate dot script from a parsed forest
genDot fname (Right f) = writeFile fname dots >> putStrLn dots
where
  dots = "digraph G{\n\tnode[shape=circle]\n"++(addTab $ toDot f)++"}"
  addTab s = unlines $ map ("\t"++) (lines s)

main = do
  args <- getArgs
  let (fname, s) = parseArgs args
  genDot fname (parse forest "unknown" (filter (not.isSpace) s))

-- END

I tested with the following simple cases:
./fr2dot foo.dot "(12), (7, (25)), (15, (28, (41)), (33))"
./fr2dot bar.dot "(18), (3, (37)), (6, (8, (30, (45, (55)), (32)), (23, 
(24)), (22)), (29, (48, (50)), (31)), (10, (17)), (44))"

Run the following commands can convert to PNG files:
./dot -Tpng -o foo.png foo.dot
./dot -Tpng -o bar.png bar.dot

Reference:

[1]. Thomas H. Cormen, Charles E. Leiserson, Ronald L. Rivest and Clifford 
Stein. ``Introduction to Algorithms, Second Edition''. The MIT Press, 2001. 
ISBN: 0262032937.

Best regards.
--
Larry, LIU
https://sites.google.com/site/algoxy/home
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to write such a code elegantly ?

2011-01-09 Thread z_axis

rollDice n = do 
tmp <- doesFileExist "/dev/urandom" 
myGen <- if tmp
then betterStdGen
else (mkStdGen . fromInteger) <$> picoSec 

return $ (take 1 $ randomRs (1,n) myGen) !! 0

works but not so elegant?

-
e^(π.i) + 1 = 0
-- 
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-write-such-a-code-elegantly-tp3334329p3334395.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Antoine Latter
On Sun, Jan 9, 2011 at 8:11 PM, Aaron Gray  wrote:
> On 10 January 2011 01:08, Antoine Latter  wrote:
>>
>> Although the 24-bit access might be difficult - how are they aligned?
>>
>
> They are non aligned, they are actually used as jump offsets in the byte
> code.
>

Hah hah, yes. That would make a lot more sense.

>>
>> I guess with either of these you'd have to peek a Word8 and then a
>> Word16 and then munge them together, depending.
>
> Three put/getWord8's would probably be neater.
>>
>> http://hackage.haskell.org/package/binary
>> http://hackage.haskell.org/package/blaze-builder
>
> Blaze looks a bit more specialized.

It has a larger surface area and more types, so it can be
intimidating, but it has the module 'Blaze.ByteString.Builder.Word'
which is an idealogical equivalent to the word primitives in
Data.Binary.Builder.

Antoine

> Many thanks,
> Aaron
>

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


Re: [Haskell-cafe] How to write such a code elegantly ?

2011-01-09 Thread Ivan Lazar Miljenovic
On 10 January 2011 12:25, z_axis  wrote:
>
> thanks for all of your replies.  I will test your code later. Another newbie
> question is why has the following code indentation problem ?
>
> rollDice n = do
>    let myGen =
>        if doesFileExist "/dev/urandom"
>            then betterStdGen
>            else (mkStdGen . fromInteger) <$> picoSec
>    return $ (take 1 $ randomRs (1,n) myGen) !! 0

I don't see an indentation problem, but I _do_ see a type problem:
doesFileExist presumably uses IO, and as such can't be used as a Bool
for the if statement.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] How to write such a code elegantly ?

2011-01-09 Thread z_axis

thanks for all of your replies.  I will test your code later. Another newbie
question is why has the following code indentation problem ?

rollDice n = do
let myGen =
if doesFileExist "/dev/urandom" 
then betterStdGen
else (mkStdGen . fromInteger) <$> picoSec
return $ (take 1 $ randomRs (1,n) myGen) !! 0


Sincerely!

-
e^(π.i) + 1 = 0
-- 
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-write-such-a-code-elegantly-tp3334329p3334379.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] How to write such a code elegantly ?

2011-01-09 Thread Ertugrul Soeylemez
z_axis  wrote:

> betterStdGen :: IO StdGen
> betterStdGen = alloca $ \p -> do
>h <- openBinaryFile "/dev/urandom" ReadMode
>hGetBuf h p $ sizeOf (undefined :: Int)
>hClose h
>mkStdGen <$> peek p
>
> picoSec :: IO Integer
> picoSec = do
> t <- ctPicosec `liftM` (getClockTime >>= toCalendarTime)
> return t
>
> The pseudo-code is :
>
> if doesFileExist "/dev/urandom"
> then myGen = betterStdGen
> else myGen = (mkStdGen . fromTnteger) <$> picoSec
>
> How to write these pseudo-code elegantly ?

I would do this:

  {-# LANGUAGE ScopedTypeVariables #-}

  readFrom :: forall a. Storable a => Handle -> IO a
  readFrom h =
alloca $ \ptr ->
  hGetBuf h ptr (sizeOf (undefined :: a)) >>
  peek ptr

  newStdGen' :: IO StdGen
  newStdGen' = do
mh <- try $ openBinaryFile "/dev/urandom" ReadMode
case mh of
  Left err -> ctPicosec <$> (getClockTime >>= toCalendarTime)
  Right h  -> mkStdGen <$> readFrom h `finally` hClose h

Warning: Untested code, but it should work and have a safer file
handling.  Also note that the current implementation (base >= 4) does
this already.

You should probably try one of the more sophisticated PRNG libraries out
there.  Check out mersenne-random and mwc-random.  If you want a pure
generator, there is also mersenne-random-pure64 and some other
libraries.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Aaron Gray
On 10 January 2011 01:08, Antoine Latter  wrote:

> On Sun, Jan 9, 2011 at 6:05 PM, Aaron Gray 
> wrote:
> > On 9 January 2011 21:30, Henning Thielemann <
> lemm...@henning-thielemann.de>
> > wrote:
> >>
> >> On Sun, 9 Jan 2011, Aaron Gray wrote:
> >>
> >>> I am trying to work out how to use GHC.Ptr, Foreign.Storable,
> >>> Data.Storable.Endian, and
> >>> am looking for good examples of usage.
> >>
> >> What do you intend to do with them?
> >>
> >
> > An (ABC) ActionScript Byte Code backend for Haskell.
> > Basically I need to write little-endian binary to a file, and was
> wondering
> > the best way to do this; I need various types including a 24bit type.
> >
>
> Ah, I would recommend the 'binary' package on hackage, specifically
> the module Data.Binary.Builder. Another recently popular alternative
> is the 'blaze-builder' package.
>

It does say that it is designed to work with bigendian data, but there are
some little-endian primatives in Data.Binary.Get/Put


> Although the 24-bit access might be difficult - how are they aligned?
>
>
They are non aligned, they are actually used as jump offsets in the byte
code.


> I guess with either of these you'd have to peek a Word8 and then a
> Word16 and then munge them together, depending.
>

Three put/getWord8's would probably be neater.


> http://hackage.haskell.org/package/binary
> http://hackage.haskell.org/package/blaze-builder


Blaze looks a bit more specialized.

Many thanks,

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Antoine Latter
On Sun, Jan 9, 2011 at 6:05 PM, Aaron Gray  wrote:
> On 9 January 2011 21:30, Henning Thielemann 
> wrote:
>>
>> On Sun, 9 Jan 2011, Aaron Gray wrote:
>>
>>> I am trying to work out how to use GHC.Ptr, Foreign.Storable,
>>> Data.Storable.Endian, and
>>> am looking for good examples of usage.
>>
>> What do you intend to do with them?
>>
>
> An (ABC) ActionScript Byte Code backend for Haskell.
> Basically I need to write little-endian binary to a file, and was wondering
> the best way to do this; I need various types including a 24bit type.
>

Ah, I would recommend the 'binary' package on hackage, specifically
the module Data.Binary.Builder. Another recently popular alternative
is the 'blaze-builder' package.

Although the 24-bit access might be difficult - how are they aligned?

I guess with either of these you'd have to peek a Word8 and then a
Word16 and then munge them together, depending.

Antoine

http://hackage.haskell.org/package/binary
http://hackage.haskell.org/package/blaze-builder

>>
>> The package storablevector uses a lot of Ptr, peek, and poke. Maybe this
>> is of some help.
>
> Okay thanks,
> Aaron
>
>
> ___
> 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


Re: [Haskell-cafe] How to write such a code elegantly ?

2011-01-09 Thread Ivan Lazar Miljenovic
On 10 January 2011 10:44, z_axis  wrote:
>
> betterStdGen :: IO StdGen
> betterStdGen = alloca $ \p -> do
>   h <- openBinaryFile "/dev/urandom" ReadMode
>   hGetBuf h p $ sizeOf (undefined :: Int)
>   hClose h
>   mkStdGen <$> peek p

Maybe use a catch or something here and have it return "IO (Maybe
StdGen)", with Nothing denoting that file not existing?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


[Haskell-cafe] How to write such a code elegantly ?

2011-01-09 Thread z_axis

betterStdGen :: IO StdGen
betterStdGen = alloca $ \p -> do
   h <- openBinaryFile "/dev/urandom" ReadMode
   hGetBuf h p $ sizeOf (undefined :: Int)
   hClose h
   mkStdGen <$> peek p

picoSec :: IO Integer
picoSec = do
t <- ctPicosec `liftM` (getClockTime >>= toCalendarTime)
return t

The pseudo-code is :

if doesFileExist "/dev/urandom" 
then myGen = betterStdGen
else myGen = (mkStdGen . fromTnteger) <$> picoSec

How to write these pseudo-code elegantly ?

Sincerely!

-
e^(π.i) + 1 = 0
-- 
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-write-such-a-code-elegantly-tp3334329p3334329.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Aaron Gray
On 9 January 2011 21:30, Henning Thielemann
wrote:

>
> On Sun, 9 Jan 2011, Aaron Gray wrote:
>
>  I am trying to work out how to use GHC.Ptr, Foreign.Storable,
>> Data.Storable.Endian, and
>> am looking for good examples of usage.
>>
>
> What do you intend to do with them?
>
>
An (ABC) ActionScript Byte Code backend for Haskell.

Basically I need to write little-endian binary to a file, and was wondering
the best way to do this; I need various types including a 24bit type.


> The package storablevector uses a lot of Ptr, peek, and poke. Maybe this is
> of some help.
>

Okay thanks,

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Aaron Gray
On 9 January 2011 22:34, Henk-Jan van Tuyl  wrote:

> On Sun, 09 Jan 2011 14:48:09 +0100, Aaron Gray 
> wrote:
>
>  Hi,
>>
>> I am trying to work out how to use GHC.Ptr, Foreign.Storable,
>> Data.Storable.Endian, and am looking for good examples of usage.
>>
>> Many thanks in advance,
>>
>> Aaron
>>
>
> You can lookup, which packages use these, by looking at the reverse
> dependencies:
>
> http://bifunctor.homelinux.net/~roel/hackage/packages/archive/pkg-list.html
>
> Handy I did not notice that, nice.

Thanks,

Aaron



> Regards,
> Henk-Jan van Tuyl
>
>
> --
> http://Van.Tuyl.eu/
> http://members.chello.nl/hjgtuyl/tourdemonad.html
> --
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Henk-Jan van Tuyl
On Sun, 09 Jan 2011 14:48:09 +0100, Aaron Gray  
 wrote:



Hi,

I am trying to work out how to use GHC.Ptr, Foreign.Storable,
Data.Storable.Endian, and am looking for good examples of usage.

Many thanks in advance,

Aaron


You can lookup, which packages use these, by looking at the reverse  
dependencies:

  http://bifunctor.homelinux.net/~roel/hackage/packages/archive/pkg-list.html

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Henning Thielemann


On Sun, 9 Jan 2011, Aaron Gray wrote:


I am trying to work out how to use GHC.Ptr, Foreign.Storable, 
Data.Storable.Endian, and
am looking for good examples of usage.


What do you intend to do with them?

The package storablevector uses a lot of Ptr, peek, and poke. Maybe this 
is of some help.


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


Re: [Haskell-cafe] web-routes and forms

2011-01-09 Thread Corentin Dupont
Hello,
after installing digestive-functors-blaze with:
cabal install digestive-functors-blaze

My prog doesn't compiles anymore:
Warning: This package indirectly depends on multiple versions of the same
package. This is highly likely to cause a compile failure.
Followed by an error on MonadCatchIO.


I'm using the following versions:
happstack-server-0.5.0.2
mtl-1.1.0.2
blaze-html-0.2.3
web-routes-0.22.0
text-0.7.2.1

But cabal tried to install newer versions for these:
mtl-2.0.1.0
blaze-html-0.3.2.1
text-0.11.0.1

I already add this problem in the past, when I tried to update my MTL...
With absolutely no success!!
I encountered the same sort of problem of multiple versions dependencies. I
was unable to solve it.

After some research, I followed an advise telling that you should stick with
the same version of the libraries during development, so that I did: I went
back to the previous versions.

Is there a safe way to update some base libraries like MTL and all depending
libraries?
Would I be able to use digestive-functors with my current set of libraries?

Thanks,
Corentin


On Sun, Jan 9, 2011 at 8:36 PM, Jeremy Shaw  wrote:

> Hello,
>
> newRule also needs to have the type, RoutedNomicServer. The
> transformation of RoutedNomicServer into NomicServer is done in the
> handleSite function. Something like this:
>
>
> nomicSpec :: ServerHandle -> Site Route (ServerPartT IO Response)
> nomicSpec sh =
>  Site { handleSite  = \f url -> unRouteT (nomicSite sh url) f
> ...
>
> main =
>do ...
>  simpleHTTP nullConf $ siteImpl (nomicSpec sh)
>
> Or something like that -- it's hard to tell exactly what is going on
> in your app based on the snippets you provided.
>
> Also, I highly recommend using digestive functors instead of formlets.
> It is the successor to formlets. Same core idea, better implementation
> and actively maintained.
>
> I have attached a quick demo of using:
>
> happstack+digestive-functors+web-routes+HSP
>
> To use it you will need the latest happstack from darcs plus:
>
>  hsp
>  web-routes
>  web-routes-hsp
>  web-routes-happstack
>  web-routes-mtl
>  digestive-functors
>  digestive-functors-hsp
>
> I plan to clean up this example and document it better in the crash
> course for the upcoming release. Clearly things like the FormInput
> instance and the formPart function belong a library.
>
> let me know if you have more questions.
> - jeremy
>
> On Sat, Jan 8, 2011 at 6:44 PM, Corentin Dupont
>  wrote:
> > Hello,
> >
> > I have difficulties mixing web-routes and forms:
> > I have put routes in all my site, except for forms which remains with the
> > type ServerPartT IO Response.
> > How to make them work together?
> >
> > I have:
> > type NomicServer = ServerPartT IO
> > type RoutedNomicServer = RouteT PlayerCommand NomicServer
> >
> > newRule :: ServerHandle -> NomicServer Response
> > newRule sh = do
> >methodM POST -- only accept a post method
> >mbEntry <- getData -- get the data
> >case mbEntry of
> >   Nothing -> error $ "error: newRule"
> >   Just (NewRule name text code pn) -> do
> >  html <- nomicPageComm pn sh (submitRule name text code pn))
> >  ok $ toResponse html
> >
> >
> > nomicPageComm :: PlayerNumber -> ServerHandle -> Comm () ->
> > RoutedNomicServer Html
> > nomicPageComm pn sh comm =
> > (..)
> >
> >
> > launchWebServer :: ServerHandle -> IO ()
> > launchWebServer sh = do
> >putStrLn "Starting web server...\nTo connect, drive your browser to
> > \"http://localhost:8000/Login\ ""
> >d <- liftIO getDataDir
> >simpleHTTP nullConf $ mconcat [dir "postLogin" $ postLogin,
> >   fileServe [] d,
> >   dir "Login" $ ok $ toResponse $
> loginPage,
> >   dir "NewRule" $ newRule sh,
> >   dir "NewGame" $ newGameWeb sh,
> >   dir "Nomic" $ do
> >  html <- implSite
> > "http://localhost:8000/Nomic/"; "" (nomicSite sh)
> >  ok $ toResponse html
> >   ]
> >
> >
> > The red line doesn't compile. I don't know how to transform a
> > RoutedNomicServer into a NomicServer.
> >
> > For the future I intend to use formlets: is these some examples of
> programs
> > using happstack + web-routes + formlets?
> >
> > Thanks,
> > Corentin
> >
> >
> >
> >
> > On Fri, Jan 7, 2011 at 5:10 PM, Jeremy Shaw 
> wrote:
> >>
> >> Hello,
> >>
> >> The [(String, String)] argument is for adding query parameters.
> >>
> >> > encodePathInfo ["foo", "bar", "baz"] [("key","value")]
> >>
> >> "foo/bar/baz?key=value"
> >>
> >> Instead of showURL you would use showURLParams.
> >>
> >> hope this helps!d
> >> - jeremy
> >>
> >> On Fri, Jan 7, 2011 at 8:12 AM, Corentin Dupont
> >>  wrote:
> >> > Hello Jeremy,
> >> > I'm using Web routes with ha

Re: [Haskell-cafe] hoogle command line program on Linux

2011-01-09 Thread Erik de Castro Lopo
Neil Mitchell wrote:

> Hoogle 4.1.3 is now released, which reads and writes Hoogle input
> files in UTF8 throughout. Please let me know if this doesn't fix your
> problem.

Thanks Neil for the quick response. That definitely has fixed thet
problem.

The next problem is that hoogle installed as a Debian package would
install as root as /usr/bin/hoogle. Then, when I run "hoogle data" it
wants to install the database at /usr/share/hoogle/hoogle-4.1.3/databases
which fails because I'm not running as root. So, to install the databases
I need to run "sudo hoogle data" (which is acceptable), but then an
unprivelidge user can't run hoogle because they don't have read permission
on the database.

The solution would be to set the umask before writing the databases.
Something like (untested):

import System.Posx


-- Set umask to world read/execute. Save old umask for
-- restoration later.
oldumask <- setFileCreationMask 0o022


If you need help with this, let me know.

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

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


Re: [Haskell-cafe] web-routes and forms

2011-01-09 Thread Jeremy Shaw
Hello,

newRule also needs to have the type, RoutedNomicServer. The
transformation of RoutedNomicServer into NomicServer is done in the
handleSite function. Something like this:


nomicSpec :: ServerHandle -> Site Route (ServerPartT IO Response)
nomicSpec sh =
  Site { handleSite  = \f url -> unRouteT (nomicSite sh url) f
 ...

main =
do ...
  simpleHTTP nullConf $ siteImpl (nomicSpec sh)

Or something like that -- it's hard to tell exactly what is going on
in your app based on the snippets you provided.

Also, I highly recommend using digestive functors instead of formlets.
It is the successor to formlets. Same core idea, better implementation
and actively maintained.

I have attached a quick demo of using:

happstack+digestive-functors+web-routes+HSP

To use it you will need the latest happstack from darcs plus:

 hsp
 web-routes
 web-routes-hsp
 web-routes-happstack
 web-routes-mtl
 digestive-functors
 digestive-functors-hsp

I plan to clean up this example and document it better in the crash
course for the upcoming release. Clearly things like the FormInput
instance and the formPart function belong a library.

let me know if you have more questions.
- jeremy

On Sat, Jan 8, 2011 at 6:44 PM, Corentin Dupont
 wrote:
> Hello,
>
> I have difficulties mixing web-routes and forms:
> I have put routes in all my site, except for forms which remains with the
> type ServerPartT IO Response.
> How to make them work together?
>
> I have:
> type NomicServer         = ServerPartT IO
> type RoutedNomicServer = RouteT PlayerCommand NomicServer
>
> newRule :: ServerHandle -> NomicServer Response
> newRule sh = do
>    methodM POST -- only accept a post method
>    mbEntry <- getData -- get the data
>    case mbEntry of
>   Nothing -> error $ "error: newRule"
>   Just (NewRule name text code pn) -> do
>  html <- nomicPageComm pn sh (submitRule name text code pn))
>  ok $ toResponse html
>
>
> nomicPageComm :: PlayerNumber -> ServerHandle -> Comm () ->
> RoutedNomicServer Html
> nomicPageComm pn sh comm =
> (..)
>
>
> launchWebServer :: ServerHandle -> IO ()
> launchWebServer sh = do
>    putStrLn "Starting web server...\nTo connect, drive your browser to
> \"http://localhost:8000/Login\"";
>    d <- liftIO getDataDir
>    simpleHTTP nullConf $ mconcat [dir "postLogin" $ postLogin,
>   fileServe [] d,
>   dir "Login" $ ok $ toResponse $ loginPage,
>   dir "NewRule" $ newRule sh,
>   dir "NewGame" $ newGameWeb sh,
>   dir "Nomic" $ do
>  html <- implSite
> "http://localhost:8000/Nomic/"; "" (nomicSite sh)
>  ok $ toResponse html
>   ]
>
>
> The red line doesn't compile. I don't know how to transform a
> RoutedNomicServer into a NomicServer.
>
> For the future I intend to use formlets: is these some examples of programs
> using happstack + web-routes + formlets?
>
> Thanks,
> Corentin
>
>
>
>
> On Fri, Jan 7, 2011 at 5:10 PM, Jeremy Shaw  wrote:
>>
>> Hello,
>>
>> The [(String, String)] argument is for adding query parameters.
>>
>> > encodePathInfo ["foo", "bar", "baz"] [("key","value")]
>>
>> "foo/bar/baz?key=value"
>>
>> Instead of showURL you would use showURLParams.
>>
>> hope this helps!d
>> - jeremy
>>
>> On Fri, Jan 7, 2011 at 8:12 AM, Corentin Dupont
>>  wrote:
>> > Hello Jeremy,
>> > I'm using Web routes with happstack.
>> > I'm following this tutorial:
>> > http://tutorialpedia.org/tutorials/Happstack+type+safe+URLs.html
>> >
>> > But It seems out of synch with the latest version of web-routes: 0.23.2.
>> > The haddock documentation seems out of date also:
>> >
>> > encodePathInfo :: [String] -> [(String, String)] -> String
>> >
>> > For example:
>> >
>> >  encodePathInfo [\"foo\", \"bar\", \"baz\"]
>> >
>> > "foo/bar/baz"
>> >
>> > And I can't figure out what this [(String, String)] is for ;)
>> >
>> > Thanks,
>> >
>> > Corentin
>> >
>
>
{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances, PackageImports, MultiParamTypeClasses, TemplateHaskell #-}
{-# OPTIONS_GHC -F -pgmFtrhsx #-}
module Main where

import Control.Applicative(Applicative((<*>)), (<*), Alternative, (<$>), optional)
import Control.Monad  (MonadPlus(mzero), msum)
import Control.Monad.Trans(MonadIO(liftIO))
import Data.ByteString.Lazy   as LB (ByteString)
import Data.ByteString.Lazy.UTF8  as LB (toString)
import Data.Data  (Data)
import qualified Data.Textas T
import   Data.Text(Text)
import qualified Data.Text.Lazy   as TL
import qualified Data.Text.Lazy.Encoding as TL
import Data.Typeable  (Typeable)
import Happstack.Server   ( HasRqData, Input(..), FilterMonad, Method(GET, HEAD, POST), Response
  

Re: [Haskell-cafe] ANN: nanoparsec 0.1

2011-01-09 Thread Magnus Therning
On 09/01/11 00:46, Maciej Piechotka wrote:
> Nanoparsec is currently simply a port of attoparsec on the ListLike (the
> abstraction of lists used by iteratee).
> 
> It allows to achive in parsing a near-attoparsec levels of speed
> (benchmarks from attoparsec library shown a 0.450 ± 0.028 for
> attoparsec, 0.479 ± 0.043 for nanoparsec and 1.532 ± 0.084 for parsec 3)
> combining the flexibility of stream of parsec 3 with the iterative
> approach and speed of attoparsec.

It's a bit unfortunate that it requires base 4.3, GHC 7 hasn't made it
into a lot of distros yet so that causes a lot of extra work when
wanting to try it out :-(

/M

-- 
Magnus Therning  OpenPGP: 0xAB4DFBA4
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe   http://therning.org/magnus



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell-beginners] theStdGen unsafePerformIO

2011-01-09 Thread Antoine Latter
You might get more answers to this sort of question on the
haskell-cafe list. Even there, I think you might need to ask whoever
the authors were for a question like this :-)

On Sun, Jan 9, 2011 at 9:55 AM, John Smith  wrote:
> Why does theStdGen require unsafePerformIO? I recompiled the Random module
> with
>
> theStdGen :: IO (IORef StdGen)
> theStdGen  = do
>                rng <- mkStdRNG 0
>                newIORef rng
>
> The implementations of a few functions needed to change slightly (to extract
> the IORef from IO), but no other type signatures needed changing, and
> nothing blew up.
>
>
> ___
> Beginners mailing list
> beginn...@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>

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


[Haskell-cafe] ANNOUNCE: Monad.Reader Issue 17

2011-01-09 Thread Brent Yorgey
I am pleased to announce that Issue 17 of The Monad.Reader is now
available [1].

Issue 17 consists of the following three articles:

  * List Leads Off with the Letter Lambda by Douglas M. Auclair
  * The InterleaveT Abstraction: Alternative with Flexible Ordering by
Neil Brown
  * The Reader Monad and Abstraction Elimination by Petr Pudlak

Feel free to browse the source files [2]. You can check out the entire
repository using darcs:

  darcs get http://code.haskell.org/~byorgey/TMR/Issue17

Watch for a special announcement regarding Issue 18 soon!

[1] http://themonadreader.files.wordpress.com/2011/01/issue17.pdf
[2] http://code.haskell.org/~byorgey/TMR/Issue17

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


[Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-09 Thread Aaron Gray
Hi,

I am trying to work out how to use GHC.Ptr, Foreign.Storable,
Data.Storable.Endian, and am looking for good examples of usage.

Many thanks in advance,

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


Re: [Haskell-cafe] Set monad

2011-01-09 Thread Lennart Augustsson
That looks like it looses the efficiency of the underlying representation.

On Sun, Jan 9, 2011 at 6:45 AM, Sebastian Fischer  wrote:

> On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson  > wrote:
>
>> It so happens that you can make a set data type that is a Monad, but it's
>> not exactly the best possible sets.
>>
>> module SetMonad where
>>
>> newtype Set a = Set { unSet :: [a] }
>>
>
> Here is a version that also does not require restricted monads but works
> with an arbitrary underlying Set data type (e.g. from Data.Set). It uses
> continuations with a Rank2Type.
>
> import qualified Data.Set as S
>
> newtype Set a = Set { (>>-) :: forall b . Ord b => (a -> S.Set b) ->
> S.Set b }
>
> instance Monad Set where
>   return x = Set ($x)
>   a >>= f  = Set (\k -> a >>- \x -> f x >>- k)
>
> Only conversion to the underlying Set type requires an Ord constraint.
>
> getSet :: Ord a => Set a -> S.Set a
> getSet a = a >>- S.singleton
>
> A `MonadPlus` instance can lift `empty` and `union`.
>
> instance MonadPlus Set where
>   mzero = Set (const S.empty)
>   mplus a b = Set (\k -> S.union (a >>- k) (b >>- k))
>
> Maybe, Heinrich Apfelmus's operational package [1] can be used to do the
> same without continuations.
>
> [1]: http://projects.haskell.org/operational/
>
> ___
> 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


Re: [Haskell-cafe] Set monad

2011-01-09 Thread Andrea Vezzosi
On Sun, Jan 9, 2011 at 7:45 AM, Sebastian Fischer  wrote:
> [...]
> Only conversion to the underlying Set type requires an Ord constraint.
>     getSet :: Ord a => Set a -> S.Set a
>     getSet a = a >>- S.singleton

this unfortunately also means that duplicated elements only get
filtered out at the points where you use getSet,
so in "getSet ((return 1 `mplus` return 1) >>= k)" k gets still called twice

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


Re: [Haskell-cafe] hoogle command line program on Linux

2011-01-09 Thread Neil Mitchell
Hi Erik,

Hoogle 4.1.3 is now released, which reads and writes Hoogle input
files in UTF8 throughout. Please let me know if this doesn't fix your
problem.

Thanks, Neil

On Sun, Jan 9, 2011 at 11:22 AM, Neil Mitchell  wrote:
> Hi Erik,
>
> I'll release Hoogle 4.1.3 with a fix later today.
>
> Thanks, Neil
>
> On Sun, Jan 9, 2011 at 5:07 AM, Erik de Castro Lopo
>  wrote:
>> Hi all,
>>
>> I'm testing out hoogle 4.1.2 on Debian Linux and getting the
>> following when trying to update the local hoogle databases:
>>
>>    erik > sudo hoogle data
>>    Starting default
>>    Starting keyword
>>    hoogle: keyword.txt: commitAndReleaseBuffer: invalid argument
>>    (Invalid or incomplete multibyte or wide character)
>>
>> My LANG related envorinment variables are set as follows:
>>
>>    erik > env | grep LANG
>>    LANG=en_AU.UTF-8
>>    GDM_LANG=en_AU.UTF-8
>>    LANGUAGE=en_AU.UTF-8
>>    LC_LANG=en_AU.UTF-8
>>
>> When faced with a similar problem while working on Ben Lippmeier's
>> compiler, I fixed this by replacing all instances of readFile with
>> readUtf8File which is defined as:
>>
>>    readUtf8File :: FilePath -> IO String
>>    readUtf8File filePath
>>     = do   h <- openFile filePath ReadMode
>>            hSetEncoding h utf8
>>            hSetEncoding stdout utf8
>>            hGetContents h
>>
>> Is it possible to fix this without hacking the hoogles sources?
>> I'd like to package hoogle for Debian, but first I need to get
>> it working.
>>
>> Cheers,
>> Erik
>> --
>> --
>> Erik de Castro Lopo
>> http://www.mega-nerd.com/
>>
>> ___
>> 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


Re: [Haskell-cafe] hoogle command line program on Linux

2011-01-09 Thread Neil Mitchell
Hi Erik,

I'll release Hoogle 4.1.3 with a fix later today.

Thanks, Neil

On Sun, Jan 9, 2011 at 5:07 AM, Erik de Castro Lopo
 wrote:
> Hi all,
>
> I'm testing out hoogle 4.1.2 on Debian Linux and getting the
> following when trying to update the local hoogle databases:
>
>    erik > sudo hoogle data
>    Starting default
>    Starting keyword
>    hoogle: keyword.txt: commitAndReleaseBuffer: invalid argument
>    (Invalid or incomplete multibyte or wide character)
>
> My LANG related envorinment variables are set as follows:
>
>    erik > env | grep LANG
>    LANG=en_AU.UTF-8
>    GDM_LANG=en_AU.UTF-8
>    LANGUAGE=en_AU.UTF-8
>    LC_LANG=en_AU.UTF-8
>
> When faced with a similar problem while working on Ben Lippmeier's
> compiler, I fixed this by replacing all instances of readFile with
> readUtf8File which is defined as:
>
>    readUtf8File :: FilePath -> IO String
>    readUtf8File filePath
>     = do   h <- openFile filePath ReadMode
>            hSetEncoding h utf8
>            hSetEncoding stdout utf8
>            hGetContents h
>
> Is it possible to fix this without hacking the hoogles sources?
> I'd like to package hoogle for Debian, but first I need to get
> it working.
>
> Cheers,
> Erik
> --
> --
> Erik de Castro Lopo
> http://www.mega-nerd.com/
>
> ___
> 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