Re: [Haskell-cafe] [Haskell] ANN: Haskell bindings for the igraph C library

2012-12-17 Thread Nils Schweinsberg

Am 16.12.2012 20:24, schrieb Jason Dagit:

How does this compare with fgl? http://hackage.haskell.org/package/fgl


FGL is a pure Haskell library while our haskell-igraph package uses the 
foreign function interface to run all graph-related calculations in C 
the C library igraph (I haven't implemented any graph algorithms). The 
runtime performance with our igraph library should be the same as if 
you'd be using the native C library (if you ignore the small 
Haskell-C-Haskell overhead).


It is also seems to be more of a higher level library. As user you don't 
have to worry about node-IDs/labels or whether your graph is static or 
not (in the FGL context). Using features like GADTs and type 
families/associated types it is possible to keep track of informations 
like whether or not your graph is directed/weighted or not, while in FGL 
all graphs are by default directed and unweighted. Consider for example


  edges :: Graph d a - [Edge d a]

  -- directed, unweighted graph
  g :: Graph D a

  -- undirected, weighted graph
  w :: Graph (Weighted U) a

which leads to

  edges g :: [Edge D a]
  edges w :: [Edge (Weighted U) a]

or even functions like

  toUndirected :: (IsDirected d, E (ToUndirected d) a)
   = Graph d a
   - Graph (ToUndirected d) a

  toDirected   :: (IsUndirected u, E (ToDirected u) a)
   = Graph u a
   - Graph (ToDirected u) a

which evaluate to

  toUndirected g :: Graph U a
  toDirected   w :: Graph (Weighted D) a

This is even revertable, and `toDirected . toUndirected == id` while the 
FGL function `undir` simply adds all missing edges and loses track of 
what the original/directed graph looked like.


Maybe George has more details on why he wanted to use igraph instead of FGL.


- Nils

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


[Haskell-cafe] ANN: Haskell bindings for the igraph C library

2012-12-16 Thread Nils Schweinsberg

Hi Haskellers, dear igraph community,

I am pleased to announce the release of our (inofficial) Haskell 
bindings to the igraph C library. igraph is a powerfull library for 
creating and manipulating directed, undirected and weighted graphs. Our 
package offers a complete coverage of all functions on structural 
properties of graphs.


Compared to the official packages for R and Python it is the first 
library that offers type level distinction between directed/undirected 
and weighted graphs. Haskells type system allows to keep track of the 
types of your nodes and whether or not your graph and its edges are 
directed or undirected, weighted or unweighted.


Haskell graphs may contain any Haskell value as node values, kind of 
similar to Pythons attributes.


igraph on hackage, the official package database for Haskell: 
http://hackage.haskell.org/package/igraph (requires the current 
igraph-0.6 C library)


The official igraph website: http://igraph.sourceforge.net/index.html

Until hackage generates the haddock documentation, the documentation is 
also available at: http://hs.nils.cc/igraph-0.1/html/index.html



Any feedback is appreciated,

- Nils Schweinsberg
- George Giorgidze

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


Re: [Haskell-cafe] haskell cryptogaphic libraries

2012-08-24 Thread Nils Schweinsberg
Am 24.08.2012 14:47, schrieb marcmo:
 * AES Encryption/Decryption (CBC-Mode)

For AES there is the SimpleAES package[1] which is super easy to use:

 import qualified Data.ByteString  as BS
 import   Data.ByteString.Lazy as BL
 
 import Codec.Crypto.SimpleAES
 
 key :: IO Key
 key = BS.readFile key
 
 encrypt :: ByteString - IO ByteString
 encrypt bs = do
   k - key
   encryptMsg CBC k bs
 
 decrypt :: ByteString - IO ByteString
 decrypt bs = do
   k - key
   return $ decryptMsg CBC k bs

(note that the key is a strict ByteString while the encrypted/decrypted
data is lazy)

[1]: http://hackage.haskell.org/package/SimpleAES

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


[Haskell-cafe] GSoC proposal: Units for GHC

2012-04-04 Thread Nils Schweinsberg

Hi Haskell-Cafe  GHC-users!

I'm looking to apply for the GSoC and since I've worked on GHC before 
I'd like to continue to do so. My proposal would be something that 
tempted me (as a physics student) for a while: Units for Haskell/GHC.


This project has been suggested for a long time on the GHC wiki, and 
there is already a lot of work done for other languages like ML, F# 
etc[1]. I have tried to implement e.g. the unification algorithm from 
the Types for Units-of-Measure in F# talk[2] for an abstract syntax 
tree[3] and it was pretty much straight forward. As I see it, the 
project would consist of:


 1.) Find appropriate rules/algorithms for unit analysis. Most (if not 
all?) of this should be covered in those papers/talks on [1].


 2.) Applying the rules to the Haskell syntax tree used in GHC.

I have approximately 3 years of experience with Haskell, I worked for 
the database research group[4] at the University of Tübingen (Germany) 
on the Database Supported Haskell[5] library. I've done most of the 
coding for the monad comprehension[6] extension, which has been added to 
the latest GHC release version. I'm already quite familiar with the GHC 
internals of the compiler/typechecker, and even though I'd have to look 
up how exactly type interference etc. works in GHC (as I've only *used* 
it, but never tried to understand/modify it) I'm confident that the work 
on GHC itself should be doable in the given timeframe.


So my questions would be:

Do you think this is a appropriate GSoC project?
What should I include in the application/project proposal?
Anything else? Opinions, suggestions?

I realize that I'm kind of late and probably should have written this 
email a long time ago. But there are still 2 days left for the student 
application and hopefully I'll get some good feedback by then.




- Nils



[1]: http://research.microsoft.com/en-us/um/people/akenn/units/index.html
[2]: 
http://research.microsoft.com/en-us/um/people/akenn/units/MLWorkshop2008.pdf

[3]: https://github.com/mcmaniac/units/blob/master/src/Unification.hs
[4]: http://db.inf.uni-tuebingen.de/team
[5]: http://hackage.haskell.org/package/DSH
[6]: http://db.inf.uni-tuebingen.de/files/giorgidze/haskell2011.pdf

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


Re: [Haskell-cafe] GSoC proposal: Units for GHC

2012-04-04 Thread Nils Schweinsberg

Am 04.04.2012 13:48, schrieb Jurriën Stutterheim:

This sounds pretty cool and useful. How much of this can be implemented in a 
library and how much of this would need to be supported on a compiler level? 
Ideally, most of this would be solved on the library level.


The compiler would have to know how to typecheck units, e.g. the 
addition (+) would combine two values of the same unit, the (/) 
operation would divide them:


  (+) :: a - a - a
  (/) :: a - b - a/b

The idea is to have the compiler complain whenever you try to add b to 
a or if you expect something other than a/b as result from a 
division. This would require modifications to GHC at compiler level. A 
library could offer some basic units (SI units for example) and maybe 
even unit aliases (N = kg*m/s^2), but I don't see how the core 
of this unit verification system could be placed into a library.



- Nils

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


[Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Hi,

I'm having a few problems with cabals build-type configure on windows, 
especially with the packages curl and pcre-light. Both fail either with:


* Missing C library: pcre
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Hi,

I'm having a few problems with cabals build-type configure on windows, 
especially with the packages curl and pcre-light. Both fail either with:


configure: error: curl libraries not found, so curl package cannot 
be built


Configuring pcre-light-0.4...
cabal: Missing dependency on a foreign library:
* Missing C library: pcre

Both libraries (pcre3.dll and libcurl.dll) are in my PATH variable, and 
I can build other non-haskell-applications which are using these via 
mingws gcc compiler. But still, somehow cabal seems unable to find them. 
Using the recommanded --extra-include-dirs and --extra-lib-dirs 
won't help either. Or is cabal looking for different files than those 
two .dlls?


Can anyone help me on this? Did anyone manage to build curl/pcre-light 
on windows?


My current configuration is MinGW/msys with gcc 4.5, ghc 6.12.3, 
cabal-install 0.8.2, cabal 1.8.0.6. libcurl.dll and pcre.dll are the 
latest builds from the official webpages.



Thanks for any Help,
Nils


PS: Sorry for the previous (incomplete) mail.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Am 11.11.2010 13:41, schrieb Stephen Tetley:

Do you have the headers installed as well as the dlls?

For headers, MSys will have a search path of at least these two directories

msys\1.0\local\include
MinGW\include


Is there an environment variable for this? As I said, I tried using 
--extra-include-dirs with MinGW\include.

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


Re: [Haskell-cafe] build-type: configure on windows

2010-11-11 Thread Nils Schweinsberg

Am 11.11.2010 14:25, schrieb Stephen Tetley:

I'm not sure about an environment variable. Adding the MinGW\ prefix
looks wrong, you may have to experiment with paths and forward or back
slash separators a bit. I can't remember which convention (Windows)
cabal uses.


I tried every possible combination. Apparently, the configure script is 
completly ignoring those --extra-..-dirs flags.

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


Re: [Haskell-cafe] windows network programming

2010-11-02 Thread Nils Schweinsberg

Am 02.11.2010 01:20, schrieb Paulo Tanimoto:

http://hackage.haskell.org/package/network


You just have to remember that you need to call withSocketsDo on 
windows before doing anything with the network library.

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


Re: [Haskell-cafe] windows network programming

2010-11-02 Thread Nils Schweinsberg

Am 02.11.2010 19:57, schrieb Michael Litchard:

got any urls with examples?


Sure, see this short server-client-ping-pong application.

By the way, I noticed that you don't need withSocketsDo on windows 7, 
but I guess it's there for a reason for older windows versions. :)




import Control.Concurrent
import Network
import System.IO

main :: IO ()
main = withSocketsDo $ do
forkIO waitAndPong
ping

-- The basic server
waitAndPong :: IO ()
waitAndPong = do
socket - listenOn (PortNumber 1234)
(handle,_,_) - accept socket
hSetBuffering handle LineBuffering
incoming - hGetLine handle
putStrLn (  ++ incoming)
hPutStrLn handle pong

-- The basic client
ping :: IO ()
ping = do
handle - connectTo localhost (PortNumber 1234)
hSetBuffering handle LineBuffering
hPutStrLn handle ping
incoming - hGetLine handle
putStrLn (  ++ incoming)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsing workflow

2010-10-31 Thread Nils Schweinsberg

Hi!

I'm having a really hard time to write a correct parser for a small 
language I've developed. I have been trying to write a parser using 
parsec, but always get a lot of error messages like unexpected \n, 
expected ..., new-line or... when trying to run the parser. Then I read 
about the happy parser and really liked the separation of lexing the 
text into tokens and parsing the actual logic behind those tokens. Since 
I couldn't get familiar with the lexer alex I gave up on the 
alex-happy-approach again and went back to parsec. But with that 
lexer-parser idea on my mind, my parser currently looks a lot like a 
lexer. So I came up with the idea of using a combination of parsec and 
happy, where I generate a list of tokens for my text via parsec and 
analyse it with happy.



My questions would be:

- Is this a valid approach?

- What is your workflow on parsing complex data structures?

- What about performance? Since my project is going to be an interpreted 
language parsing performance might be interesting aswell. I've read that 
happy is in general faster than parsec, but what if I combine both of 
them as I said above? I guess that parsing a simple list of tokens 
without any nested parser structures would be pretty fast?


- Do you have any other ideas on how to improve my parser?

- What are your general thoughts on happy vs. parsec?


Thanks for any replies,

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


Re: [Haskell-cafe] Parsing workflow

2010-10-31 Thread Nils Schweinsberg

Am 31.10.2010 16:50, schrieb Ozgur Akgun:
 I don't know if you've already used it, but Parsec includes some kind of
 a lexer through the Language
 
http://hackage.haskell.org/packages/archive/parsec/3.1.0/doc/html/Text-Parsec-Language.html 


 and Token
 
http://hackage.haskell.org/packages/archive/parsec/3.1.0/doc/html/Text-Parsec-Token.html 


 modules.
 You can start by having a look at the makeTokenParser
 
http://hackage.haskell.org/packages/archive/parsec/3.1.0/doc/html/Text-Parsec-Token.html#v:makeTokenParser 
function.


Yeah, I've read about the TokenParser, but since my language is not a 
typical programming language it's use is very limited for me. My 
language is basicly a combination of a scripting language and a markup 
language like, for example, markdown. And parsing that scripting 
language isn't the difficult part so far...

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


Re: [Haskell-cafe] Parsing workflow

2010-10-31 Thread Nils Schweinsberg

Am 31.10.2010 16:53, schrieb Vo Minh Thu:

I can't really tell from your description, but maybe this is because
of the way Parsec works when it deals with alternatives. When you
combine several parsers with e.g. '|' or 'choice', an alternative
that can consume some input but fails will make the whole combined
parser fail too. So you have to either factorize you parsers or use
the 'try'. See the documentation for 'try' at
http://hackage.haskell.org/packages/archive/parsec/3.1.0/doc/html/Text-Parsec-Prim.html
.



This is exactly what gives me headaches. It's hard to tell where you 
need try/lookAhead and where you don't need them. And I don't really 
feel comfortable wrapping everything into try blocks...

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


Re: [Haskell-cafe] Ultra-newbie Question

2010-09-18 Thread Nils Schweinsberg

Am 18.09.2010 09:51, schrieb Christopher Tauss:

I am trying to write a function that takes a list and returns the last n
elements.


last_n n = fst . foldr step ([], n)
  where
step _ (xs, 0) = (xs, 0)
step x (xs, n) = (x:xs, n-1)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: happstack-auth-0.2

2010-09-18 Thread Nils Schweinsberg

Am 17.09.2010 22:06, schrieb Nils Schweinsberg:

[1] http://hackage.haskell.org/package/happstack-auth


Hackage fails to build this package:

http://hackage.haskell.org/packages/archive/happstack-auth/0.2/logs/failure/ghc-6.12

However, Crypto == 4.* should be on hackage:

http://hackage.haskell.org/package/Crypto-4.2.1

Is there anything I can do with my package to get this to build?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: happstack-auth-0.2

2010-09-17 Thread Nils Schweinsberg

Hey!

I'd like to announce the release of happstack-auth-0.2 [1]. It offers an 
easy (and secure) way to implement user authentication for Happstack web 
applications with a lot of high level functions and a solid 
Happstack-State back-end.


The original project got started by MightyByte, until I took it over and 
improved the whole package. As a result, the API has changed a lot and 
if you were using the old happstack-auth you might consider rewriting 
your application to use the new api.* However, your applications state 
will be completely compatible with the new version and be migrated 
automatically.


The package got uploaded to hackage and can now be installed via cabal:

cabal install happstack-auth

It should build with both, the current stable release of happstack 
(0.5.0.2) and the latest darcs version (0.5.1). If there are any 
errors/bugs during building/running, please contact me!


A demonstration website is up and running with about 30 lines of code (+ 
html templates and the actual happstack server code) at [2].


If you don't want to wait until hackage rendered the haddock pages, you 
can take a look at the (latest git version of the) API at [3].




Hope you enjoy it! :)

- Nils Schweinsberg / McManiaC



* You can still use the old state-query/update constructors by importing 
Happstack.Auth.Internal, although you'll miss a lot of features like 
session management etc. In addition, MightyBytes old repo should be 
still available at [4].


[1] http://hackage.haskell.org/package/happstack-auth
[2] http://n-sch.de/happstack-auth
[3] http://n-sch.de/hdocs/happstack-auth
[4] http://github.com/mightybyte/happstack-auth
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Combining applicative with arrows?

2010-09-10 Thread Nils Schweinsberg

Hey,


I just wondered if you can define Applicative instances for arrows? 
Basicly what I thought of is:


I have a type for my arrow which is CollectA (using HXT here):

type CollectA a = SomeArrow XmlTree a

And my datatype which I want to construct:

data Test = Test
{ testString:: String
, testInt   :: Int
}

With the functions:

collectString :: CollectA String
collectInt:: CollectA Int

Now, what I currently do is something like:

collectTest :: CollectA Test
collectTest = getChildren
   someOtherArrow  -- etc...
   proc foo - do
  s - collectString - foo
  i - collectInt- foo
  returnA - Test s i

With Applicatives that proc-do-part would become:

collectTest' :: CollectA Test
collectTest' = ... -- arrow stuff
Test $ collectString
* collectInt

Is something like this possible? I don't understand that proc part 
good enough to see what it's actually doing there, maybe someone with a 
better understanding for this could help out? :)



Thx,

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


Re: [Haskell-cafe] Style and a problem

2010-09-09 Thread Nils Schweinsberg

Am 09.09.2010 22:55, schrieb Wanas:

Hey all,

So I have a two part question (I'm new to haskell, so you can throw all
your mugs at me).

a) I want to write a function that generates lists of lists of size $n$.
All having the property that sum lst = sum [1..n].
a-1) After that, I want to remove all permutations. My idea of doing
this is to get all lists from the first function and create a new list
with the property that if sorted list A is not in the list, add it.

b-2) I think that's too much questions, but I want to get the hang of
this quickly (it was kickass for the few things I've tried out).


Something like this?

import Data.List

newList :: Int - [[Int]]
newList n = myNub
[ l | l - undefined -- not really sure how you want
 -- to generate these lists :)
, sum l == sum [1..n]
]

myNub :: (Ord a) = [[a]] - [[a]]
myNub = nubBy (\a b - sort a == sort b)


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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Nils Schweinsberg

On 26.07.2010 23:55, Ozgur Akgun wrote:

I think it is pretty cool as well. But I think there is a problem with
viewing it as a wildcard.

let's say we define the following:

(??) = flip

foo :: a - b - c
foo ?? x :: a - c

Perfect!

But saying ?? can be used as a wildcard might in the following wrong
perception:

foo x ?? :: b - c -- WRONG


This looks interesting. I played around with this for a bit:


{-# LANGUAGE MultiParamTypeClasses
   , FunctionalDependencies
   , FlexibleInstances
   #-}

class Wildcard f v r | f - v r where
(??) :: f - v - r

instance Wildcard (a - b - c) b (a - c) where
(??) = flip

instance Wildcard (b - c) b c where
(??) = id

f :: String - Int - String
f s i = s ++ show i

a :: String - String
a = (f ?? 5)

b :: Int - String
b = (f Int:  ??)



Sadly, this won't typecheck:


pattern.hs:19:0:
Couldn't match expected type `Int' against inferred type `[Char]'
  Expected type: Int
  Inferred type: String
When using functional dependencies to combine
  Wildcard (b - c) b c,
arising from the dependency `f - a r'
in the instance declaration at pattern.hs:12:9
  Wildcard (String - Int - String) Int (String - String),
arising from a use of `??' at pattern.hs:19:5-10
When generalising the type(s) for `a'


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


Re: [Haskell-cafe] Re: Is my code too complicated?

2010-07-04 Thread Nils Schweinsberg
On Sun, 4 Jul 2010 15:47:21 +0200, Ertugrul Soeylemez e...@ertes.de wrote:
 This requires a bunch of type system extensions, though, most notably
 the UndecidableInstances extension.  But it's safe to use here.

Probably a bit off topic, but whats wrong with UndecidableInstances? Where
is it safe to use, when would you avoid it and what can go wrong here?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



[Haskell-cafe] MState: A consistent State monad for concurrent applications

2010-07-02 Thread Nils Schweinsberg

Hi,

I have been trying to use the State monad for concurrent applications 
and came up with a little library.[1] My MState uses an IORef to 
maintain the state between different threads. The library also offers a 
simple way to fork off new threads using its own forkM function. This 
function will asure that every thread in an evalMState/execMState 
call will be finished before the final result is returned.


The library is also on github.com.[2] Please let me know what you think 
of it and whether or not I should put it on hackage.




Cheers,
Nils Schweinsberg


[1] http://n-sch.de/hdocs/mstate/Control-Concurrent-MState.html
[2] http://github.com/mcmaniac/mstate
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MState: A consistent State monad for concurrent applications

2010-07-02 Thread Nils Schweinsberg

On 02.07.2010 20:05, Jason Dagit wrote:

In other words, don't be shy!


Ok, thanks for the reply! :) However, a question about haddock:

evalMState :: Forkable m
   = MState t m a  -- ^ Action to evaluate
   - t -- ^ Initial state value
   - m a

This (and run-/execMState) gets rendered incorrectly. Action to 
evaluate is completly lost and Initial state value has moved one 
upwards to the MState t m a. Is that a haddock bug or my fault?

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


Re: [Haskell-cafe] MState: A consistent State monad for concurrent applications

2010-07-02 Thread Nils Schweinsberg

And here wo go. MState on hackage:

http://hackage.haskell.org/package/mstate

My first hackage library. :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for GUI (WX) example code

2010-07-02 Thread Nils Schweinsberg

On 02.07.2010 23:02, Günther Schmidt wrote:

Hi all,

I'd be interested in studying GUI (wxhaskell) code. Does anyone have
links to good gui code?


Not wxHaskell, but I just wrote a very small gtk2hs application.[1] 
Should give you a quick overview of how things work with gtk. :)



[1] http://github.com/mcmaniac/whoLogin/blob/master/src/whologin.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MState: A consistent State monad for concurrent applications

2010-07-02 Thread Nils Schweinsberg

On 03.07.2010 03:27, Matthew Gruen wrote:

Awesome. I needed something like that once, too, down to the same type
signature for the fork function. Here's an instance from my code:

instance MonadFork (ReaderT s IO) where
 fork newT = ask= liftIO . forkIO . runReaderT newT


I've added this instance to the Forkable class and a few other instances 
to the MState (Fix, Reader, Writer, Cont and Error). I hope they're all 
correct.


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


Re: [Haskell-cafe] ANN: bitspeak 0.0.1

2010-06-21 Thread Nils Schweinsberg

On 21.06.2010 23:50, Maurí­cio CA wrote:

Hi, all,

bitspeak is a small proof of concept application that allows
writing text using only two commands (yes/no, 1/2, top/down etc.).


Looks cool! Did you forget any dependencies tho? I get the following error:


0:16 nils` cabal update
Downloading the latest package list from hackage.haskell.org
0:17 nils` cabal install bitspeak
Resolving dependencies...
Configuring bitspeak-0.0.1...
Preprocessing executables for bitspeak-0.0.1...
Building bitspeak-0.0.1...

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


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