Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Raphael Gaschignard
I think it might be impossible with type families. I don't think it's
possible to differentiate with type families something like T a a, and T a
b, with b different from a.

I think that you would need overlap to write this.
Here'sthe
GHC page on it. With type families you can do overlap, but in that
case, the result of unification must be the same. So basically :

 T a a === T a b (with b set to a)

whereas the "intuitive" way of doing Find requires a way of differentiating
between these two cases.


On Wed, Feb 27, 2013 at 4:33 PM, Dmitry Kulagin wrote:

> Hi,
>
> I try to implement typed C-like structures in my little dsl.
> I was able to express structures using type-level naturals (type Ty is
> promoted):
>
> > data Ty = TInt | TBool | TStruct Symbol [Ty]
>
> That allowed to implement all needed functions, including type-level
> function:
>
> > type family Get (n :: Nat) (xs :: [Ty]) :: Ty
>
> But it is not very convenient to identify struct's fields using naturals,
> and I wanted to change Ty definition to:
>
> > data Ty = TInt | TBool | TStruct Symbol [(Symbol, Ty)]
>
> It is much closer to how C-struct looks, but I was unable to implement
> required type function:
>
>  > type family Find (s :: Symbol) (xs :: [(Symbol,Ty)]) :: Ty
>
> Which just finds a type in a associative list.
>
> Could someone give me a hint, how to do it?
> Or perhaps, is it just impossible thing to do?
>
> Thanks!
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Running out of space while concatinating a list of bytestring

2013-02-27 Thread C K Kashyap
Hi,

I have the following code - It looks like things go okay until
concatination is attempted. I get the following output

There are 2258 ByteStrings
*** Exception: : hPutBuf: resource exhausted (Not enough space)

I am thinking that I should do strict concatination at each point in the
support function - how can I go about doing so? (BS is the lazy.char8
bytestring)


connectionGetNBytes :: NC.Connection -> Int -> IO ByteString
connectionGetNBytes c n = do
bs <- connectionGetNBytes' c n
putStrLn ("There are " ++ (show (length bs)) ++ "
ByteStrings")
return (BS.concat bs)

connectionGetNBytes' :: NC.Connection -> Int -> IO [ByteString]
connectionGetNBytes' _ 0 = return []
connectionGetNBytes' c n = do
l <- NC.connectionGet c n
let ll = BS.length l
remaining <- connectionGetNBytes' c (n - ll)
return (l:crlfStr:remaining)


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


Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Aleksey Khudyakov
On 27 February 2013 12:01, Raphael Gaschignard  wrote:
> I think it might be impossible with type families. I don't think it's
> possible to differentiate with type families something like T a a, and T a
> b, with b different from a.
>
It's indeed impossible to write such type function using type
families. It will be possible with new closed type familes (they are
in GHC head already).

But for now it's possible to use overlapping instances and fundeps.
Implementation of type level equality is simple and it's only
instances which need ovelap.

-- | Type class for type equality.
class  TypeEq (a :: α) (b :: α) (eq :: Bool) | a b -> eq
instance   TypeEq a a True
instance eq ~ False => TypeEq a b eq


Implementation of lookup by key is relatively straightforward. Note
that it doesn't check that key is unique.

data k :> v
infix 6 :>

-- | Lookup type for given key
class TyLookup (map :: [*]) (k :: *) (v :: *) | map k -> v where

class TyLookupCase (map :: [*]) (k :: *) (v :: *) (eq :: Bool) | map k
eq -> v where

instance ( TypeEq k k' eq
 , TyLookupCase (k :> v ': xs) k' v' eq
 ) => TyLookup  (k :> v ': xs) k' v' where

instance TyLookupCase (k  :> v  ': xs) k v True  where
instance TyLookup xs k v => TyLookupCase (k' :> v' ': xs) k v False where

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


[Haskell-cafe] Help to write type-level function

2013-02-27 Thread oleg

Dmitry Kulagin wrote:
> I try to implement typed C-like structures in my little dsl.

HList essentially had those
http://code.haskell.org/HList/

> I was unable to implement required type function:
> type family Find (s :: Symbol) (xs :: [(Symbol,Ty)]) :: Ty
> Which just finds a type in a associative list.

HList also implemented records with named fields. Indeed, you need a
type-level lookup in an associative list, and for that you need type
equality. (The ordinary List.lookup has the Eq constraint, doesn't
it?) 

Type equality can be implemented with type functions, right now.
http://okmij.org/ftp/Haskell/typeEQ.html#TTypeable

(That page also defined a type-level list membership function).






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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Tom Murphy
There's another one...
http://3.bp.blogspot.com/-0-NT1rzFpik/Tpe4sb18gOI/AuM/j2BHO_TgLi4/s1600/calvinball.jpg

Tom

On Tue, Feb 26, 2013 at 7:07 PM, Ben Lippmeier  wrote:
>
> On 27/02/2013, at 10:28 , Corentin Dupont  wrote:
>
>> Hello everybody!
>> I am very happy to announce the beta release [1] of Nomyx, the only game 
>> where You can change the rules.
>
> Don't forget 1KBWC: http://www.corngolem.com/1kbwc/
>
> Ben.
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Dmitry Kulagin
That seems to be very relevant to my problem (especially HList.Record).
Am I right that UndecidableInstances is required mostly because of eq on
types, like in this instances:


class HRLabelSet (ps :: [*])
instance HRLabelSet '[]
instance HRLabelSet '[x]

instance ( HEq l1 l2 leq
 , HRLabelSet' l1 l2 leq r
 ) => HRLabelSet (LVPair l1 v1 ': LVPair l2 v2 ': r)

so the usage of the extension is unavoidable for my purposes?

Thank you!


On Wed, Feb 27, 2013 at 12:28 PM,  wrote:

>
> Dmitry Kulagin wrote:
> > I try to implement typed C-like structures in my little dsl.
>
> HList essentially had those
> http://code.haskell.org/HList/
>
> > I was unable to implement required type function:
> > type family Find (s :: Symbol) (xs :: [(Symbol,Ty)]) :: Ty
> > Which just finds a type in a associative list.
>
> HList also implemented records with named fields. Indeed, you need a
> type-level lookup in an associative list, and for that you need type
> equality. (The ordinary List.lookup has the Eq constraint, doesn't
> it?)
>
> Type equality can be implemented with type functions, right now.
> http://okmij.org/ftp/Haskell/typeEQ.html#TTypeable
>
> (That page also defined a type-level list membership function).
>
>
>
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Dmitry Kulagin
Very clear solution, I will try to adopt it.

Thank you!


On Wed, Feb 27, 2013 at 12:17 PM, Aleksey Khudyakov <
alexey.sklad...@gmail.com> wrote:

> On 27 February 2013 12:01, Raphael Gaschignard  wrote:
> > I think it might be impossible with type families. I don't think it's
> > possible to differentiate with type families something like T a a, and T
> a
> > b, with b different from a.
> >
> It's indeed impossible to write such type function using type
> families. It will be possible with new closed type familes (they are
> in GHC head already).
>
> But for now it's possible to use overlapping instances and fundeps.
> Implementation of type level equality is simple and it's only
> instances which need ovelap.
>
> -- | Type class for type equality.
> class  TypeEq (a :: α) (b :: α) (eq :: Bool) | a b -> eq
> instance   TypeEq a a True
> instance eq ~ False => TypeEq a b eq
>
>
> Implementation of lookup by key is relatively straightforward. Note
> that it doesn't check that key is unique.
>
> data k :> v
> infix 6 :>
>
> -- | Lookup type for given key
> class TyLookup (map :: [*]) (k :: *) (v :: *) | map k -> v where
>
> class TyLookupCase (map :: [*]) (k :: *) (v :: *) (eq :: Bool) | map k
> eq -> v where
>
> instance ( TypeEq k k' eq
>  , TyLookupCase (k :> v ': xs) k' v' eq
>  ) => TyLookup  (k :> v ': xs) k' v' where
>
> instance TyLookupCase (k  :> v  ': xs) k v True  where
> instance TyLookup xs k v => TyLookupCase (k' :> v' ': xs) k v False where
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Running out of space while concatinating a list of bytestring

2013-02-27 Thread C K Kashyap
Oops, false alarm.
Please ignore - and sorry about it.
Regards,
Kashyap


On Wed, Feb 27, 2013 at 1:32 PM, C K Kashyap  wrote:

> Hi,
>
> I have the following code - It looks like things go okay until
> concatination is attempted. I get the following output
>
> There are 2258 ByteStrings
> *** Exception: : hPutBuf: resource exhausted (Not enough space)
>
> I am thinking that I should do strict concatination at each point in the
> support function - how can I go about doing so? (BS is the lazy.char8
> bytestring)
>
>
> connectionGetNBytes :: NC.Connection -> Int -> IO ByteString
> connectionGetNBytes c n = do
> bs <- connectionGetNBytes' c n
> putStrLn ("There are " ++ (show (length bs)) ++ "
> ByteStrings")
> return (BS.concat bs)
>
> connectionGetNBytes' :: NC.Connection -> Int -> IO [ByteString]
> connectionGetNBytes' _ 0 = return []
> connectionGetNBytes' c n = do
> l <- NC.connectionGet c n
> let ll = BS.length l
> remaining <- connectionGetNBytes' c (n - ll)
> return (l:crlfStr:remaining)
>
>
> Regards,
> Kashyap
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
I think it would be harder to implement a computer version of 1KBWC and
Calvin ball!! Have to think of it ;)

On Wed, Feb 27, 2013 at 9:48 AM, Tom Murphy  wrote:

> There's another one...
>
> http://3.bp.blogspot.com/-0-NT1rzFpik/Tpe4sb18gOI/AuM/j2BHO_TgLi4/s1600/calvinball.jpg
>
> Tom
>
> On Tue, Feb 26, 2013 at 7:07 PM, Ben Lippmeier  wrote:
> >
> > On 27/02/2013, at 10:28 , Corentin Dupont 
> wrote:
> >
> >> Hello everybody!
> >> I am very happy to announce the beta release [1] of Nomyx, the only
> game where You can change the rules.
> >
> > Don't forget 1KBWC: http://www.corngolem.com/1kbwc/
> >
> > Ben.
> >
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Dmitry Kulagin
Hi Aleksey,

Unfortunately, your solution does not work for me (ghc 7.6.2). I reduced
the problem to:

-- | Type class for type equality.
class  TypeEq (a :: α) (b :: α) (eq :: Bool) | a b -> eq
instance   TypeEq a a True
-- instance TypeEq a b False
instance eq ~ False => TypeEq a b eq

f :: TypeEq Int Int True => Int
f = 1

When I try to invoke f, I get overlapping instances error:
Overlapping instances for TypeEq * Int Int 'True
  arising from a use of `f'
Matching instances:
  instance TypeEq k a a 'True -- Defined at Test.hs:14:24
  instance eq ~ 'False => TypeEq k a b eq -- Defined at Test.hs:16:10

Thanks.


On Wed, Feb 27, 2013 at 12:17 PM, Aleksey Khudyakov <
alexey.sklad...@gmail.com> wrote:

> On 27 February 2013 12:01, Raphael Gaschignard  wrote:
> > I think it might be impossible with type families. I don't think it's
> > possible to differentiate with type families something like T a a, and T
> a
> > b, with b different from a.
> >
> It's indeed impossible to write such type function using type
> families. It will be possible with new closed type familes (they are
> in GHC head already).
>
> But for now it's possible to use overlapping instances and fundeps.
> Implementation of type level equality is simple and it's only
> instances which need ovelap.
>
> -- | Type class for type equality.
> class  TypeEq (a :: α) (b :: α) (eq :: Bool) | a b -> eq
> instance   TypeEq a a True
> instance eq ~ False => TypeEq a b eq
>
>
> Implementation of lookup by key is relatively straightforward. Note
> that it doesn't check that key is unique.
>
> data k :> v
> infix 6 :>
>
> -- | Lookup type for given key
> class TyLookup (map :: [*]) (k :: *) (v :: *) | map k -> v where
>
> class TyLookupCase (map :: [*]) (k :: *) (v :: *) (eq :: Bool) | map k
> eq -> v where
>
> instance ( TypeEq k k' eq
>  , TyLookupCase (k :> v ': xs) k' v' eq
>  ) => TyLookup  (k :> v ': xs) k' v' where
>
> instance TyLookupCase (k  :> v  ': xs) k v True  where
> instance TyLookup xs k v => TyLookupCase (k' :> v' ': xs) k v False where
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
Thank you very much, that's very nice!
That was a great journey, I started Nomyx 2-3 years ago as a personal
project and learned Haskell on the way.
I went through many refactorings as my comprehension of Haskell and Nomic
progressed.
Out of the top of my head, the points that gave me some headaches were:
- how to split the program into modules properly without dependency cycles
- Happstack big type signatures
- having the right structures to pass data in a StateT
- using existential types and type families for variables and events
- ACID state, this is really not practical during development

Cheers,
Corentin

On Wed, Feb 27, 2013 at 2:17 AM, Alexander Solla wrote:

>
>
>
> On Tue, Feb 26, 2013 at 3:28 PM, Corentin Dupont <
> corentin.dup...@gmail.com> wrote:
>
>> Hello everybody!
>> I am very happy to announce the beta release [1] of Nomyx, the only game
>> where You can change the rules.
>> This is an implementation of a Nomic [2] game in Haskell (I believe the
>> first complete implementation). In a Nomyx game you can change the rules of
>> the game itself while playing it. The players can submit new rules or
>> modify existing ones, thus completely changing the behaviour of the game
>> through time. The rules are managed and interpreted by the computer. They
>> must be written in the Nomyx language, which is a subset of Haskell.
>
>
> That's very nice.  I've been following your progress on the list.
>  Congratulations!
>
> Did you learn as much about Haskell as you hoped?
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
Hi Chris,
Thanks!
That's true for the user number. What should I do? Encrypt it?

On Wed, Feb 27, 2013 at 5:02 AM, Chris Wong  wrote:

> > Hello everybody!
> > I am very happy to announce the beta release [1] of Nomyx, the only game
> > where You can change the rules.
>
> I just gave it a go -- it looks fun :)
>
> However, I've spotted a security hole. The current user number is
> stored in the URL -- if I change that number, I can masquerade as
> someone else! Is this behavior intended?
>
> > This is an implementation of a Nomic [2] game in Haskell (I believe the
> > first complete implementation). In a Nomyx game you can change the rules
> of
> > the game itself while playing it. The players can submit new rules or
> modify
> > existing ones, thus completely changing the behaviour of the game through
> > time. The rules are managed and interpreted by the computer. They must be
> > written in the Nomyx language, which is a subset of Haskell.
> > At the beginning, the initial rules are describing:
> > - how to add new rules and change existing ones. For example a unanimity
> > vote is necessary to have a new rule accepted.
> > - how to win the game. For example you win the game if you have 5 rules
> > accepted.
> > But of course even that can be changed!
> >
> > Here is a video introduction and first tutorial of the game:
> > http://vimeo.com/58265498
> > The game is running here: www.nomyx.net:8000/Nomyx
> > I have set up a forum where players can learn about Nomyx and discuss the
> > rules they intend to propose: www.nomyx.net/forum
> >
> > As this is the first beta release of the game, I'm looking for beta
> testers
> > :) Although I tested it quite a lot, I'm sure a lot of bugs remains,
> > especially in multiplayer.
> > So if you are interested in testing Nomyx, please go to this forum thread
> > and we'll set up a small team to start a match!
> > http://www.nomyx.net/forum/viewtopic.php?p=5
> >
> > Comments/contributions are very highly welcome! There is still a lot to
> do.
> > As for now, the game is not completely securised. It is easy to break it
> by
> > submitting rules containing malicious code. I'm working on it. If you'd
> like
> > to do security testing, please do it locally on your own machine and
> send me
> > a bug report :).
> >
> > Cheers,
> > Corentin
> >
> > [1] http://hackage.haskell.org/package/Nomyx
> > [2] www.nomic.net
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Conflicting bindings legal?!

2013-02-27 Thread Andreas Abel

Hi Tillmann,

no, I am not against shadowing.  It's a two-edged sword, but I find it 
very useful.


Shadowing is very intuitive if one can proceed in a left-to-right, 
top-to-bottom order, just as one reads.  Then it is clear that the later 
occurrence of a binding shadows the earlier one.  No formal spec. is 
needed to resolve binding in that case.


The confusion comes when one binding comes from a 'where' which is below 
the use, and another comes from a 'do' or 'let' which is above the use. 
 Then there is no trivial intuitive reading (especially if the block 
structure is implicit and handled by indentation).


Cheers,
Andreas

On 26.02.2013 10:57, Tillmann Rendel wrote:

Hi,

Andreas Abel wrote:

To your amusement, I found the following in the Agda source:

abstractToConcreteCtx :: ToConcrete a c => Precedence -> a -> TCM c
abstractToConcreteCtx ctx x = do
   scope <- getScope
   let scope' = scope { scopePrecedence = ctx }
   return $ abstractToConcrete (makeEnv scope') x
   where
 scope = (currentScope defaultEnv) { scopePrecedence = ctx }

I am surprised this is a legal form of shadowing.  To understand which
definition of 'scope' shadows the other, I have to consult the formal
definition of Haskell.


Isn't this just an instance of the following, more general rule:

To understand what a piece of code means, I have to consult the formal
definition of the language the code is written in.


In the case you cite, you "just" have to desugar the do notation


abstractToConcreteCtx :: ToConcrete a c => Precedence -> a -> TCM c
abstractToConcreteCtx ctx x =
 getScope >>= (\scope ->
 let scope' = scope { scopePrecedence = ctx } in
 return $ abstractToConcrete (makeEnv scope') x)
   where
 scope = (currentScope defaultEnv) { scopePrecedence = ctx }


and it becomes clear by the nesting structure that the lambda-binding
shadows the where-binding. It seems that if you argue against this case,
you argue against shadowing in general. Should we adopt the Barendregt
convention as a style guide for programming?

   Tillmann




--
Andreas Abel  <><  Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Mats Rauhala
The user id is not necessarily the problem, but rather that you can
impose as another user. For this, one solution is to keep track of a
unique (changing) user token in the cookies and use that for verifying
the user.

-- 
Mats Rauhala
MasseR


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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
Yes, having a cookie to keep track of the session if something I plan to do.

On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala wrote:

> The user id is not necessarily the problem, but rather that you can
> impose as another user. For this, one solution is to keep track of a
> unique (changing) user token in the cookies and use that for verifying
> the user.
>
> --
> Mats Rauhala
> MasseR
>
> -BEGIN PGP SIGNATURE-
> Version: GnuPG v1.4.10 (GNU/Linux)
>
> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
> =tf0d
> -END PGP SIGNATURE-
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Erik Hesselink
Note that cookies are not the solution here. Cookies are just as user
controlled as the url, just less visible. What you need is a session
id: a mapping from a non-consecutive, non-guessable, secret token to
the user id (which is sequential and thus guessable, and often exposed
in urls etc.). It doesn't matter if you then store it in the url or a
cookie. Cookies are just more convenient.

Erik

On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
 wrote:
> Yes, having a cookie to keep track of the session if something I plan to do.
>
> On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala 
> wrote:
>>
>> The user id is not necessarily the problem, but rather that you can
>> impose as another user. For this, one solution is to keep track of a
>> unique (changing) user token in the cookies and use that for verifying
>> the user.
>>
>> --
>> Mats Rauhala
>> MasseR
>>
>> -BEGIN PGP SIGNATURE-
>> Version: GnuPG v1.4.10 (GNU/Linux)
>>
>> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
>> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
>> =tf0d
>> -END PGP SIGNATURE-
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

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


Re: [Haskell-cafe] The state of binary (de)serialization

2013-02-27 Thread Johan Tibell
On Tue, Feb 26, 2013 at 11:17 PM, Vincent Hanquez  wrote:

> On Mon, Feb 25, 2013 at 11:59:42AM -0800, Johan Tibell wrote:
> > > - cereal can output a strict bytestring (runPut) or a lazy one
> > > (runPutLazy), whilst binary only outputs lazy ones (runPut)
> > >
> >
> > The lazy one is more general and you can use toStrict (from bytestring)
> to
> > get a strict ByteString from a lazy one, without loss of performance.
>
> Two major problems of lazy bytestrings is that:
>
> * you can't pass it to a C bindings easily.
> * doing IO with it without rewriting the chunks, can sometimes (depending
>   how the lazy bytestring has been produced) result in a serious
> degradation of
>   performance calling syscalls on arbitrary and small chunks (e.g.
> socket's 'send').
>
> Personally, i also like the (obvious) stricter behavior of strict
> bytestring.
>

My point was rather that all cereal does for you is to concat the lazy
chunks it already has to a strict bytestring before returning them. If you
want that behavior with binary just call concat yourself. The benefit of
not concatenating by default is that it costs O(n) time, which you might
avoid if you can consume the lazy bytestring directly (e.g. through writev).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Aleksey Khudyakov

On 27.02.2013 17:35, Dmitry Kulagin wrote:

Hi Aleksey,

Unfortunately, your solution does not work for me (ghc 7.6.2). I reduced
the problem to:

-- | Type class for type equality.
class  TypeEq (a :: α) (b :: α) (eq :: Bool) | a b -> eq
instance   TypeEq a a True
-- instance TypeEq a b False
instance eq ~ False => TypeEq a b eq


You need to add pragma {-# LANGUAGE OverlappingInstances #-}
to the file where instances defined. Without it GHC will complain
about overlap and unlike other extensions won't recommend pragma

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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
So I need to "encrypt" the user ID in some way? What I need is to associate
the user ID to a random number and store the association is a table?


On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink  wrote:

> Note that cookies are not the solution here. Cookies are just as user
> controlled as the url, just less visible. What you need is a session
> id: a mapping from a non-consecutive, non-guessable, secret token to
> the user id (which is sequential and thus guessable, and often exposed
> in urls etc.). It doesn't matter if you then store it in the url or a
> cookie. Cookies are just more convenient.
>
> Erik
>
> On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
>  wrote:
> > Yes, having a cookie to keep track of the session if something I plan to
> do.
> >
> > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala 
> > wrote:
> >>
> >> The user id is not necessarily the problem, but rather that you can
> >> impose as another user. For this, one solution is to keep track of a
> >> unique (changing) user token in the cookies and use that for verifying
> >> the user.
> >>
> >> --
> >> Mats Rauhala
> >> MasseR
> >>
> >> -BEGIN PGP SIGNATURE-
> >> Version: GnuPG v1.4.10 (GNU/Linux)
> >>
> >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
> >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
> >> =tf0d
> >> -END PGP SIGNATURE-
> >>
> >>
> >> ___
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Clark Gaebel
You could just hash it.

  - Clark


On Wed, Feb 27, 2013 at 2:08 PM, Corentin Dupont
wrote:

> So I need to "encrypt" the user ID in some way? What I need is to
> associate the user ID to a random number and store the association is a
> table?
>
>
>
> On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink wrote:
>
>> Note that cookies are not the solution here. Cookies are just as user
>> controlled as the url, just less visible. What you need is a session
>> id: a mapping from a non-consecutive, non-guessable, secret token to
>> the user id (which is sequential and thus guessable, and often exposed
>> in urls etc.). It doesn't matter if you then store it in the url or a
>> cookie. Cookies are just more convenient.
>>
>> Erik
>>
>> On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
>>  wrote:
>> > Yes, having a cookie to keep track of the session if something I plan
>> to do.
>> >
>> > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala 
>> > wrote:
>> >>
>> >> The user id is not necessarily the problem, but rather that you can
>> >> impose as another user. For this, one solution is to keep track of a
>> >> unique (changing) user token in the cookies and use that for verifying
>> >> the user.
>> >>
>> >> --
>> >> Mats Rauhala
>> >> MasseR
>> >>
>> >> -BEGIN PGP SIGNATURE-
>> >> Version: GnuPG v1.4.10 (GNU/Linux)
>> >>
>> >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
>> >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
>> >> =tf0d
>> >> -END PGP SIGNATURE-
>> >>
>> >>
>> >> ___
>> >> Haskell-Cafe mailing list
>> >> Haskell-Cafe@haskell.org
>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >>
>> >
>> >
>> > ___
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe@haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
hash is reversible or not?

On Wed, Feb 27, 2013 at 8:18 PM, Clark Gaebel  wrote:

> You could just hash it.
>
>   - Clark
>
>
> On Wed, Feb 27, 2013 at 2:08 PM, Corentin Dupont <
> corentin.dup...@gmail.com> wrote:
>
>> So I need to "encrypt" the user ID in some way? What I need is to
>> associate the user ID to a random number and store the association is a
>> table?
>>
>>
>>
>> On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink wrote:
>>
>>> Note that cookies are not the solution here. Cookies are just as user
>>> controlled as the url, just less visible. What you need is a session
>>> id: a mapping from a non-consecutive, non-guessable, secret token to
>>> the user id (which is sequential and thus guessable, and often exposed
>>> in urls etc.). It doesn't matter if you then store it in the url or a
>>> cookie. Cookies are just more convenient.
>>>
>>> Erik
>>>
>>> On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
>>>  wrote:
>>> > Yes, having a cookie to keep track of the session if something I plan
>>> to do.
>>> >
>>> > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala 
>>> > wrote:
>>> >>
>>> >> The user id is not necessarily the problem, but rather that you can
>>> >> impose as another user. For this, one solution is to keep track of a
>>> >> unique (changing) user token in the cookies and use that for verifying
>>> >> the user.
>>> >>
>>> >> --
>>> >> Mats Rauhala
>>> >> MasseR
>>> >>
>>> >> -BEGIN PGP SIGNATURE-
>>> >> Version: GnuPG v1.4.10 (GNU/Linux)
>>> >>
>>> >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
>>> >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
>>> >> =tf0d
>>> >> -END PGP SIGNATURE-
>>> >>
>>> >>
>>> >> ___
>>> >> Haskell-Cafe mailing list
>>> >> Haskell-Cafe@haskell.org
>>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >>
>>> >
>>> >
>>> > ___
>>> > Haskell-Cafe mailing list
>>> > Haskell-Cafe@haskell.org
>>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >
>>>
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help to write type-level function

2013-02-27 Thread Dmitry Kulagin
Oh, that is my fault - I was sure that I specified the extension and it
didn't help.
It really works with Overlapping&Undecidable.
Thank you!


On Wed, Feb 27, 2013 at 10:36 PM, Aleksey Khudyakov <
alexey.sklad...@gmail.com> wrote:

> On 27.02.2013 17:35, Dmitry Kulagin wrote:
>
>> Hi Aleksey,
>>
>> Unfortunately, your solution does not work for me (ghc 7.6.2). I reduced
>> the problem to:
>>
>> -- | Type class for type equality.
>> class  TypeEq (a :: α) (b :: α) (eq :: Bool) | a b -> eq
>> instance   TypeEq a a True
>> -- instance TypeEq a b False
>> instance eq ~ False => TypeEq a b eq
>>
>>  You need to add pragma {-# LANGUAGE OverlappingInstances #-}
> to the file where instances defined. Without it GHC will complain
> about overlap and unlike other extensions won't recommend pragma
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread David Thomas
hash(id:secret) should not be reversible, if you use a cryptographic hash.

hash(id) can be brute-forced, on something with so small a range.


On Wed, Feb 27, 2013 at 11:20 AM, Corentin Dupont  wrote:

> hash is reversible or not?
>
>
> On Wed, Feb 27, 2013 at 8:18 PM, Clark Gaebel wrote:
>
>> You could just hash it.
>>
>>   - Clark
>>
>>
>> On Wed, Feb 27, 2013 at 2:08 PM, Corentin Dupont <
>> corentin.dup...@gmail.com> wrote:
>>
>>> So I need to "encrypt" the user ID in some way? What I need is to
>>> associate the user ID to a random number and store the association is a
>>> table?
>>>
>>>
>>>
>>> On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink wrote:
>>>
 Note that cookies are not the solution here. Cookies are just as user
 controlled as the url, just less visible. What you need is a session
 id: a mapping from a non-consecutive, non-guessable, secret token to
 the user id (which is sequential and thus guessable, and often exposed
 in urls etc.). It doesn't matter if you then store it in the url or a
 cookie. Cookies are just more convenient.

 Erik

 On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
  wrote:
 > Yes, having a cookie to keep track of the session if something I plan
 to do.
 >
 > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala >>> >
 > wrote:
 >>
 >> The user id is not necessarily the problem, but rather that you can
 >> impose as another user. For this, one solution is to keep track of a
 >> unique (changing) user token in the cookies and use that for
 verifying
 >> the user.
 >>
 >> --
 >> Mats Rauhala
 >> MasseR
 >>
 >> -BEGIN PGP SIGNATURE-
 >> Version: GnuPG v1.4.10 (GNU/Linux)
 >>
 >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
 >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
 >> =tf0d
 >> -END PGP SIGNATURE-
 >>
 >>
 >> ___
 >> Haskell-Cafe mailing list
 >> Haskell-Cafe@haskell.org
 >> http://www.haskell.org/mailman/listinfo/haskell-cafe
 >>
 >
 >
 > ___
 > Haskell-Cafe mailing list
 > Haskell-Cafe@haskell.org
 > http://www.haskell.org/mailman/listinfo/haskell-cafe
 >

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


[Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread John D. Ramsdell
How does one create a value of type System.IO.Handle for reading that
takes its input from a string instead of a file?  I'm looking for the
equivalent of java.io.StringReader in Java.  Thanks in advance.

John

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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
Hi all,
there is quite a lot of players! Fantastic!
I proposed a rule to lower the vote quorum from unanimity to a quorum of
only 4, for the experimentation.
But still, to have this rule accepted, everybody needs to vote! Could you
please cast your vote? If you don't plan on playing, it's better to
unsubscribe.
The players which have submitted their email should have received a
notification for this rule.

To experiment with the rules, it's better to install Nomyx on your machine
(cabal install Nomyx) and play alone, since the voting process can be long
in multiplayer (I expect 1 or 2 days to reach the quorum for a rule).

I saw people having problem writing the rules (in the log), I'll post some
comments on the game's forum: http://www.nomyx.net/forum/viewtopic.php?p=5
not to flood this mailing list ;) Just note that all proposed rules should
have type "RuleFunc".
If you'd like to use GHCI to compose your rule, here's how:
$ wget
http://hackage.haskell.org/packages/archive/Nomyx-Rules/0.1.0/Nomyx-Rules-0.1.0.tar.gz
$ tar -xzvf Nomyx-Rules-0.1.0.tar.gz
$ ghci Nomyx-Rules-0.1.0/src/Language/Nomyx/Examples.hs

Cheers!
Corentin

On Wed, Feb 27, 2013 at 12:28 AM, Corentin Dupont  wrote:

> Hello everybody!
> I am very happy to announce the beta release [1] of Nomyx, the only game
> where You can change the rules.
> This is an implementation of a Nomic [2] game in Haskell (I believe the
> first complete implementation). In a Nomyx game you can change the rules of
> the game itself while playing it. The players can submit new rules or
> modify existing ones, thus completely changing the behaviour of the game
> through time. The rules are managed and interpreted by the computer. They
> must be written in the Nomyx language, which is a subset of Haskell.
> At the beginning, the initial rules are describing:
> - how to add new rules and change existing ones. For example a unanimity
> vote is necessary to have a new rule accepted.
> - how to win the game. For example you win the game if you have 5 rules
> accepted.
> But of course even that can be changed!
>
> Here is a video introduction and first tutorial of the game:
> http://vimeo.com/58265498
> The game is running here: www.nomyx.net:8000/Nomyx
> I have set up a forum where players can learn about Nomyx and discuss the
> rules they intend to propose: www.nomyx.net/forum
>
> As this is the first beta release of the game, I'm looking for beta
> testers :) Although I tested it quite a lot, I'm sure a lot of bugs
> remains, especially in multiplayer.
> So if you are interested in testing Nomyx, please go to this forum thread
> and we'll set up a small team to start a match!
> http://www.nomyx.net/forum/viewtopic.php?p=5
>
> Comments/contributions are very highly welcome! There is still a lot to do.
> As for now, the game is not completely securised. It is easy to break it
> by submitting rules containing malicious code. I'm working on it. If you'd
> like to do security testing, please do it locally on your own machine and
> send me a bug report :).
>
> Cheers,
> Corentin
>
> [1] http://hackage.haskell.org/package/Nomyx
> [2] www.nomic.net
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
NB: being unsubscribed, you can still watch the game. It's just that you
are not anymore considered as a "citizen" of that game, thus not counted in
the votes.

On Wed, Feb 27, 2013 at 10:12 PM, Corentin Dupont  wrote:

> Hi all,
> there is quite a lot of players! Fantastic!
> I proposed a rule to lower the vote quorum from unanimity to a quorum of
> only 4, for the experimentation.
> But still, to have this rule accepted, everybody needs to vote! Could you
> please cast your vote? If you don't plan on playing, it's better to
> unsubscribe.
> The players which have submitted their email should have received a
> notification for this rule.
>
> To experiment with the rules, it's better to install Nomyx on your machine
> (cabal install Nomyx) and play alone, since the voting process can be long
> in multiplayer (I expect 1 or 2 days to reach the quorum for a rule).
>
> I saw people having problem writing the rules (in the log), I'll post some
> comments on the game's forum: http://www.nomyx.net/forum/viewtopic.php?p=5
> not to flood this mailing list ;) Just note that all proposed rules should
> have type "RuleFunc".
> If you'd like to use GHCI to compose your rule, here's how:
> $ wget
> http://hackage.haskell.org/packages/archive/Nomyx-Rules/0.1.0/Nomyx-Rules-0.1.0.tar.gz
> $ tar -xzvf Nomyx-Rules-0.1.0.tar.gz
> $ ghci Nomyx-Rules-0.1.0/src/Language/Nomyx/Examples.hs
>
> Cheers!
> Corentin
>
>
> On Wed, Feb 27, 2013 at 12:28 AM, Corentin Dupont <
> corentin.dup...@gmail.com> wrote:
>
>> Hello everybody!
>> I am very happy to announce the beta release [1] of Nomyx, the only game
>> where You can change the rules.
>> This is an implementation of a Nomic [2] game in Haskell (I believe the
>> first complete implementation). In a Nomyx game you can change the rules of
>> the game itself while playing it. The players can submit new rules or
>> modify existing ones, thus completely changing the behaviour of the game
>> through time. The rules are managed and interpreted by the computer. They
>> must be written in the Nomyx language, which is a subset of Haskell.
>> At the beginning, the initial rules are describing:
>> - how to add new rules and change existing ones. For example a unanimity
>> vote is necessary to have a new rule accepted.
>> - how to win the game. For example you win the game if you have 5 rules
>> accepted.
>> But of course even that can be changed!
>>
>> Here is a video introduction and first tutorial of the game:
>> http://vimeo.com/58265498
>> The game is running here: www.nomyx.net:8000/Nomyx
>> I have set up a forum where players can learn about Nomyx and discuss the
>> rules they intend to propose: www.nomyx.net/forum
>>
>> As this is the first beta release of the game, I'm looking for beta
>> testers :) Although I tested it quite a lot, I'm sure a lot of bugs
>> remains, especially in multiplayer.
>> So if you are interested in testing Nomyx, please go to this forum thread
>> and we'll set up a small team to start a match!
>> http://www.nomyx.net/forum/viewtopic.php?p=5
>>
>> Comments/contributions are very highly welcome! There is still a lot to
>> do.
>> As for now, the game is not completely securised. It is easy to break it
>> by submitting rules containing malicious code. I'm working on it. If you'd
>> like to do security testing, please do it locally on your own machine and
>> send me a bug report :).
>>
>> Cheers,
>> Corentin
>>
>> [1] http://hackage.haskell.org/package/Nomyx
>> [2] www.nomic.net
>>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Ozgun Ataman
I would encourage you to take a look at the snap (the web framework)
package, where this concern is handled for you as part of the "session"
snaplet.

The 
Snap.Snaplet.Session
module
and the 
Snap.Snaplet.Session.Backends.CookieSession
ensure
that contents of the cookie-persistent sessions are encrypted and so you
can place anything from user ids to other secret information there,
although I would certainly keep it to a minimum for size concerns.

Here it is: http://hackage.haskell.org/package/snap

Hope this helps,
Oz


On Wed, Feb 27, 2013 at 2:08 PM, Corentin Dupont
wrote:

> So I need to "encrypt" the user ID in some way? What I need is to
> associate the user ID to a random number and store the association is a
> table?
>
>
> On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink wrote:
>
>> Note that cookies are not the solution here. Cookies are just as user
>> controlled as the url, just less visible. What you need is a session
>> id: a mapping from a non-consecutive, non-guessable, secret token to
>> the user id (which is sequential and thus guessable, and often exposed
>> in urls etc.). It doesn't matter if you then store it in the url or a
>> cookie. Cookies are just more convenient.
>>
>> Erik
>>
>> On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
>>  wrote:
>> > Yes, having a cookie to keep track of the session if something I plan
>> to do.
>> >
>> > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala 
>> > wrote:
>> >>
>> >> The user id is not necessarily the problem, but rather that you can
>> >> impose as another user. For this, one solution is to keep track of a
>> >> unique (changing) user token in the cookies and use that for verifying
>> >> the user.
>> >>
>> >> --
>> >> Mats Rauhala
>> >> MasseR
>> >>
>> >> -BEGIN PGP SIGNATURE-
>> >> Version: GnuPG v1.4.10 (GNU/Linux)
>> >>
>> >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
>> >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
>> >> =tf0d
>> >> -END PGP SIGNATURE-
>> >>
>> >>
>> >> ___
>> >> Haskell-Cafe mailing list
>> >> Haskell-Cafe@haskell.org
>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >>
>> >
>> >
>> > ___
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe@haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Corentin Dupont
Thanks Ozgun,
but I'm using Happstack: this will be compatible?

On Wed, Feb 27, 2013 at 10:30 PM, Ozgun Ataman  wrote:

> I would encourage you to take a look at the snap (the web framework)
> package, where this concern is handled for you as part of the "session"
> snaplet.
>
> The 
> Snap.Snaplet.Session
>  module
> and the 
> Snap.Snaplet.Session.Backends.CookieSession
>  ensure
> that contents of the cookie-persistent sessions are encrypted and so you
> can place anything from user ids to other secret information there,
> although I would certainly keep it to a minimum for size concerns.
>
> Here it is: http://hackage.haskell.org/package/snap
>
> Hope this helps,
> Oz
>
>
> On Wed, Feb 27, 2013 at 2:08 PM, Corentin Dupont <
> corentin.dup...@gmail.com> wrote:
>
>> So I need to "encrypt" the user ID in some way? What I need is to
>> associate the user ID to a random number and store the association is a
>> table?
>>
>>
>> On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink wrote:
>>
>>> Note that cookies are not the solution here. Cookies are just as user
>>> controlled as the url, just less visible. What you need is a session
>>> id: a mapping from a non-consecutive, non-guessable, secret token to
>>> the user id (which is sequential and thus guessable, and often exposed
>>> in urls etc.). It doesn't matter if you then store it in the url or a
>>> cookie. Cookies are just more convenient.
>>>
>>> Erik
>>>
>>> On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
>>>  wrote:
>>> > Yes, having a cookie to keep track of the session if something I plan
>>> to do.
>>> >
>>> > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala 
>>> > wrote:
>>> >>
>>> >> The user id is not necessarily the problem, but rather that you can
>>> >> impose as another user. For this, one solution is to keep track of a
>>> >> unique (changing) user token in the cookies and use that for verifying
>>> >> the user.
>>> >>
>>> >> --
>>> >> Mats Rauhala
>>> >> MasseR
>>> >>
>>> >> -BEGIN PGP SIGNATURE-
>>> >> Version: GnuPG v1.4.10 (GNU/Linux)
>>> >>
>>> >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
>>> >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
>>> >> =tf0d
>>> >> -END PGP SIGNATURE-
>>> >>
>>> >>
>>> >> ___
>>> >> Haskell-Cafe mailing list
>>> >> Haskell-Cafe@haskell.org
>>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >>
>>> >
>>> >
>>> > ___
>>> > Haskell-Cafe mailing list
>>> > Haskell-Cafe@haskell.org
>>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >
>>>
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Ozgun Ataman
You probably can't use it directly but it should at least show you how we did 
it. In particular, the Snap.Snaplet.Session.SecureCookie module (internal, I 
think, so look at source) may be of interest to you as it implements the 
self-contained idea of encrypted cookies.

- Oz 


On Wednesday, February 27, 2013 at 4:43 PM, Corentin Dupont wrote:

> Thanks Ozgun,
> but I'm using Happstack: this will be compatible?
> 
> On Wed, Feb 27, 2013 at 10:30 PM, Ozgun Ataman  (mailto:ozata...@gmail.com)> wrote:
> > I would encourage you to take a look at the snap (the web framework) 
> > package, where this concern is handled for you as part of the "session" 
> > snaplet.
> > 
> > The Snap.Snaplet.Session 
> > (http://hackage.haskell.org/packages/archive/snap/0.11.2/doc/html/Snap-Snaplet-Session.html)
> >  module and the Snap.Snaplet.Session.Backends.CookieSession 
> > (http://hackage.haskell.org/packages/archive/snap/0.11.2/doc/html/Snap-Snaplet-Session-Backends-CookieSession.html)
> >  ensure that contents of the cookie-persistent sessions are encrypted and 
> > so you can place anything from user ids to other secret information there, 
> > although I would certainly keep it to a minimum for size concerns. 
> > 
> > Here it is: http://hackage.haskell.org/package/snap
> > 
> > Hope this helps,
> > Oz
> > 
> > 
> > On Wed, Feb 27, 2013 at 2:08 PM, Corentin Dupont  > (mailto:corentin.dup...@gmail.com)> wrote:
> > > So I need to "encrypt" the user ID in some way? What I need is to 
> > > associate the user ID to a random number and store the association is a 
> > > table?
> > > 
> > > 
> > > On Wed, Feb 27, 2013 at 3:52 PM, Erik Hesselink  > > (mailto:hessel...@gmail.com)> wrote:
> > > > Note that cookies are not the solution here. Cookies are just as user
> > > > controlled as the url, just less visible. What you need is a session
> > > > id: a mapping from a non-consecutive, non-guessable, secret token to
> > > > the user id (which is sequential and thus guessable, and often exposed
> > > > in urls etc.). It doesn't matter if you then store it in the url or a
> > > > cookie. Cookies are just more convenient.
> > > > 
> > > > Erik
> > > > 
> > > > On Wed, Feb 27, 2013 at 3:30 PM, Corentin Dupont
> > > > mailto:corentin.dup...@gmail.com)> wrote:
> > > > > Yes, having a cookie to keep track of the session if something I plan 
> > > > > to do.
> > > > >
> > > > > On Wed, Feb 27, 2013 at 3:16 PM, Mats Rauhala  > > > > (mailto:mats.rauh...@gmail.com)>
> > > > > wrote:
> > > > >>
> > > > >> The user id is not necessarily the problem, but rather that you can
> > > > >> impose as another user. For this, one solution is to keep track of a
> > > > >> unique (changing) user token in the cookies and use that for 
> > > > >> verifying
> > > > >> the user.
> > > > >>
> > > > >> --
> > > > >> Mats Rauhala
> > > > >> MasseR
> > > > >>
> > > > >> -BEGIN PGP SIGNATURE-
> > > > >> Version: GnuPG v1.4.10 (GNU/Linux)
> > > > >>
> > > > >> iEYEARECAAYFAlEuFVQACgkQHRg/fChhmVMu3ACeLLjbluDQRYekIA2XY37Xbrql
> > > > >> tH0An1eQHrLLxCjHHBQcZKmy1iYxCxTt
> > > > >> =tf0d
> > > > >> -END PGP SIGNATURE-
> > > > >>
> > > > >>
> > > > >> ___
> > > > >> Haskell-Cafe mailing list
> > > > >> Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
> > > > >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> > > > >>
> > > > >
> > > > >
> > > > > ___
> > > > > Haskell-Cafe mailing list
> > > > > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
> > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe
> > > > >
> > > 
> > > 
> > > ___
> > > Haskell-Cafe mailing list
> > > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
> > > http://www.haskell.org/mailman/listinfo/haskell-cafe
> > > 
> > 
> 

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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread Gregory Collins
On Wed, Feb 27, 2013 at 9:38 PM, John D. Ramsdell wrote:

> How does one create a value of type System.IO.Handle for reading that
> takes its input from a string instead of a file?  I'm looking for the
> equivalent of java.io.StringReader in Java.  Thanks in advance.
>

You can't. There are several libraries that purport to provide better
interfaces for doing IO in Haskell, like conduit, pipes, enumerator, and my
own io-streams library (http://github.com/snapframework/io-streams, soon to
be released). You could try one of those.

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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread Don Stewart
I don't think that's right - Simon's buffer class rewrite should have made
this possible, I think.

http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/GHC-IO-BufferedIO.html
On Feb 27, 2013 10:52 PM, "Gregory Collins"  wrote:

> On Wed, Feb 27, 2013 at 9:38 PM, John D. Ramsdell wrote:
>
>> How does one create a value of type System.IO.Handle for reading that
>> takes its input from a string instead of a file?  I'm looking for the
>> equivalent of java.io.StringReader in Java.  Thanks in advance.
>>
>
> You can't. There are several libraries that purport to provide better
> interfaces for doing IO in Haskell, like conduit, pipes, enumerator, and my
> own io-streams library (http://github.com/snapframework/io-streams, soon
> to be released). You could try one of those.
>
> G
> --
> Gregory Collins 
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread Gregory Collins
Hm, perhaps I stand corrected. Then how exactly do you make the bytestring
Handle?


On Thu, Feb 28, 2013 at 12:15 AM, Don Stewart  wrote:

> I don't think that's right - Simon's buffer class rewrite should have made
> this possible, I think.
>
>
> http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/GHC-IO-BufferedIO.html
> On Feb 27, 2013 10:52 PM, "Gregory Collins" 
> wrote:
>
>> On Wed, Feb 27, 2013 at 9:38 PM, John D. Ramsdell wrote:
>>
>>> How does one create a value of type System.IO.Handle for reading that
>>> takes its input from a string instead of a file?  I'm looking for the
>>> equivalent of java.io.StringReader in Java.  Thanks in advance.
>>>
>>
>> You can't. There are several libraries that purport to provide better
>> interfaces for doing IO in Haskell, like conduit, pipes, enumerator, and my
>> own io-streams library (http://github.com/snapframework/io-streams, soon
>> to be released). You could try one of those.
>>
>> G
>> --
>> Gregory Collins 
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>


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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-27 Thread Brandon Allbery
On Wed, Feb 27, 2013 at 8:37 AM, Corentin Dupont
wrote:

> Hi Chris,
> Thanks!
> That's true for the user number. What should I do? Encrypt it?


It's not that you have a user number, or even that it's accessible: it's
that it's the entirety of access control, meaning that if the user changes
it they can masquerade as another user. The correct solution is that a user
should authenticate, which creates a session hash that you stash away and
also send back to the user as a cookie so the browser will present it on
accesses. Then you check that the presented hash is there and matches the
session hash. These should expire periodically, requiring the user to log
back in again.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: cabal-dev 0.9.2 - sandboxed haskell builds

2013-02-27 Thread Rogan Creswick
The (ever growing) cabal-dev team is happy to announce v. 0.9.2!

Cabal-dev is a tool to test development libraries by creating a
sandboxed package and dependency build environment.  Executing
`cabal-dev install` will create a sandbox, named cabal-dev in the
current directory, and populate it with the project dependencies,
which are built and installed into a package database within the
sandbox.

This is a bug-fix/maintenance release, but it's worth noting that it is
now possible to build cabal-dev from hackage with a recent GHC.  We've
also decided to focus our efforts to provide support for the current
release of GHC, the current Haskell Platform, and the previous Haskell
Platform.

This is the long-awaited version that actually builds with recent
GHC's (7.6, in particular). A great deal of thanks for this release to
go to active members of the community who've patiently directed other
Haskell users to the github repo for a working cabal-dev, and in
particular to the dozens (!) of you who've submitted bug reports and
patches that resulted in this release (in particular: Bob Ippolito for
not only fixing a race condition that caused the test suite to
fail. Thanks Bob!)).

Urls:
 * Hackage: http://hackage.haskell.org/package/cabal-dev
 * Issue tracker: http://github.com/creswick/cabal-dev/issues
 * Github repo: http://github.com/creswick/cabal-dev

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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread Bob Ippolito
I haven't had time to make an example yet but it looks like if you go down
to GHC.IO.Handle.Internals there's a mkHandle function that takes a
BufferedIO and some other stuff and gives you an IO Handle.


On Wed, Feb 27, 2013 at 3:23 PM, Gregory Collins wrote:

> Hm, perhaps I stand corrected. Then how exactly do you make the bytestring
> Handle?
>
>
> On Thu, Feb 28, 2013 at 12:15 AM, Don Stewart  wrote:
>
>> I don't think that's right - Simon's buffer class rewrite should have
>> made this possible, I think.
>>
>>
>> http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/GHC-IO-BufferedIO.html
>> On Feb 27, 2013 10:52 PM, "Gregory Collins" 
>> wrote:
>>
>>> On Wed, Feb 27, 2013 at 9:38 PM, John D. Ramsdell 
>>> wrote:
>>>
 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.

>>>
>>> You can't. There are several libraries that purport to provide better
>>> interfaces for doing IO in Haskell, like conduit, pipes, enumerator, and my
>>> own io-streams library (http://github.com/snapframework/io-streams,
>>> soon to be released). You could try one of those.
>>>
>>> G
>>> --
>>> Gregory Collins 
>>>
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>
>
> --
> Gregory Collins 
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to return a network connection to C

2013-02-27 Thread C K Kashyap
Hi,
I am using Network.Connection to connect to gmail in my Haskell module -
that's compiled to DLL and invoked from C.

I need a mechanism to return the connection handle to C so that it can pass
it in the subsequent calls. How can I achieve this?

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