[Haskell-cafe] Getting highest sum of list elements with Map

2009-08-05 Thread gwern0
-- based on http://jtauber.com/blog/2008/02/10/a_new_kind_of_graded_reader/
-- TODO: read knownwords from file
--   print out matching sentences as well (make optional)
--   fix performance; goal: handle Frank Herbert corpus in under 5 minutes
--   benchmark parallelism; is it gaining me anything or is 'pmap' just wasting 4 lines?

import Data.Char (isPunctuation, toLower)
import Data.List -- (nub, sort)
import qualified Data.Set as Set
import qualified Data.Map as Map
import Control.Parallel.Strategies
import Data.Function (on)
import Data.Maybe

import Data.List.Split (splitWhen)

import System.IO.UTF8 (getContents, putStrLn)
import System.Environment (getArgs)

main :: IO ()
main = do depth <- fmap (read . head) $ getArgs
  corpus <- System.IO.UTF8.getContents
  let pcorpus = processCorpus corpus
  let knownwords = map (map toLower) ["You", "dont", "see", "more", "than", "that", "The", "first", "episode", "of", "Kare", "Kano", "is", "rotten", "with", "Evangelion", "visual", "motifs", "the", "trains", "the", "spotlights", "and", "telephone", "poles", "and", "wires", "the", "masks", "and", "this", "is", "how", "everyone", "sees", "me", "etc", "a", "it", "did", "are", "to", "in", "I", "Dune", "was", "Stalin", "Mussolini", "Hitler", "Churchill", "beginning", "That", "all", "be", "like", "on", "an", "Its", "But", "only", "you", "themes", "into", "as", "my", "human", "paradox","he","said","paul","his","she","her","not","him","had","for","at","alia","no","from","what","asked","they","there","have","stilgar"]
  let optimalwords = answer depth pcorpus knownwords
  System.IO.UTF8.putStrLn optimalwords

-- | Clean up. Don't want 'Je suis." to look different from "Je suis"...
--
-- > stringPunctuation "Greetings, fellow human flesh-sacks!" ~> "Greetings fellow human fleshsacks"
stripPunctuation :: String -> String
stripPunctuation = filter (not . isPunctuation)

-- Turn a single big document into a stream of sentences of individual words; lower-case so we don't get
-- multiple hits for 'He', 'he' etc
processCorpus :: String -> [[String]]
processCorpus = pmap (sort . words . stripPunctuation) . splitWhen (=='.') . map toLower

-- parallel map
pmap :: (NFData b) =>(a -> b) -> [a] -> [b]
pmap = parMap rnf

sentences :: (NFData a, Ord a) => [[a]] -> Map.Map Int (Set.Set a)
sentences = Map.fromList . zip [(0::Int)..] . pmap Set.fromList

fidiv :: (Integral a, Fractional b) => a -> a -> b
fidiv = (/) `on` fromIntegral

swap :: (a, b) -> (b, a)
swap = uncurry (flip (,))

ranks :: (NFData v, Ord k, Ord v) => Map.Map k (Set.Set v) -> Maybe (Rational, v)
ranks s =  listToMaybe . sortBy (flip compare) .
  pmap swap .
  Map.toList .
  Map.fromListWith (+) $
  [(word, 1 `fidiv` Set.size wrds)
  | (_sentenceId, wrds) <- Map.toList s
  , word <- Set.toList wrds]

approximation :: (NFData v, Ord k, Ord v) => Map.Map k (Set.Set v) -> Int -> [v]
approximation _ 0 = []
approximation s n =
case ranks s of
  Nothing -> []
  Just (_value, word) ->
let withoutWord = Map.map (Set.delete word) s
in word : approximation withoutWord (n-1)

-- do not use parmap in this function on pain of death; GHC is broken?
process :: (Ord v, NFData v) => [[v]] -> [Int] -> [[v]]
process ss ns = map (approximation $ sentences ss) ns

getBest :: [Int] ->[[String]] -> String
getBest x y = unlines . last  $ process y x

filterKnown :: [String] -> [[String]] -> [[String]]
filterKnown known = filter (not . null) . pmap (filter (flip notElem $ known))

answer :: Int -> [[String]] -> [String] -> String
answer depth corp known = let corp' = filterKnown known corp in getBest  [1..depth] corp'___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Generating functions for games

2009-04-03 Thread gwern0

So some time ago I saw mentioned the game of Zendo 
https://secure.wikimedia.org/wikipedia/en/wiki/Zendo_(game) as a good game for 
programmers to play (and not just by Okasaki). The basic idea of Zendo is that 
another player is creating arrangements of little colored plastic shapes and 
you have to guess what rule they satisfy. I thought it'd be fun to play, but 
not knowing anyone who has it, I figured a Haskell version would be best.

3D graphics and that sort of geometry is a bit complex, though. Better to start 
with a simplified version to get the fundamentals right. Why not sequences of 
numbers? For example: [2, 4, 6] could satisfy quite a few rules - the rule 
could be all evens, or it could be ascending evens, or it could be incrementing 
by 2, or it could just be ascending period.

Now, being in the position of the player who created the rule is no good. A 
good guesser is basically AI, which is a bit far afield. But it seems 
reasonable to have the program create a rule and provide examples. Have a few 
basic rules, some ways to combine them (perhaps a QuickCheck generator), and 
bob's your uncle.

So I set off creating a dataype. The user could type in their guessed rules and 
then read could be used to compare.  I got up to something like 'data Function 
= Not | Add' and began writing a 'translate' function, along the lines of 
'translate Not = not\ntranslate Add = (+)', at which point I realized that 
translate was returning different types and this is a Bad Thing in Haskell. 
After trying out a few approaches, I decided the basic idea was flawed and 
sought help.

Someone in #haskell suggested GADTs, which I've never used. Before I plunge 
into the abyss, I was wondering: does anyone know of any existing examples of 
this sort of thing or alternative approachs? I'd much rather crib than create. 
:)

--
gwern

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] problems building hpodder

2008-04-08 Thread gwern0
On 2008.04.08 15:19:12 -0500, John Goerzen <[EMAIL PROTECTED]> scribbled 1.1K 
characters:
> On Mon April 7 2008 9:31:04 pm [EMAIL PROTECTED] wrote:
> >
> > Well, changing the deps at least would be a good idea.
>
> Right.  I've uploaded a new version of hpodder to hackage that will require
> the correct HaXml versions.

Great.

> > And actually, there is a method - Cabal supports the 'stability:' field,
> > but I don't believe it's enforced by cabal-install or anything.
>
> I think part of the problem is visibility in Hackage.  Unless I'm wrong,
> Hackage always takes you to the release with the highest version number.
> There is no "latest stable version" list and "latest development version"
> list, which would be helpful.  Something akin to, say,
> http://packages.debian.org/hpodder

Yes, that's true. There is no good way of doing in Hackage that doesn't involve 
self-discipline or messing with release schedules. I do have a thought about 
the 'stability:' field, though. Feel free to weigh in at 
.

> > (Personally, I'd update it, not just because of issues like this, but
> > because there looked to be a number of changes necessary when I commented
> > all the type sigs, and the longer you wait... &etc.)
>
> The thing is -- I don't want a stable hpodder to jump to a development
> version of HaXml.  The released version is working just fine, and when there
> is a new stable release, I'll update then.  XML parsing is quite central to
> hpodder.
>
> -- John

Sure, but there are costs to not transitioning just as there are costs to so 
doing. I was just saying which cost I found preferable.

--
gwern
JANET Salsa GSA TRANSEC LASINT A/B DJC Al BIOLWPN Xandros


pgpEMIfhjkcHJ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem building HXT

2008-04-07 Thread gwern0
On 2008.04.07 20:17:06 +0200, ln <[EMAIL PROTECTED]> scribbled 1.1K characters:
> Hi,
>
> I would like to try HXT, but I can't manage to build it. I resolved all
> the dependencies, but I get the following error:
>
> > > [EMAIL PROTECTED]:~/Desktop/hxt$ make all
> > > make -C src  all VERSION=7.5
> > > make[1]: Entering directory `/home/ln/Desktop/hxt/src'
> > > make install_local_hxt
> > > make[2]: Entering directory `/home/ln/Desktop/hxt/src'
> > > ghc -Wall -O2 -fglasgow-exts -ignore-package hxt -package-name hxt-7.5
> > > -package parsec -package HTTP -package tagsoup --make HXT.hs
> > > [  1 of 143] Compiling Text.XML.HXT.Validator.RE (
> > > Text/XML/HXT/Validator/RE.hs, Text/XML/HXT/Validator/RE.o )
> > > (.)
> > > [100 of 143] Compiling Text.XML.HXT.Parser.TagSoup (
> > > Text/XML/HXT/Parser/TagSoup.hs, Text/XML/HXT/Parser/TagSoup.o )
>
> > > Text/XML/HXT/Parser/TagSoup.hs:305:21: Not in scope: `options'
> > > make[2]: *** [libHShxt.a] Error 1
>
> The alternative installation method with cabal leads to the same result.
>
> Using Ubuntu 8.04 Beta and GHC6.8. Maybe there are incompabilities with
> newer versions of the dependencies?
>
> Would appreciate any help.
>
> Regards
> Lukas

You got it right. The issue is that in TagSoup.hs there is a line like 
'parseTagsOptions (options { foo =...}'. That's invalid syntax AFAIK; more 
importantly, it's using functions from ndm's TagSoup library. TagSoup, with 
version 0.5, renamed the Options type to ParseOptions (we know the '(options 
{...' stuff is intended to be ParseOptions because parseTagsOptions handily 
comes with an explicit type signature).

So if you simply edit the file such that 'options' -> 'ParseOptions', you 
should find it working for you.

(I did this against the Darcs repo of HXT, and things compiled for me then on. 
I'm sending patches.)

--
gwern
747 mailbomb the Alouette NSWT UKUSA Canine hitword fraud 1071


pgpg1IirJ5OnJ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] problems building hpodder

2008-04-07 Thread gwern0
On 2008.04.07 00:24:10 +0200, Karl Hasselström <[EMAIL PROTECTED]> scribbled 
0.9K characters:
> I'm trying to build hpodder 1.1.2 with ghc 6.8.2. I successfully
> downloaded, built, and installed (the latest versions of) all its
> dependencies, but when building hpodder itself, I get
>
> FeedParser.hs:146:26:
> `Content' is not applied to enough type arguments
> Expected kind `??', but `Content' has kind `* -> *'
> In the type `Content -> Either String String'
> In the type `String -> Content -> Either String String'
> In the type signature for `strof_either':
>   strof_either :: String -> Content -> Either String String
>
> I don't know enough Haskell to even determine what kind of problem
> this is -- wrong version of some dependency? Wrong version of ghc?
> Help appreciated. :-)
>
> ( FWIW, the hackage auto-builder thingie seems to have the exact same
>   problem I have:
> http://hackage.haskell.org/packages/archive/hpodder/1.1.2/logs/failure/ghc-6.8
> )
>
> --
> Karl Hasselström, [EMAIL PROTECTED]

The issue here isn't GHC, but I think it's the former.

If we open up the FeedParser.hs file, we see that the problem is that the type 
being inferred from what the code does clashes with the type gotten from what 
the code says. The issue is this Content type.

A quick search shows that Content isn't defined in FeedParser.hs, and so if we 
comment out imports, we find that Content is coming from Text.XML.HaXml, and is 
documented here: 
.

So almost certainly the issue is that HaXml has updated and changed things 
around in a way that broke Hpodder; not surprising, since HaXml-1.19.2 is as 
recent as 14 January 2008, and Goerzen may simply not have updated and 
discovered the error before he released Hpodder in February.

If the problem is too-recent HaXml, there's an obvious work around. You could 
install HaXml-1.13.3 
 and 
edit the hpodder.cabal file to replace the 'HaXml>=' bit with 'HaXml==1.13.3'. 
That works for me.

--
gwern
Etacs FOSS NTIS SUPIR mindwar NATOA SARA niche DNR 3B2


pgpbCnY42ol9O.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Some old and quite old news.

2008-04-05 Thread gwern0
On 2008.04.05 17:42:00 +0400, Serguey Zefirov <[EMAIL PROTECTED]> scribbled 
0.6K characters:
> [EMAIL PROTECTED] пишет:
>> Hmm. I'm having trouble getting it through SVN:
>>
>> [EMAIL PROTECTED]:1003~>svn co http://thesz.mskhug.ru/browser/hiersort [
>> 1:44PM]
>> svn: PROPFIND request failed on '/browser/hiersort'
>> svn: PROPFIND of '/browser/hiersort': 200 OK (http://thesz.mskhug.ru)
>>
>> Is there some trick that as a Darcser I don't know about?
>>
> Actually, I do not know too. Maybe, just a version mismatch?
>
> Did you tried to access files using just a web browser?
>
> I CC'd that to myself at home and will try to resolve matters ASAP. At
> least I will make a tarball and post it somewhere at MskHUG website.
>
> Thank you for your interest. ;)

Well, I looked at some of the files with a browser, and that worked fine. It's 
just when I tried to do a checkout that fails.

I've asked the guys in #svn, and they said the 'real' repo is elsewhere, so I 
went and asked #trac where the real repo's URL is. One of them said

 12:37 < thatch> gwern: the faq can't cover it.  Trac only knows the local 
filesystem path to the repo, not its web-accessible path.

So I dunno. After some guessing, thatch came up with 
 as the repo URL. It's downloading now, 
although slowly.

--
gwern
Z7 Service NSG Sayeret FIPS140-1 encryption data-haven continuous black-bag 
illuminati


pgps0IyGGuSG0.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: SoC project: Python-Haskell bridge - request for feedback

2008-03-30 Thread gwern0
On 2008.03.27 14:07:23 -0700, Dan Weston <[EMAIL PROTECTED]> scribbled 0.7K 
characters:
> I did not see MissingPy on Hackage (presumably it would be next to
> MissingH?)

Remember, Hackage is alphabetical by category and then by title; I personally 
would not stick MissingH in the Unclassified category but something like 
Development.

Anyway, I doubt you'll see MissingPy on Hackage soon; note that the 
installation procedure requires you to use a python script to generate an 
appropriate cabal file. (It doesn't build for me anyway, but that's a separate 
issue.)

> I found it (listed on http://www.complete.org/jgoerzen/softindex.html) at
> http://darcs.complete.org/missingpy
>
> Is this the right place to get it?
>
> Dan

I think so. That's the host I recognize from HSH, at least.

--
gwern
Brown virtual DDR&E B83 Kwajalein Team IMF CANSLO Watergate MOD


pgpD6EyGSgW1h.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: HFuse: ls fails in HelloFS

2008-03-19 Thread gwern0
On 2008.03.19 02:43:27 -0400, "Brandon S. Allbery KF8NH" <[EMAIL PROTECTED]> 
scribbled 0.8K characters:
>
> On Mar 19, 2008, at 2:12 , Austin Seipp wrote:
>
>> Excerpts from Will Thompson's message of Sun Mar 16 08:37:00 -0500 2008:
>>> Currently the module's name is HFuse.  Presumably it really belongs
>>> under System somewhere; System.Posix.Fuse maybe?  What do folks think?
>>> Are there any guidelines for picking a namespace?
>>
>> I don't think there's any sort of doc on picking a namespace or how to
>> logically name your package modules (would likely be worth writing);
>> for something like this, I would say something under System.Posix.*
>> would be the most appropriate.
>
> Erm, "POSIX" does not mean "Linux and sufficiently similar systems".  FUSE
> is supported by open source Unixlikes, not by POSIX compliant systems in
> general.
>
> --
> brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]

Not sure that's a useful distinction to make. Wikipedia says "FUSE is available 
for Linux, FreeBSD, NetBSD (as PUFFS), OpenSolaris and Mac OS X (as MacFUSE)."

Linux, the BSDs, and Solaris are all pretty POSIX compliant, where they have 
not actually been officially certified by POSIX; OS X Leopard is surprisingly 
enough, certified -  says
"Leopard is an Open Brand UNIX 03 Registered Product, conforming to the SUSv3 
and POSIX 1003.1 specifications for the C API, Shell Utilities, and Threads. 
Since Leopard can compile and run all your existing UNIX code, you can deploy 
it in environments that demand full conformance — complete with hooks to 
maintain compatibility with existing software."

Since there's no Filesystem.* hierarchy, what's wrong with System.Posix.FUSE.*? 
I know of no non-Posix systems that run FUSE...

--
gwern
enigma main Warfare DREC Intiso cards kilderkin Crypto Waihopai Oscor


pgpcfkv27PFZf.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] libmad and os/x coreaudio wrappers

2008-03-19 Thread gwern0
On 2008.03.19 11:09:00 -0700, Chris Waterson <[EMAIL PROTECTED]> scribbled 1.7K 
characters:
> Hi there!  I've taken my first stab at writing some (admittedly
> minimal) libraries for Haskell, and would love to get feedback on
> them:
>
>   * hmad: a wrapper for the libmad MP3 decoder.
>   http://maubi.net/~waterson/REPO/hmad
>
>   * CoreAudio: a wrapper for OS/X CoreAudio.
>   http://maubi.net/~waterson/REPO/CoreAudio
>
> (You should be able to "darcs get" the above links, if you want.)
>
> I wrote the libmad wrapper to generate a "stream" (i.e., a lazy list)
> of audio samples.  CoreAudio allows the input stream to be lazy, as
> well.  So, here's a simple MP3 player:
>
> > module Main where
> >
> > import Sound.CoreAudio
> > import Codec.Audio.MP3.Mad
> > import qualified Data.ByteString.Lazy as B
> > import System
> > import System.IO
> >
> > main :: IO ()
> > main = do files <- getArgs
> >   mapM_ playFile files
> >
> > playFile :: String -> IO ()
> > playFile file =
> > withBinaryFile file ReadMode $ \ inHandle ->
> >do xs  <- B.hGetContents inHandle
> >   samples <- decode xs
> >   play samples
>
> I do have a couple questions...
>
>   * The CoreAudio library requires its users to be compiled with
> "-threaded".  Is there a way to specify that in the Cabal file?

I don't think so. Actually, I asked dcoutts, and he said Cabal cannot make a 
user use a specified ghc-option:. Apparently it did once, but it was abused and 
got removed:
"The only problem is that threaded applies to the final program. If a library 
declares that it needs threaded, does that mean we have to propagate the flag 
and use it with all programs that use it?

Propagating GHC flags is not possible currently - by design. GHC used to have 
such a feature and it was removed.

Or perhaps we say it's an extension that only applies to executables?"


...
> chris

--
gwern
enigma main Warfare DREC Intiso cards kilderkin Crypto Waihopai Oscor


pgpH7st3jXs1S.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Data.HashTable

2008-03-07 Thread gwern0
On 2008.03.06 22:43:53 +0100, Johannes Waldmann <[EMAIL PROTECTED]> scribbled 
1.4K characters:
> > In practice, Data.Map outperforms it in essentially all cases
> > (Data.HashTable stops working beyond a certain size and so any
> > asymptotic benefits, if they exist at all, don't have time to kick
> > in).
>
> What!
>
> I learned at school, and I teach my students,
> * balanced binary tree: costs are log(size)
> * hashtable: cost are essentially constant
> therefore, hashtable should be preferred in almost all cases
> (if you know a reasonable hash function
> and except where you need persistency, of course)
>
> the difference should be visible even for moderate sizes
> (e.g. 1000). With a reasonable implementation  I expect
> log(1000) = 10 comparisons (and dereferencings) for the tree;
> while the hashtable should have the computation of the hash value
> (ideally, in registers), one memory access, and one comparison.
>
> ... but indeed some experiments with Data.Map and Data.Hashtable
> support the point you made. That's either good for Data.Map
> or bad for Data.Hashtable.
>
> PS: I did not manage to compile HsJudy-1.0 with ghc-6.8.2
> (some hsc file missing - perhaps that should be auto-generated? how?)
>
> Best regards, Johannes.

Oh... I'm terribly sorry about that. It was I who uploaded HsJudy.

The problem was, it's maintained by the Pugs project for some reason. The 
directory structure looks like:

pugs/
  thirdparty/
 HsJudy/
 hsregex/
 HsSyck/
 installed/
 judy/
Judy-1.0.3/

Here Judy-1.0.3/ contains the actual C library Judy itself. So what the 
Cabalized package residing in HsJudy/ was doing was literally linking against 
stuff like '../judy/Judy-1.0.3/src/JudyL/*.o'.

At the time I was packaging, Cabal didn't yet warn about problems like ../, so 
it would build and install just fine when I ran it with no problems; but I 
forgot that obviously all the ../ stuff would totally break in an sdist tarball.

I think I've fixed it: 
.

--
gwern
Air eavesdropping pipe-bomb TSCM Centro ^X JIC TWA USACIL Protection


pgpPeExTiZYSc.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble finding exception source

2008-02-26 Thread gwern0
On 2008.02.26 23:13:59 -0500, Denis Bueno <[EMAIL PROTECTED]> scribbled 7.4K 
characters:
> Hi all,
>
> I've got some code crashing with "Prelude.foldr1: empty list".  In
> GHCi, the code uses too much memory (I kill it after it consumes 1GB)
> to be able to use :trace and :history, but I just found out about the
> -xc RTS option.  I tried that, and I get the following:
>
> dsat: Prelude.foldr1: empty list
>
> Now, manually going through GHC.List
> (http://haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-List.html)
> I only found one CAF, namely prel_list_str, at the bottom of the file.
>  However, it is late and I quite possibly missed something.  This CAF,
> of course, doesn't seem a likely culprit.  I also stumbled on some
> discussion of the explicit call stack
> (http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack/StackTraceExperience)
> which exemplifies the behavior I've found, but doesn't seem to suggest
> a way to fix it.
>
> I'm developing on GHC 6.8.2.  I've attached my code, the output of a
> cabal sdist, which requires parse-dimacs [0] and bitset [1] (both
> cabalised) to build.  If you build the executable (with profiling),
> you should see my behavior by running:
>
> ./dist/build/dsat/dsat -verify +RTS -xc
>
> I know that the problem is somewhere in the "Backtracking" section, in
> the backJump function.  But I don't know where.
>
> Any help is appreciated.
>
> --
>   Denis

Fortuitously, I recently came across a bunch of bioinformatics software in 
Haskell. One of the libraries was called 'interlude', and it claims to be able 
to give line locations for errors in the Prelude. I was intending to upload 
them all as a group once I'd finished, but you might be able to make use of it 
here.

You can find it here: 
.

If it does work out for you, be sure to let me know. I haven't run across any 
Prelude errors in my code since I installed it, so I haven't really tried it 
out.

--
gwern
brigand Investigation Firewalls Galil NTIS TDYC Yukon Morse Jazeera INR


pgpZqRTmVz7Pe.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: nano-hmac 0.2.0

2008-02-11 Thread gwern0
On 2008.02.11 09:42:44 -0800, Adam Langley <[EMAIL PROTECTED]> scribbled 0.5K 
characters:
> On Feb 11, 2008 12:54 AM, Hitesh Jasani <[EMAIL PROTECTED]> wrote:
> > nano-hmac provides bindings to OpenSSL's HMAC interface.  With this release 
> > the
> > set of hashing functions supported is: MD5, SHA, SHA1, SHA224, SHA256, 
> > SHA384,
> > SHA512.
>
> Just a heads up; PHO has written nice bindings to much of OpenSSL:
>
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HsOpenSSL-0.3.1
>
> AGL
>
> --
> Adam Langley  [EMAIL PROTECTED]

Also, I recently uploaded hopenssl at 
.
 I don't know how it stacks up, but it was necessary to be able to 'cabal 
install postmaster' (which now works very nicely).

--
gwern
JD Yongyue SITOR t bemd Magdeyev 1911 ISS Gorizont Juiliett


pgppeM8vdXrXh.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskore dead?

2008-02-04 Thread gwern0
On 2008.02.04 16:11:55 -0200, Maurí­cio <[EMAIL PROTECTED]> scribbled 0.3K 
characters:
> Hi,
>
> I've just tried using Haskore (I use Ubuntu
> and GHC), with no success. Since Haskore was
> started a long time ago, but it's not yet
> cabalized, and the author's page can not be
> reached, I can't say for sure if it's still
> maintained. Does anybody know?
>
> Thanks,
> Maurício

I think the homepage  is more than a bit old. 
I googled a bit more, and found  
which links to a Darcs repo at . The most 
recent modification date is for src/, 04-Dec-2007. I'm trying it out right now, 
but the darcs get is taking a while.

--
gwern
ssa NMS encryption Finksburg Panama 1071 fraud import MDA South


pgpBKsrGSxIea.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Hlist 0.1 on Hackage

2008-02-02 Thread gwern0
Hey everyone:

I'd like to make a short announcement that with the permission of its 
maintainer, I've uploaded HList v0.1 to Hackage. You can find the Hackage page 
here: . 
'cabal install HList' should also work.

HList for those who don't know is a sort of OO Haskell package which permits 
heterogeneous lists; you can find out more at 
. (The Darcs repository is at 
.)

What changes have been made to the darcs repo? Well, they are mostly updates 
and cleanups -  I've updated build-depends for GHC 6.8.x; largely moved from 
-fglasgow-exts to LANGUAGE pragmas; put the modules in a proper module 
namespace; fixed up Haddock generation; removed some unused files, and other 
things of that nature.

--
gwern
Covert data bank Armani Larson Missiles Dick CTP SO13 AUTODIN


pgpXMNyRA7zZg.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: [Haskell] Announce: Yi 0.3

2008-01-31 Thread gwern0
On 2008.01.31 16:27:05 -, "Bayley, Alistair" <[EMAIL PROTECTED]> scribbled 
0.7K characters:
> > From: Thomas Schilling [mailto:[EMAIL PROTECTED]
> > >
> > > So Yi works on Windows? hs-plugins was broken for Windows
> > for a while,
> > > so I'm wondering if this has been fixed too. Does Yi use
> > hs-plugins, or
> > > does it go straight down to ghc? (looking at the yi.cabal
> > file seems to
> > > indicate no dependency on hs-plugins)
> >
> > Correct.
> >
> > Does that mean you volunteer and report any problems of running Yi on
> > Windows? ;-)
>
> I'd love to, but JP has just indicated (privately) that it's broken on
> Windows, for other reasons.
>
> I was trying to establish whether it was worth my time to attempt to
> download Yi and GTK2HS and build them.
>
> Alistair

It probably isn't your time, but I think it's doable. If you grep for .Posix, 
you see:

> Yi/Dired.hs:import System.Posix.Files
> Yi/Dired.hs:import System.Posix.Types
> Yi/Dired.hs:import System.Posix.User
> Yi/Dired.hs:import Text.Regex.Posix
> Yi/UI/Vty.hs:import System.Posix.Signals ( raiseSignal, sigTSTP )
> Yi/Search.hs:import Text.Regex.Posix.String  ( Regex, compExtended, > 
> compIgnoreCase, compNewline, compile, execBlank )
> Yi/Buffer/Implementation.hs:import Text.Regex.Posix
> Yi/Eval.hs:import Text.Regex.Posix
> Yi/MkTemp.hs:import qualified System.Posix.Internals ( c_getpid )
> Yi/MkTemp.hs:System.Posix.Directory.createDirectory dir ownerModes
> Yi/MkTemp.hs:getProcessID = System.Posix.Internals.c_getpid >>= return . > 
> fromIntegral
> Yi/Editor.hs:import Text.Regex.Posix.Wrap( Regex )
> Yi/Buffer.hs:import Text.Regex.Posix.Wrap(Regex)

All the mentions Text.Regex.Posix is not a problem, as regex-posix doesn't 
depend on the 'unix' package so far as I know.

If you wanted to, you could quietly remove Dired.hs, which would remove its 
dependencies on System.Posix.*, and the same goes for VTY.hs (not that you'd 
really want that on Windows anyway). MkTemp is built, but I don't believe it's 
actually used by anything (maybe Dired?). And that would be it, so far as I 
know.

But all that would be a lot of work, and Yi isn't mind-blowingly good, if you 
follow me.

--
gwern
Recon tors EOD MSNBC K3 NB Spoke MITM Crust filofax


pgp2Lrz8crikg.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Testing one's .ghci

2008-01-26 Thread gwern0
So I was recently going over my config files (which are version-controlled in 
Darcs, of course), and I was adding tests for recording patches. For some of 
the files, it was easy enough - the application generally provided some mean of 
loading in the rc file and then it would error or not based on whether the file 
was at least syntactically correct. For example, to test my .emacs, I have 
'emacs -batch -f batch-byte-compile ~/.emacs'. If the .emacs won't 
byte-compile, it probably won't run!

My question is, how many I do the same thing with GHCi? No options specifically 
for this seem to be listed, and the normal trick doesn't work - I tried:

> ghci -read-dot-ghci -e 'let main = return() in main' && echo foo

And regardless of whether the .ghci had hideous crippling errors in it, at the 
end "foo" was still merrily being printed out. Does haskell-cafe have any ideas 
or should I just go file a feature request?

--
gwern
chameleon Vale RSA Recon 1080H beanpole advisors Harvard Texas PARKHILL


pgpFWAOD15LnS.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yi and Data.ByteString

2008-01-21 Thread gwern0
On 2008.01.22 01:39:33 +0100, Cetin Sert <[EMAIL PROTECTED]> scribbled 3.4K 
characters:
>-- Yi
>
>that's the error message I got following the instructions on
>http://www.nobugs.org/developer/yi/building.html
>
>setup: At least the following dependencies are missing:
>fingertree -any
>make: *** [dist/setup-config] Error 1
>
>Where can I get fingertree from? Do I need a specific version of this 
> package?

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fingertree-0.0

Always a good idea to check Hackage when dependencies are missing.

>-- Data.ByteString
>
>Where can I read more about GHC options like -XOverloadedStrings or this 
> ":: ByteString" type
>declaration?

The ByteString API documentation, presumably.

>I did not know ByteString was less performant than a linked list of 
> characters. It is used
>even in the language shootout benchmark programs.
>
>Cetin

As Don said, it's a matter of domain. For small amounts of data, the overhead 
erases the performance gains - although no one is denying that for medium (like 
you see on the Shootout) to large amounts of data (up to tera-, I think someone 
benchmarked) ByteString is excellent.

--
gwern
O/S bet pipe-bomb SARA Adriatic BSS M5 LBSD NOCS CBNRC


pgprGtlIiiutO.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yi and Data.ByteString

2008-01-21 Thread gwern0
On 2008.01.21 19:12:26 +0100, Cetin Sert <[EMAIL PROTECTED]> scribbled 1.9K 
characters:
>1) Can anyone tell me how I can build Yi or point me to a binary release 
> of that editor?
>
>I tried to follow the instructions on 
> http://www.nobugs.org/developer/yi/building.html but got
>a missing component error each time.

The specific error would help a lot. Also, yi-devel might be a good list to 
subscribe to.

>2) When if ever is Data.ByteString going to be the default string 
> representation in GHC?

Not sure. I once asked about this, and it seems that ByteStrings don't support 
all the operations and definitions [Char] does; and there was mention of 
Unicode problems. Plus, ByteStrings aren't really built-in - they're a separate 
library. You could perhaps suggest that [Char] could be often optimized into 
ByteString operations but then ByteStrings need to either lose their library 
status and be incorporated into GHC or you need to expand the list of depended 
libraries... I wouldn't look for't anytime soon.

>I study computational linguistics and plan to switch to Haskell in the 
> near future, that is
>once I get to grips with the language and the whole new thought model one 
> has to develop as an
>imperative programmer.

Well, you're not the first computational linguist. There are some pretty 
impressive projects in Haskell.

>Best Regards,
>Cetin Sert

--
gwern
argus ARPA garbage Internet Halliburton Corporation SASP disruptio Egret SLBM


pgpElzgTK5Y4a.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-20 Thread gwern0
On 2008.01.19 19:11:13 +0100, Peter Verswyvelen <[EMAIL PROTECTED]> scribbled 
1.4K characters:
> The problem is that this only works when the complete source file compiles
> correctly no?

Yes. As I said, it's a very hackish solution - think of it as proof-of-concept.

> I would find it most useful to get type inference information on the fly,
> even when not all of the code compiles correctly yet.

Does that make sense? If the code doesn't compile, then how could any 
type-inference be trustable? It might be reliable if the error is in 
definitions which don't get called or otherwise used by the function you are 
asking after, but there are going to be edge-cases, I should think, where it 
would bite you.

--
gwern
Freeh ASU 32 CIO GGL Force 97 b in Macintosh


pgpjicjhzpFeX.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-19 Thread gwern0
On 2008.01.19 17:30:50 +, Jon Harrop <[EMAIL PROTECTED]> scribbled 0.2K 
characters:
>
> Is it possible to get throwback of inferred types into Emacs or an IDE for
> Haskell?
>
> --
> Dr Jon D Harrop, Flying Frog Consultancy Ltd.

Sure. I once hacked together quite a while ago a little function for 
haskell-mode which looked like:

,
| (defun getHaskellFunctionTypeSignature ()
|   (interactive)
|   (progn
| (setq file-name buffer-file-name)
| (setq functionName (thing-at-point 'word))
| (shell-command (concat "echo :t " functionName " | ghci -v0 -cpp 
-fglasgow-exts -w " file-name "|grep " functionName) t)))
| (global-set-key "\C-c\l" 'getHaskellFunctionTypeSignature)
`

And I think haskell-mode has a better way of doing things somewhere in its 
inf-haskell.el.

--
gwern
Information II captain SAS BRLO unclassified of Audiotel Taiwan RSOC


pgpHVN2nHWUXN.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] First go at reactive programming

2008-01-19 Thread gwern0
On 2008.01.19 12:22:43 -0500, Steve Lihn <[EMAIL PROTECTED]> scribbled 1.5K 
characters:
...
> I am asking this question in another thread. The problem is -- I've
> got many modules compiled under 6.6, some with much agony. If I switch
> to 6.8, I have to recompile them again. Two issues I image:
>
> (1) It may take lots of effort to recompile all the modules. I have
> forgetten how I got around some of the modules! Too bad... Got to take
> notes next time...

These days, every package you'd want to install (with the exception of GHC, 
Darcs, and the large graphics toolkits) should be available on Hackage or at 
least in Cabalized form.

If they aren't, then that's a bug or at least missing feature. The whole point 
of Cabal was so you don't have to take notes!

> (2) If I got stuck in 6.8, it may not be easy to switch back.

Well, uh, is that really a bad thing? Do you worry about device drivers 
'because if I got stuck in the 2.x series of Linux kernels, it may not be easy 
to switch back [to 1.x]'? No; 6.8.x is the future. The older GHCs will fall 
behind, people will rightfully upgrade, things will bitrot, and so on. There's 
no real benefit to willfully using outdated software - the most painful parts 
of the 6.8.x upgrade are past.

> It does not appear straightforward to me. I'd like to hear how other
> people approach these issues before I jump into it. Don't want to
> break the working environment that I spent months to set up!

I began darcs send'ing patches for stuff broken by 6.8.x; by this point, all 
the major stuff I use is fixed, at least out of Darcs (although many packages 
are woefully outdated on Hackage. I've been working on this).

...
> Thanks.
> Steve

--
gwern
Information II captain SAS BRLO unclassified of Audiotel Taiwan RSOC


pgpg7mEkHNDX2.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] One-line haskell program with GHC

2008-01-18 Thread gwern0
On 2008.01.18 13:57:27 -0800, Sukit Tretriluxana <[EMAIL PROTECTED]> scribbled 
1.3K characters:
>Hi,
>
>I don't know if it's been asked before. I just wonder if GHC supports some 
> sort of one-liner
>program that can be specify right as the argument to either ghci or runghc 
> program. In perl,
>they have something like
>
>perl -e 'print "Hello"'
>
>Do we have similar thing with GHC?
>
>Thanks,
>Ed

http://www.joachim-breitner.de/blog/archives/156-Haskell-on-the-Command-Line.html

http://haskell.org/haskellwiki/Simple_Unix_tools

http://www.haskell.org/pipermail/haskell-cafe/2007-March/023035.html

or

http://groups.google.com/group/fa.haskell/browse_thread/thread/e948ff0ad4d7c0c9/241dca1a802c68bb


--
gwern
hope Coderpunks sigvoice .45 sabana MI5 CISSP Digicash b Tyrell


pgpBNosiQNpBK.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Data constructors versus types

2008-01-16 Thread gwern0
On 2008.01.17 00:58:19 +0100, [EMAIL PROTECTED] scribbled 0.9K characters:
> Achim Schneider writes:
>> Lisp is actually not really meant to be compiled, but interpreted. The
>> nice thing is that it doesn't need more than a handful of primitives, a
>> list parser and heap manager/garbage collector and evaluator, which all
>> can be implemented in under 1000 lines of C. Things get more involved
>> with get/cc, but then how many C programmers ever heard of setjmp...
>
> Would you mind stopping to spread dubious truths?
> Certainly, Lisp processors started with simple eval/apply interpreters,
> since they were easy to construct, but compilers, their name is Legion!
> Look at CMU Common Lisp compiler.
> GNU CLISP compiler
> Lisp Works compiler
> Allegro compiler
> ...
...
> Jerzy Karczmarczuk

I don't think it's a dubious truth. Apparently a lot of Lisps (like Maclisp or 
Interlisp, I hear) had a situation where the semantics of a program could 
differ depending on whether it was compiled or interpreted, and Scheme and 
Common Lisp made a point of trying to avoid that.

In _Introduction to Common Lisp_, we read:
 "Most Lisp implementations are internally inconsistent in that by default the 
interpreter and compiler may assign different semantics to correct programs. 
This semantic difference stems primarily from the fact that the interpreter 
assumes all variables to be dynamically scoped, whereas the compiler assumes 
all variables to be local unless explicitly directed otherwise. This difference 
has been the usual practice in Lisp for the sake of convenience and efficiency 
but can lead to very subtle bugs. The definition of Common Lisp avoids such 
anomalies by explicitly requiring the interpreter and compiler to impose 
identical semantics on correct programs so far as possible." 


Given that it was designed as interpreted, compilation was motivated by 
efficiency concerns, and interpreted techniques differed from compiled 
techniques (and in a way that would allow you to redefine and change more stuff 
on the fly), I think it's a reasonable case to say that many Lisps - like all 
the ones before Scheme and CL - were meant to be interpreted and not so much 
compiled.

--
gwern
NATIA DIA Burns espionage 97 utopia orthodox Meade cond SOCIMI


pgpWxdV8bwJV7.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yi editor tutorial

2008-01-16 Thread gwern0
On 2008.01.15 22:54:08 -0800, "Benjamin L. Russell" <[EMAIL PROTECTED]> 
scribbled 1.8K characters:
> Your Yi editor tutorial looks like a fascinating idea,
> but I use Mac OS X (10.2.8 Jaguar, soon to be upgraded
> to 10.5.x Leopard) at home, and Windows XP at work,
> while your tutorial is based on Ubuntu and the bash
> shell.
>
> A few questions:
>
> 1) Do you have any versions of your Yi tutorial for
> Mac OS X or Windows XP; if not, are there any plans
> for such tutorials in the future?

I suspect you would have a hard time running on Windows XP: the cabal file 
currently declares a dependency on 'unix' because the VTY interface needs it, 
and also because the Dired module needs System.Posix.Users (to look up file 
owners). So at the very least you'd need to edit those out.

> 2) On your tutorial top page
> (http://nobugs.org/developer/yi/), you mentioned that
> you had first learned Haskell in 2001 from _The
> Haskell School of Expression_ by Paul Hudak.  I also
> tried studying that book, and found it very
> interesting (especially with its focus on multimedia
> examples), but unfortunately got stuck on an exercise
> in Chapter 2 that required trigonometry, which I had
> forgotten from lack of use and didn't have time to
> review.  Also, I wanted to study it online, and had
> purchased the book (and thus paid the licensing fee),
> but was unable to find an online version.  Do you have
> any suggestions for online books with the same flavor
> that require less domain-specific knowledge;
> alternatively, do you have any suggestions for online
> material that precisely covers the domain-specific
> knowledge assumed by that book?
>
> Benjamin L. Russell

--
gwern
NAVCM Area51 M.P.R.I. Misawa Manfurov CACI Internet rapnel W3 HF


pgprV7qzwi182.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yi editor tutorial

2008-01-14 Thread gwern0
On 2008.01.14 13:34:42 +, Andrew Birkett <[EMAIL PROTECTED]> scribbled 0.8K 
characters:
> [EMAIL PROTECTED] wrote:
>> I'm going through them now, and I like them a lot. (Maybe I'll finally
>> begin doing stuff with Yi!)
>> Is there any particular reason you didn't put your tutorials on the
>> Haskell wiki? I'd think they'd be good there.
>
> Cool, thanks.  :-)
>
> I agree it'll be a good idea to move it to the wiki, and I'll do that soon.
>  On my own site, I can make lots of little changes locally and then
> atomically (well, quickly at least!) rsync the new version up onto the
> server.  It makes life easier when I'm likely to change around the top
> level structure.  The wiki makes a lot of sense though, because it's
> central and other people can extend the tutorial and fix bugs.

I'd say editing a wiki is even easier. :) But if you want to wait until you've 
gotten it to a state where you're happy with it, that's good too.

> It's also nice to be able to check the server logs and gauge interest too
> (about 5000 hits since yesterday).
>
> Andrew

True, but the interest won't last forever; so maybe after the Reddit links go 
quiescent?

--
gwern
rico Glock telex million propellants Warfare Ortega CNN 8182 Vauxhall


pgpokedMhOryB.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with function with two clauses

2008-01-09 Thread gwern0
On 2008.01.09 18:15:33 +, Fernando Rodriguez <[EMAIL PROTECTED]> scribbled 
0.3K characters:
>
> Hi,
>
> I have the following type and function:
>
> data ConsCell a = Nil | Cons a (ConsCell a) deriving Show
> head' Nil = Nothing
> head' (Cons a _) = Just a
>
> Works fine, however, what's wrong with the following function?
>
> head''| Nil = Nothing
>   | Cons a _ = Just a
>
> Thanks!

Couple of things. Your head'' is trying to use pattern-matching, but guards 
(which are what you are actually using) require a Bool expression on the left 
hand side; guards just desugar into if-then-else clauses.

In this case it'd look something like

> head'' a = if Nil then Nothing else if Cons a _ then Just a else ???

This doesn't make sense. Nil is just Nil, it's not in Bool; the if can't do 
anything with that. Similarly, Cons a _ is just ConsCell and in the Show 
typeclass; it too is not Bool.

If we turn it into pattern-matching:

> head'' Nil = Nothing
> head'' Cons a _ = Just a

But this still doesn't work - one definition takes a single argument, and the 
other 3; Nil (1), vs [Cons, a, _] (3). So:

head'' Nil = Nothing
head'' (Cons a _) = Just a

Parentheses force the Cons to be seen as a single argument.

So I guess your final product would look like this, which is pretty much what 
you start out with.

> data ConsCell a = Nil | Cons a (ConsCell a) deriving Show
>
> head' :: ConsCell a -> Maybe a
> head' Nil = Nothing
> head' (Cons a _) = Just a

--
gwern
Hackers Emerson EO SAS Majic CANSLO rail ABC CFD RSOC


pgpxSht62yj3I.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC 6.8.2 as a library on Windows and GHCi

2008-01-09 Thread gwern0
On 2008.01.09 17:07:46 +0100, Peter Verswyvelen <[EMAIL PROTECTED]> scribbled 
4.7K characters:
>I while I ago I sent an email regarding hs-plugins not working on windows.
>
>I now tried to directly use GHC API, but I also failed.
>
>The following program (which might be buggy, I copy/pasted from various
>sources)
>
>import DynFlags
>import GHC
>
>main = defaultErrorHandler defaultDynFlags $ do
>  session <- newSession (Just "d:/app/ghc-6.8.2")
>  flags <- getSessionDynFlags session
>  (flags, _) <- parseDynamicFlags flags []
>  GHC.defaultCleanupHandler flags $ do
>setSessionDynFlags session flags{ hscTarget=HscInterpreted }
>prelude <- findModule session (mkModuleName "Prelude") Nothing
>setContext session [] [prelude]
>runStmt session "let n = 2 + 2" RunToCompletion -- n is bound
>runStmt session "n"  RunToCompletion-- 4 is printed (note
>"it" is bound)
>
>gives the following error when run from GHCi
>*Main> :load "l:/test.hs"
>[1 of 1] Compiling Main ( l:/test.hs, interpreted )
>Ok, modules loaded: Main.
>*Main> main
>
>GHCi runtime linker: fatal error: I found a duplicate definition for
>symbol
>   _forkOS_entry
>whilst processing object file
>   d:/app/ghc-6.8.2/lib\base-3.0.1.0/HSbase-3.0.1.0.o
>This could be caused by:
>   * Loading two different object files which export the same symbol
>   * Specifying the same object file twice on the GHCi command line
>   * An incorrect `package.conf' entry, causing some object to be
> loaded twice.
>GHCi cannot safely continue in this situation.  Exiting now.  Sorry.
>
>Process haskell finished
>
>Is my code incorrect, or is this a (known?) bug in GHC 6.8.2 on Windows? I
>haven't tried the Linux version yet.
>
>NOTE: The program *does* run fine when compiling via GHC --make.
>
>Thanks,
>Peter

I think your installation is just buggy. I ran it here, and it compiles fine 
(although it doesn't run, as Linux obviously has "d:/app/ghc-6.8.2") and runs, 
printing "4" if I replace the string with "/usr/lib/ghc-6.8.2". Could it be 
that your GHCi is not the 6.8.2 one, or your path incorrect?

--
gwern
& b AHPCRC Playboy Dolch += SG530 Karimov CNCIS beef


pgpGmqmOy2vcz.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC's dynamic linker and Windows

2008-01-07 Thread gwern0
On 2008.01.07 07:20:05 -0600, Austin Seipp <[EMAIL PROTECTED]> scribbled 2.6K 
characters:
> > I recently tried the latest version of HS-PLUGINS, and it gave an error on
> > Windows. After a bit of Googling it seemed Conal Elliot had the same
> > problem. I reported this problem to the author. This is also (one of) the
> > reason why I could not get YI running on Windows.
>
> Currently I believe Conal is working on getting the latest hs-plugins to
> work on windows. It was recently updated to work with ghc 6.8.x (thanks
> Cale & co.) but there was no release as the aim is to get it working for
> 6.8 on both windows and linux before making an official release
> (currently it seems to be linux only, as I have the latest 1.1 installed
>  from the repo below.) The latest repo for hs-plugins for 6.8 can be found at
>
> http://code.haskell.org/~dons/code/hs-plugins
>
> I'm sure Conal and others would appreciate any patches to help move it
> along!

Ah. That explains it. I'd been annoyed for some time now that hs-plugins was 
broken for so long with 6.8.x, but I had been pulling from 
.

It's probably worth noting that the first Google hit for 'hs-plugins' is Don's 
pages, and that points to the old Darcs repo, 
 
("Darcs repository of the latest code: darcs get --set-scripts-executable 
http://www.cse.unsw.edu.au/~dons/code/hs-plugins";).

The second and third hits links to that page as well. Maybe the docs could be 
upgraded and the usual deprecation warning inserted in the old repo?

--
gwern
GSM Submarine E. 510 ddnp building y friends RDI JCET

pgpZnZFZwaub0.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Tools in Haskell

2008-01-06 Thread gwern0
On 2007.12.12 12:51:58 -0600, Tommy M McGuire <[EMAIL PROTECTED]> scribbled 
2.7K characters:
> Gwern Branwen wrote:
>> Some of those really look like they could be simpler, like 'copy' -
>> couldn't that simply be 'main = interact (id)'?
>> Have you seen ?
>> For example, 'charcount' could be a lot simpler - 'charcount = showln
>> . length' would work, wouldn't it, for the core logic, and the whole
>> thing might look like:
>>> main = do (print . showln . length) =<< getContents
>> Similarly wordcount could be a lot shorter, like 'wc_l = showln .
>> length . lines'
>> (showln is a convenience function: showln a = show a ++ "\n")
>
> Yes, that's absolutely true, and I am adding a section showing
> implementations based on interact as soon as I send this message.  The
> reason I didn't do so before is that I was trying to (to an extent)
> preserve the structure of the original implementations, which means using
> an imperative style.

Yes, I'm looking at it now. Pretty nice.

> Strangely, I have considerably more confidence in the imperative-ish
> Haskell code than I do in the imperative Pascal code, in spite of the fact
> that they are essentially the same.  Probably this is due to the
> referential transparency that monadic IO preserves and that does not even
> enter into the picture in traditional Pascal.  For example, the
> pseudo-nroff implementation has a giant, horrible block of a record
> (containing the state taken directly from K&P) that is threaded through the
> program, but I am tolerably happy with it because I know that is the *only*
> state going through the program.
>
> Further, while interact could probably handle all of the filter-style
> programs (and if I understand correctly, could also work for the main loop
> of the interactive editor)

If your editor is referentially transparent, I think. Something like ed or sed 
could be done, as long as you didn't implement any of the IO stuff (like ! for 
ed).

> and a similar function could handle the later
> file-reading programs, I do not see how to generalize that to the
> out-of-core sort program.

Well, for out-of-core sort, someone several many months back posted a very neat 
solution using ByteStrings which iirc had performance as competitive as GNU 
sort's out-of-core sort

[much searching later]

Ah! Here we go: "[Haskell-cafe] External Sort and unsafeInterleaveIO" 
. I at 
least found it interesting.

> (Plus, interact is scary. :-D )

It's not scary! It's neat!

>> I... I want to provide a one-liner for 'detab', but it looks
>> impressively monstrous and I'm not sure I understand it.
>
> If you think that's bad :-)
>
> detab is one of the programs I do not like.  I kept the "direct
> translation" approach up through that, but I think it really hides the
> simplicity there; detab copies its input to its output replacing tabs with
> 1-8 spaces, based on where the tab occurs in a line.  The only interesting
> state dealt with is the count of characters on each line, but that gets
> hidden, not emphasized.
>
> On the other hand, I'm not looking for one-liners; I really want clarity as
> opposed to cleverness.

Well, one-liners generally can be expanded to 2 or 3 lines if you want to add 
descriptive variable names. Better to start with a short version and expand it 
where unclear than have a long unclear one in the first place, right?

>> One final comment: as regards run-length encoding, there's a really
>> neat way to do it. I wrote a little article on how to do it a while
>> ago, so I guess I'll just paste it in here. :)
>
> That *is* neat.
>
> --
> Tommy M. McGuire

Thanks. It took a while to write, but I never really found any place to put it 
up for other people to read.

--
gwern
GSM Submarine E. 510 ddnp building y friends RDI JCET


pgpHvlS1RIXiQ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: US Homeland Security program language security risks

2008-01-06 Thread gwern0
On 2008.01.06 15:54:00 +0100, Achim Schneider <[EMAIL PROTECTED]> scribbled 
0.6K characters:
> Daniel Fischer <[EMAIL PROTECTED]> wrote:
>
> > Am Sonntag, 6. Januar 2008 15:18 schrieb Andrew Coppin:
> > > Daniel Fischer wrote:
> > > > Just because I don't know:
> > > > what bugs would be possible in a language having only the
> > > > instruction return ()
> > >
> > > Bug #1: You cannot write any nontrivial programs. ;-)
> > >
> > That's not a bug, that's a feature.
> >
> That's an interesting task: Design a non-touring complete,
> restricted language in which every expression is decidable, without
> making the language unusable for usual programming problems.

Total functional programming, yay: .

--
gwern
$ Majic shaped Grove infrastructure Spoke BOSS mercur SEIDM BX


pgpvu78AlgsIx.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hackage web page

2008-01-04 Thread gwern0
On 2008.01.02 17:20:04 +, Duncan Coutts <[EMAIL PROTECTED]> scribbled 0.8K 
characters:
> In message <[EMAIL PROTECTED]> "Neil
> Mitchell" <[EMAIL PROTECTED]> writes:
> > Hi,
> >
> > The hackage web page confuses me:
> > http://hackage.haskell.org/packages/hackage.html
>
> > Hackage has now graduated from being a nice idea to being a critial
> > user-focused thingy, which is great. Perhaps the website needs a
> > little bit of thought along those lines. This isn't intended to be a
> > complaint at all - just a new perspective to the people who develop it
> > and probably don't read the web page at all.
>
> You're quite right. We'd welcome a rewrite. You or anyone else is most welcome
> to send us a new version in .html or any other format.
>
> If there are no immediate volunteers then someone should file a bug against 
> the
> HackageDB component in our tracker so we do not forget.
> http://hackage.haskell.org/trac/hackage
>
> Duncan

Is there any Darcs repo for the Hackage HTML, or does it just sort of exist by 
itself on the servers?

--
gwern
Ridge 9705 Rubin WID Venezuela Analyzer NAIAG naphthalene Privacy AGT.


pgpIX6TefhjSv.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [xmonad] Re: XMonad.Layout.NoBorders

2007-12-19 Thread gwern0
On 2007.12.19 10:57:33 -0500, David Roundy <[EMAIL PROTECTED]> scribbled 0.3K 
characters:
> No, I don't have time.  And I'm not sure why one would want no borders
> on floating windows...
>
> David

Perhaps I don't fully understand the issues, but wouldn't such a thing be nice 
for things like MPlayer?

The other day, I happened to play a video through MPlayer, and I noticed (using 
smartBorders/NoBorders)  that there was an ugly border on the left and upper 
edges, and that it detracted from the cinematic experience. It was otherwise 
fullscreen and nice, but not as good as it could've been.

--
gwern
picking FID DES Mole Cap-Stun timers Z7 NAAP 2.6.2. ARC


pgpO7crj8bP7s.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread gwern0
On 2007.12.18 21:07:25 -0500, Brad Larsen <[EMAIL PROTECTED]> scribbled 0.6K 
characters:
> Hi there list,
>
> How would one go about creating a new type for a subset of the integers,
> for (contrived) example just the even integers?  I was thinking of making a
> new type
>
> newtype EvenInt = EvenInt Integer
>
> but the problem with this is that it accepts any integer, even odd ones.
> So to prevent this, the module does not export the constructor for
> it---rather, the module exports a function `mkEvenInt' that creates an
> EvenInt if the given value is acceptable or raises an error otherwise.
>
> What's the right way to do this?  Thanks!
>
> Brad Larsen

Well, I've had cause to do this in the past.

Before I paste the following code, I'd like to emphasize that I wrote it a 
while when I was even more new to Haskell; that it compiles but hasn't been 
tested very much; and that I'm sure there are better ways to do it.

What I wanted to do was to define a type for a subset of 'reals' (floats) which 
are either 0, or positive. The code looks like this:

> {- For many equations and results, it is nonsensical to have negative 
> results, > but we don't want
> to use solely natural numbers because then we lose precision. So we define a
> PosReal type which tries
> to define the subset of real numbers which are 0 or positive; this way the 
> type
> system checks for negative
> results instead of every other function having conditionals checking for
> negative input or output. -}
> newtype PosReal = MakePosReal Float deriving (Show, Eq, Ord)
>
> -- Basic numerical operations on positive reals
> instance Num PosReal where
> fromInteger = toPosReal . fromInteger
> x + y = MakePosReal (fromPosReal x + fromPosReal y)
> x - y = toPosReal ((fromPosReal x) - (fromPosReal y))
> x * y = MakePosReal (fromPosReal x * fromPosReal y)
> abs x | x >= 0 = x
>   | otherwise = x * (-1)
> signum x | x >= 0 = 1
>  | otherwise = (-1)
>
> -- Define division on PosReals
> instance Fractional PosReal where
> x / y = toPosReal ((fromPosReal x) / (fromPosReal y))
> fromRational x = MakePosReal (fromRational x)
>
> -- Positive reals are truncated at 0
> toPosReal :: Float -> PosReal
> toPosReal x
> | x < 0 = MakePosReal 0
> | otherwise = MakePosReal x
> fromPosReal :: PosReal -> Float
> fromPosReal (MakePosReal i) = i
>
> -- Define an instance to allow QuickCheck operations
> instance Arbitrary PosReal where
> arbitrary = liftM3 fraction arbitrary arbitrary arbitrary
> where fraction :: Integer -> Integer -> Integer -> PosReal
>   fraction a b c = fromInteger a + (fromInteger b / (abs 
> (fromInteger c) + 1))


--
gwern
RFI el Audiotel muezzin E911 B61-11 Revolution 5.0i N5P6 espionage


pgpL1SXFCbylD.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New slogan for haskell.org

2007-12-11 Thread gwern0
On 2007.12.12 03:29:13 +0100, Wolfgang Jeltsch <[EMAIL PROTECTED]> scribbled 
1.6K characters:
> Am Mittwoch, 12. Dezember 2007 03:12 schrieb [EMAIL PROTECTED]:
> > FWIW to the discussion about changing the main page, I was reading the CUFP
> > paper and I saw some germane comments (and the writer is apparently one
> > Noel Welsh, whose name I don't see in the thread); the context is a
> > discussion (pg 17) of various members or potential members of the Haskell
> > community and how supported they are:
> >
> >  "What are the needs of the potential programmer? People program to solve
> > prob- lems; so there had better be a clear statement of what kinds of
> > problem the language is good for. The Python community does a good job of
> > this on python.org: "Python is a dynamic object-oriented programming
> > language that can be used for many kinds of software development. It offers
> > strong support for integration with other languages and tools, comes with
> > extensive standard libraries, and can be learned in a few days."
> >
> >  Compare this with the equivalent from haskell.org: "Haskell is a
> >  general purpose, purely functional programming language featuring static
> >  typing, higher-order functions, polymorphism, type classes, and monadic
> >  effects. Haskell compilers are freely available for almost any computer."
> > If you understand all that, you don't need to be here: you're already a
> > Haskell programmer."
>
> Note however that also the Python slogan isn’t so much about solving problems.
> And it also contains technical terms: “dynamic object-oriented programming
> language” instead of “static typing, higher-order functions, polymorphism,
> type classes, and monadic effects”.
>
> Best wishes,
> Wolfgang

The Haskell one is dominated by the technical terms, while the Python one is by 
more generic features. Let's break them down:

> Python is a dynamic object-oriented programming language
> It can be used for many kinds of software development.
> It offers:
> > strong support for integration with other languages and tools,
> > comes with extensive standard libraries
> > and can be learned in a few days."

It uses two technical terms, one of which is extremely common and understood 
(or at least, they think they understand it) by the vast majority of 
programmers, and another which even if you don't know anything about 
static/dynamic, still sounds neat. Dynamic! Neato! *power* *bop* Leaping 
librarians Batman!

Of the rest of the description, it is all touchy-feely: it reassures you that 
it'll be able to do what you ask it to do; it'll play nice with your stuff; 
it's quick and easy to learn; and you won't have to mess around with installing 
stuff, it's brain-dead simple and 'all there'.

Now let's look at the Haskell one.

> "Haskell is a general purpose,

OK, that's good; it's not as emphatic or clear as "It can be used for many 
kinds of software development", but it does mean more or less the same thing.

> purely functional programming language

Oh dear. It's 'functional', and I've heard that means scary weird mathematical 
stuff (first technical term). But I wanted to learn something new, so let's 
look at something else. But Wait, what's this 'purely' business? If it's purely 
functional, doesn't that mean I won't be able to my usual stuff, which is 
presumably impure? (Technical term the second; parity achieved with Python 
description).

> > featuring:

Equivalent to "It offers"

> > static typing

Technical term the third. Mention of static typing is probably on balance bad: 
If you are the kind of sort of cutting-edge programmer, then you are more 
familiar with dynamic languages like Python and Ruby which liberated you from 
the horrors of languages like Java and C. And these Haskell guys are daring to 
suggest you might want to go *back*? If you aren't familiar, then static just 
sounds bad - inert, unbending, rigid and unpleasant. 'I stopped watching that 
show - its plot was just too static.'

It's probably too late now, but I think a better name would've been 'securely 
typed'. :)


> > higher-order functions,

Term the fourth. Even more obscure. Lispers might appreciate this entry though.

> > polymorphism,

Fifth term. This one is good: polymorphism is used elsewhere, and sounds 
friendly.

> > type classes,

Sixth.

OK, seriously, what group besides those who already understand Haskell would 
actually know what type classes are or care? If they have to be mentioned, 
might as well say something more useful (I dunno what, maybe something such as 
'they are like multiple inheritance or interfaces, but more powerful').

> > and monadic effects.

This actually sounds even more obscure and scary than just monads would be, and 
I've seen it oft remarked that monads should just be called soft fluffy 
things...

Seventh.

> > Haskell compilers are freely available for almost any computer."

If the reader is still interested and still takes Haskell seriously after 
puzzling

[Haskell-cafe] New slogan for haskell.org

2007-12-11 Thread gwern0
FWIW to the discussion about changing the main page, I was reading the CUFP 
paper and I saw some germane comments (and the writer is apparently one Noel 
Welsh, whose name I don't see in the thread); the context is a discussion (pg 
17) of various members or potential members of the Haskell community and how 
supported they are:

 "What are the needs of the potential programmer? People program to solve prob-
 lems; so there had better be a clear statement of what kinds of problem the
 language is good for. The Python community does a good job of this on
 python.org: "Python is a dynamic object-oriented programming language that can
 be used for many kinds of software development. It offers strong support for
 integration with other languages and tools, comes with extensive standard
 libraries, and can be learned in a few days."

 Compare this with the equivalent from haskell.org: "Haskell is a
 general purpose, purely functional programming language featuring static
 typing, higher-order functions, polymorphism, type classes, and monadic
 effects. Haskell compilers are freely available for almost any computer." If
 you understand all that, you don't need to be here: you're already a Haskell
 programmer."

--
gwern


pgpdj4pg2URHo.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unsubscribe

2007-12-11 Thread gwern0
On 2007.12.12 09:33:12 +1100, Tim- tigre11 <[EMAIL PROTECTED]> scribbled 2.2K 
characters:
>Very suspicious extension of attachment
>
>Sender:  "Gwern Branwen" <[EMAIL PROTECTED]>
>Recipient:  [EMAIL PROTECTED]
>Subject:  [Haskell-cafe] Software Tools in Haskell
>
>--
>
>[3]avast! Antivirus: Outbound message clean.
>
>Virus Database (VPS): 071210-0, 10/12/2007
>Tested on: 12/12/2007 9:33:52 AM
>avast! - copyright (c) 1988-2007 ALWIL Software.
>
> References
>
>Visible links
>1. mailto:[EMAIL PROTECTED]
>2. mailto:haskell-cafe@haskell.org
>3. http://www.avast.com/

Not very familiar with cryptographic signatures, are you?



--
gwern


pgpsluYDfQYhA.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread gwern0
On 2007.12.05 15:56:49 +0100, John van Groningen <[EMAIL PROTECTED]> scribbled 
0.7K characters:
> [EMAIL PROTECTED] wrote:
>
> >Hey everyone; recently I've been toying around with various methods of 
> >writing a shell and reading the academic literature on such things. The best 
> >prior art on the subject seems to be the ESTHER shell (see 
> >, 
> >, 
> >).
> >
> >Now, ESTHER is a really cool looking shell, but it has two main problems for 
> >me:
> >1) Source doesn't seem to be available anywhere online
> >...
>
> The source code of ESTHER is include with Clean 2.2 in the directory
> Libraries/Hilde of the windows 32 bit binary zip and the sources zip and tar.
>
> Kind regards,
>
> John van Groningen

Thanks for the information! I had no idea it'd be included with the Clean 
compiler package, but it's there alright. Interesting reading, too.

--
gwern


pgpBNEbAkyLnB.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-04 Thread gwern0
Hey everyone; recently I've been toying around with various methods of writing 
a shell and reading the academic literature on such things. The best prior art 
on the subject seems to be the ESTHER shell (see 
, 
, 
).

Now, ESTHER is a really cool looking shell, but it has two main problems for me:
1) Source doesn't seem to be available anywhere online
2) It's written in Clean and not Haskell

No problem. All the hard stuff is done, and there's like a good 50 pages of 
documentation, so how hard could it be? Clean is practically Haskell anyway.

But immediately I ran into a road-block:

 "The shell is built on top of Clean's hybrid static/dynamic type system and 
its dynamic I/O run-time support. It allows programmers to save any Clean 
expression, i.e a graph that can contain data, references to functions, and 
closures to disk. Clean expressions can be written to disk as a _dynamic_, 
which contains a representation of their (polymorphic) static type, while 
preserving sharing. Clean programs can load dynamics from disk and use run-time 
type pattern matching to reintegrate it into the statically-typed program."

The Data.Dynamic library seems to do everything as far as dynamic types and 
run-time pattern matching goes, but I haven't figured out how one could write 
Haskell expressions to disk, like Clean's system 
 apparently 
allows.

Does anyone know if there are any neat or tricky ways this could be done? 
Projects, extensions, whatever?

On #haskell, quicksilver did tell me of one neat way to serialize various stuff 
through Data.Binary by using ADTs along the lines of the following simple 
example:

--

module Main (main)
where
import Data.Binary
data Math = Add | Subtract | Multiply
deriving Show

eval :: (Num a) => Math -> a -> a -> a
eval f = case f of
   Add -> (+)
   Subtract -> (-)
   Multiply -> (*)

instance Binary Math where
  put Add = putWord8 0
  put Subtract = putWord8 1
  put Multiply = putWord8 2
  get = do tag_ <- getWord8
   case tag_ of
 0 -> return Add
 1 -> return Subtract
 2 -> return Multiply


main = do encodeFile "tmp.s" [Add, Subtract, Multiply]
  a <- decodeFile "tmp.s"
  putStr $ show (a :: [Math])

--

Since from my Lisp days I know that code is data, it strikes me that one could 
probably somehow smuggle Haskell expressions via this route although I am not 
sure this is a good way to go or even how one would do it (to turn, say, a list 
of the chosen ADT back into real functions, you need the 'eval' function, but 
apparently eval can only produce functions of the same type - so you'd need to 
either create as many adts and instances as there are varieties of type 
signatures in Haskell '98 and the libraries, I guess, or somehow encode in a 
lambda calculus). Is that a route worth pursuing?

--
gwern


pgpQSheGC4OtM.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-04 Thread gwern0
On 2007.12.04 12:12:04 +, Neil Bartlett <[EMAIL PROTECTED]> scribbled 2.2K 
characters:
> Hi Gwern,
>
> Shu-thing is great fun!
>
> I think Monadius isn't compiling because most of the source files are
> missing; you only have Main.hs in there.
>
> Regards
> Neil

Oh - you're absolutely right. For some reason, cabal's sdist didn't include all 
the files. Weird.

But I think I've fixed it:
*

Looking at the contents of the tar ball, it now seems to have everything, and 
Monadius does indeed successfully 'cabal install Monadius'.

Sorry everyone!

--
gwern


pgpOElvt7gVHo.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-03 Thread gwern0
Hi everyone. With the permission of the authors, I'd like to announce the 
release & upload to Hackage of two games written in Haskell (you may've seen 
them mentioned here once or twice before):

*Monadius
*Shu-thing

They are both scrolling 2 dimensional arcade shooting games which use 3D vector 
graphics. Shu-thing is a fairly simpler upwards scrolling shooter with one 
level and geometric objects; Monadius is a sort of clone/homage to the classic 
arcade game Gradius, and I find it quite fun (although I have yet to beat it).

You can find screenshots and original here:
*

The Hackage pages:
*
*

--

They both have dependencies on GLUT, and it's definitely advisable to have 3D 
acceleration enabled on your system. I've only tested them with GHC 6.8.1 and 
up (where they work fine) on my Gentoo Linux box.

You should be able to 'cabal install' Shu-thing, but Monadius doesn't compile 
successfully for reasons I don't understand.

--

My changes to the programs in question are not terribly major - largely 
Cabalizing them, formatting and making stylistic changes, stomping most -Wall 
messages, and occasionally changing algorithms or attempting to optimize them. 
In the case of Monadius, I removed all the Windows-specific material (the audio 
files were apparently copyright violations, so no big loss) and improved 
storage of replay files.

I'd like to thank Takayuki Muranushi for answering my questions about the code 
and giving permission to update them. I hereby release all my changes into the 
public domain.

--
gwern


pgpqnLn4sbrdT.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe