Re: [Haskell-cafe] Split function

2011-02-09 Thread Anton Kholomiov
There is a 'spit' library on hackage. Maybe you are looking for this

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


[Haskell-cafe] Where is All about monads?

2011-02-09 Thread Magicloud Magiclouds
Hi,
  Just noticed that the link was deprecated. Googling shows that this
thing does not exist on haskell.org any more?
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problems with (projects|community).haskell.org

2011-02-09 Thread Erik de Castro Lopo
Hi all,

Still a couple of problems with these servers.

Firstly, community.haskell.org shows the default Apache It works
page. It would be nice to have something better there.

Secondly the mailman web interface on projects.haskell.org [0] is
giving a Service Temporarily Unavailable message (and has been
for a couple of days).

Cheers,
Erik

[0] http://projects.haskell.org/cgi-bin/mailman/admindb/haskell-llvm
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

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


[Haskell-cafe] ANN: monad-control-0.2 a challenge

2011-02-09 Thread Bas van Dijk
Dear all,

I just released control-monad-0.2 a library for lifting control
operations, like exception catching, through monad transformers:

http://hackage.haskell.org/package/monad-control-0.2

darcs get http://bifunctor.homelinux.net/~bas/monad-control/

To quote the NEWS file:

* Use RunInBase in the type of idLiftControl.

* Added this NEWS file.

* Only parameterize Run with t and use RankNTypes to quantify n and o
  -liftControl :: (Monad m, Monad n, Monad o) = (Run t n o - m a) - t m a
  +liftControl :: Monad m = (Run t - m a) - t m a

  -type Run t n o = forall b. t n b - n (t o b)
  +type Run t = forall n o b. (Monad n, Monad o, Monad (t o)) = t n b
- n (t o b)

  Bumped version from 0.1 to 0.2 to indicate this breaking change in API.

* Added example of a derivation of liftControlIO.

This derivation of liftControlIO is really enlightening. It shows the
recursive structure of liftControlIO applied to a stack of three monad
transformers with IO as the base monad: t1 (t2 (t3 IO)) a:

(Note that the derivation in the API documentation also shows the
types of the intermediate computations)

liftControlIO
 =
 liftLiftControlBase $  -- instance MonadControlIO t1
   liftLiftControlBase $-- instance MonadControlIO t2
 liftLiftControlBase $  -- instance MonadControlIO t3
   idLiftControl-- instance MonadControlIO IO
  =
   \f → liftControl $ \run1 → -- Capture state of t1
  liftControl $ \run2 →   -- Capture state of t2
liftControl $ \run3 → -- Capture state of t3

  -- At this point we've captured the state of all transformers
  -- and have landed in the base (IO) monad.
  -- So we can start executing f:

  let run ∷ RunInBase (t1 (t2 (t3 IO))) IO
  run = -- Restore state
liftM (join ∘ lift)
  ∘ liftM (join ∘ lift)

-- Identity conversion
  ∘ liftM (join ∘ lift)
  ∘ liftM return

-- Run
  ∘ run3
  ∘ run2
  ∘ run1
  in f run

This derivation clearly shows what is happening: first the state of
all transformers is captured using the liftControl operations. Each
capture supplies us a run function that allows us to run a computation
of the respected monad transformer. When we arrive in the base (IO)
monad we can start executing f.

f expects a run function
:: ∀ b. t1 (t2 (t3 IO)) b → IO (t1 (t2 (t3 IO)) b)
which allows it to run a t1 computation in IO. The IO computation then
returns a new t1 computation that has the final state of the given t1
computation. This can later be used to restore that final state.

Although the derivation is correct, I'm not really happy with it from
a performance perspective. In the created run function there are two
places where it can do better:

* The identity conversion: (liftM (join ∘ lift) ∘ liftM return) could
be replaced with something more efficient like (liftM (join ∘ lift ∘
return)) or (liftM id) or just id.

* The restore conversion: (liftM (join ∘ lift) ∘ liftM (join ∘ lift))
could be replaced with (liftM (join ∘ lift ∘ join ∘ lift)). This
transformation is correct according to the Functor law: liftM f ∘
liftM g = liftM (f ∘ g).

I haven't figured out yet how to change monad-control in such a way
that it generates this more efficient derivation. So I'm posting this
as a challenge to you!

Good luck,

Bas

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


Re: [Haskell-cafe] forkIO on GHCI does not seem to spawn the thread in the background on some OSs

2011-02-09 Thread David Leimbach
On Tuesday, February 8, 2011, C K Kashyap ckkash...@gmail.com wrote:

 I can't reproduce this. What are you using as the action?

 I've tried bottoms, and tight loops whose Core contains no allocations, and 
 not
 managed to lock up the prompt, or seen ghci using more threads than I have
 cores.

 One thing that may give the appearance of locking up the prompt is if
 the thread starts reading from the terminal and your commands no longer make 
 it
 to the interpreter.

 It is  not always a thread.  ForkIO creates a spark and then the
 scheduler  decides when sparks should be scheduled to threads.  Thus
 you get a  guarantee of concurrent but not parallel execution.

 That is not correct - it is par that creates sparks may be discarded.

 forkIO always creates new threads, though it is of course up to the scheduler
 when the threads are executed, and how many cores are used.

 Are you running with  threads enabled?

 That is, was your ghci compiled with -threaded? This mostly
 depends on the version. what version of ghc are you running, and how did you
 install it?




 Sorry ... extremely sorry ... my bad ... for some reason, I was omitting the 
 call to forkIO :( when I was trying on other platforms.
 Regards,Kashyap

:-)

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


[Haskell-cafe] Possible bug in Control.Concurrent

2011-02-09 Thread Krzysztof Skrzętnicki
Hello Cafe,

Here is a simple program that yields strange results:

module Main where

import Control.Concurrent
import Control.Concurrent.Chan
import Control.Monad

main = do
 c - newChan
 writeChan c 1
 forkIO $ forever $ do
   i - readChan c
   print (forkio,i)
isEmptyChan c = print

First of all, if we try to run it via runhaskell, it will hang:

runhaskell deadlock.hs
(forkio,1)
-- no more output --


Compiled version OTOH behaves differently dependent on compilation flags.
Without -threaded:
./deadlock
(forkio,1)
False

With -threaded:
./deadlock
False

Now, this is strange thing: we put single element into the channel. We take
it out. And then we see the channel isn't really empty. Perhaps there is a
race condition here? So we put an delay, so that we will be sure the check
for empty channel occurs 1 second later than the channel is emptied.

import Control.Concurrent
import Control.Concurrent.Chan
import Control.Monad

main = do
 c - newChan
 writeChan c 1
 forkIO $ forever $ do
   i - readChan c
   print (forkio,i)
  threadDelay 100
 isEmptyChan c = print

This program will misbehave. Invariably of -threaded flag it will go like
this:

./deadlock
(forkio,1)
deadlock: thread blocked indefinitely in an MVar operation

I have no idea what is the problem here. Perhaps I'm not using the library
in the right way. Does anyone has any idea what's going on here?

Best regards,
Krzysztof Skrzętnicki
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible bug in Control.Concurrent

2011-02-09 Thread Krzysztof Skrzętnicki
Shame on me, I forgot to include the software versions I use:

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.12.3

$ uname -a
Linux raptor 2.6.37-ARCH #1 SMP PREEMPT Sat Jan 29 20:00:33 CET 2011 x86_64
Intel(R) Core(TM) i7 CPU 870 @ 2.93GHz GenuineIntel GNU/Linux

This is a normal Arch Linux setup with GHC installed via pacman.

Best regards,
Krzysztof Skrzętnicki

2011/2/9 Krzysztof Skrzętnicki gte...@gmail.com

 Hello Cafe,

 Here is a simple program that yields strange results:

 module Main where

 import Control.Concurrent
 import Control.Concurrent.Chan
 import Control.Monad

 main = do
  c - newChan
  writeChan c 1
  forkIO $ forever $ do
i - readChan c
print (forkio,i)
 isEmptyChan c = print

 First of all, if we try to run it via runhaskell, it will hang:

 runhaskell deadlock.hs
 (forkio,1)
 -- no more output --


 Compiled version OTOH behaves differently dependent on compilation flags.
 Without -threaded:
 ./deadlock
 (forkio,1)
 False

 With -threaded:
 ./deadlock
 False

 Now, this is strange thing: we put single element into the channel. We take
 it out. And then we see the channel isn't really empty. Perhaps there is a
 race condition here? So we put an delay, so that we will be sure the check
 for empty channel occurs 1 second later than the channel is emptied.

 import Control.Concurrent
 import Control.Concurrent.Chan
 import Control.Monad

 main = do
  c - newChan
  writeChan c 1
  forkIO $ forever $ do
i - readChan c
print (forkio,i)
   threadDelay 100
  isEmptyChan c = print

 This program will misbehave. Invariably of -threaded flag it will go like
 this:

 ./deadlock
 (forkio,1)
 deadlock: thread blocked indefinitely in an MVar operation

 I have no idea what is the problem here. Perhaps I'm not using the library
 in the right way. Does anyone has any idea what's going on here?

 Best regards,
 Krzysztof Skrzętnicki

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


Re: [Haskell-cafe] Possible bug in Control.Concurrent

2011-02-09 Thread Neil Brown

On 09/02/11 15:34, Krzysztof Skrzętnicki wrote:

Hello Cafe,

Here is a simple program that yields strange results:

module Main where

import Control.Concurrent
import Control.Concurrent.Chan
import Control.Monad

main = do
 c - newChan
 writeChan c 1
 forkIO $ forever $ do
   i - readChan c
   print (forkio,i)
isEmptyChan c = print


Now, this is strange thing: we put single element into the channel. We 
take it out.


What your program does is put a single element into the channel, and 
then *repeatedly* try to take one out (notice the forever you have in 
there!).  Judging by the results, the program deadlocks, which seems 
like a reasonable outcome to me.


Thanks,

Neil.

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


Re: [Haskell-cafe] Possible bug in Control.Concurrent

2011-02-09 Thread Holger Reinhardt
You've been bitten by the following bug:
http://hackage.haskell.org/trac/ghc/ticket/4154

In short, isEmptyChan will block because of the concurrent call to readChan.
The solution is to not use isEmptyChan or switch to STM.


2011/2/9 Krzysztof Skrzętnicki gte...@gmail.com

 Hello Cafe,

 Here is a simple program that yields strange results:

 module Main where

 import Control.Concurrent
 import Control.Concurrent.Chan
 import Control.Monad

 main = do
  c - newChan
  writeChan c 1
  forkIO $ forever $ do
i - readChan c
print (forkio,i)
 isEmptyChan c = print

 First of all, if we try to run it via runhaskell, it will hang:

 runhaskell deadlock.hs
 (forkio,1)
 -- no more output --


 Compiled version OTOH behaves differently dependent on compilation flags.
 Without -threaded:
 ./deadlock
 (forkio,1)
 False

 With -threaded:
 ./deadlock
 False

 Now, this is strange thing: we put single element into the channel. We take
 it out. And then we see the channel isn't really empty. Perhaps there is a
 race condition here? So we put an delay, so that we will be sure the check
 for empty channel occurs 1 second later than the channel is emptied.

 import Control.Concurrent
 import Control.Concurrent.Chan
 import Control.Monad

 main = do
  c - newChan
  writeChan c 1
  forkIO $ forever $ do
i - readChan c
print (forkio,i)
   threadDelay 100
  isEmptyChan c = print

 This program will misbehave. Invariably of -threaded flag it will go like
 this:

 ./deadlock
 (forkio,1)
 deadlock: thread blocked indefinitely in an MVar operation

 I have no idea what is the problem here. Perhaps I'm not using the library
 in the right way. Does anyone has any idea what's going on here?

 Best regards,
 Krzysztof Skrzętnicki

 ___
 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] haskell prop. logic

2011-02-09 Thread Patrick M
Hello all I'm working on a project and I'm down to my last 3 functions.I need 
some help(in any form) with them as I'm a beginner in haskell.I tried to create 
a description on how the functions should behave below ,if you still have some 
questions don't hesitate to ask.
Also here is the code for the function I've written so far(some with help). 
http://pastebin.com/fQp40ucg
propagateUnits :: Formula-Formula
If a clause in a propositional formula contains only one literal, then that 
literal must be true (so that the particular clause can be satisfied). When 
this 
happens,we can remove the unit clauses (the ones that contain only one 
literal), 
all the clauses where the literal appears and also,  from the remaining 
clauses, 
we can delete the negation of the literal (because if P is true, -P will be 
false).For example, in the formula (P v Q v R) ^ (-P v Q v -R) ^ (P) we have 
one 
unit clause (the third clause(P) ). Because this one has to be true for the 
whole formula to be true we assign True to P and try to find
a satisfying assignment for the remaining formula. Finally because -P cannot be 
true (given the assigned value of P) then the second clause is reduced by 
eliminating the symbol -P . This simplification results in the revised formula 
(Q v -R).
The resulting simplification can create other unit clauses. For example in the 
formula (-P v Q) ^ (P) is simplified to (Q) when the unit clause (P) is 
propagated. This makes (Q) a unit clause which can now also be simplified to 
give a satisfying assignment to the formula. The function should apply unit 
propagation until it can no longer make any further simplifications.
Note that if both P  and -P are unit clauses then the formula is unsatisfiable. 
In this case the function should return a formula with an empty clause in it to 
indicate that the formula could not be satisfied.

update :: Node - [Node]
The update function should take in a Node and return a list of the Nodes that 
result from assigning True to an unassigned atom in one case and False in the 
other (ie. a case
split). So the list returned should have two nodes as elements. One node should 
contain the formula with an atom assigned True and the model updated with this 
assignment, and the other should contain the formula with the atom assigned 
False and the model updated to show this. The lists of unassigned atoms of each 
node should also be updated accordingly. This function should use your 
implemented assign function to make the assignments. It should also use the 
chooseAtom function provided to select the literal to  assign.

search :: (Node - [Node]) - [Node] - Int - (Bool, Int)
The search function should perform a backtracking search. The function takes 
the 
update function as input and uses it to generate nodes in the search space. The 
search function also takes in a list which has one element, the initial node 
consisting of the formula along with an initial model. It should generate nodes 
using the update function and check nodes using the given check function. If a 
node is unsatisfiable then it should
abandon that branch of the search. If a node is satisfiable then a satisfying 
assignment has been found and so it should return True. If a node is neither 
satisfiable or unsatisfiable then it should generate new nodes from this node. 
If all possible branches of the search space have been tried, i.e. the list of 
nodes to try has become the empty list, then it should return False since all 
possible assignments have been  tried. The search function also has an Int 
argument which should be an integer that tracks how many
calls to the update function have been made. The search function should return 
a 
pair consisting of the truth value of the formula and the number of calls to 
update made.


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


[Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
Hi all,

I've a type problem that I cannot solve and, before I keep banging my
head against an unbreakable wall, I'd like to discuss it with the
list.

Consider the following code:


module Main where

class PRead p where {}
class PWrite p where {}

newtype Sealed p a = Sealed a

instance Monad (Sealed p) where
return = Sealed
(Sealed x) = f = f x

mustRead :: PRead p = a - Sealed p a
mustRead = Sealed

mustWrite :: PWrite p = a - Sealed p a
mustWrite = Sealed

readLog :: PRead p = String - Sealed p String
readLog = mustRead . id

writeLog :: PWrite p = String - Sealed p String
writeLog = mustWrite . id

appendLog l e = do l - readLog l
   writeLog $ l ++ e


The central type of this code is Sealed, which boxes a value inside a
newtype with a phantom type which represents a set of permissions.

This set of permissions is implemented through a series of type
classes (PRead and PWrite in this case) which are attached to the
permission value p of the Sealed newtype.

This way I can define which set of permissions I expect to be enforced
when trying to peel off the Sealed value. The use of the Monad class
and type classes as permissions behaves nicely when combining
functions with different permission constraints, as it's the case of
appendLog, whose type signature is:

appendLog  :: (PRead p, PWrite p) = String - [Char] - Sealed p String

Very nice, the permissions accumulates as constraints over the p type.
Now for the peel-off part:


unseal :: p - Sealed p a - a
unseal _ (Sealed x) = x


Basically this function requires a witness value of the type p to
peel-off the Sealed value. Notice that:


unseal undefined $ appendLog Foo Bar


won't work as the undefined value is unconstrained. That's good,
because otherwise it'd very easy to circumvent the enforcing
mechanism. So, I defined some roles:


data User = User
data Admin = Admin

instance PRead User where {}

instance PRead Admin where {}
instance PWrite Admin where {}


If I try to unseal the Sealed value passing User, it won't succeed, as
the type checker is expecting the value of a type which is also an
instance of the PWrite class:


*Main unseal User $ appendLog Foo Bar

interactive:1:14:
No instance for (PWrite User)
  arising from a use of `appendLog' at interactive:1:14-34


while works perfectly if I pass Admin as a value:


*Main unseal Admin $ appendLog Foo Bar
FooBar


The idea is to hide the Admin and User constructor from the programmer
and having two factory functions, checkAdmin and checkUser, which
checks whether the current user has the named role, something like:


checkAdmin :: IO Admin
checkUser :: IO User


where role checking happens in the IO Monad (or something similar),
a-là trusted kernel. So far so good and I'm very happy with that.

Now the problem.

I would like to enforce permissions not at the role level, but at the
permissions level. Let's say that I want to leave unseal unchanged,
I'd like to construct a p-value for unseal combining functions
checking for single permissions, that is, in pseudo-code:

unseal (checkPRead .*. checkPWrite) $ appendLog Foo Bar

where .*. is some kind of type aggregation operator.

Or maybe something like:

(checkPRead .*. checkPWrite) $ appendLog Foo Bar

So far I got only frustration. In principle it seems possible to
achieve this result because everything is known at compile time and
the type-checked should have all the information available to enforce
the security constraints.

Anyhow, I couldn't write any usable code.

Any help would be appreciated, even pointers to papers discussing this approach.

Thank you,

-- 
Cristiano

GPG Key: 4096R/C17E53C6 2010-02-22
Fingerprint = 4575 4FB5 DC8E 7641 D3D8  8EBE DF59 B4E9 C17E 53C6

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


Re: [Haskell-cafe] forkIO on GHCI does not seem to spawn the thread in the background on some OSs

2011-02-09 Thread David Leimbach
  It is  not always a thread.  ForkIO creates a spark and then the
  scheduler  decides when sparks should be scheduled to threads.  Thus
  you get a  guarantee of concurrent but not parallel execution.

 That is not correct - it is par that creates sparks may be discarded.


I guess I should have been clearer.  A forkIO thread is not an OS thread
necessarily.  Sparks may become threads or be discarded in the par sense.



 forkIO always creates new threads, though it is of course up to the
 scheduler
 when the threads are executed, and how many cores are used.


Yes, this is my understanding as well.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Steffen Schuldenzucker


In ghci I get

 let evil = appendLog Foo Bar
interactive:1:11:
Ambiguous type variable `p' in the constraints:
  `PRead p'
arising from a use of `appendLog' at interactive:1:11-31
  `PWrite p'
arising from a use of `appendLog' at interactive:1:11-31
Probable fix: add a type signature that fixes these type variable(s)

And then, specializing evil's type:

 let good = appendLog Foo Bar :: Sealed Admin String
 unseal (undefined :: Admin) good
FooBar

-- Steffen

On 02/09/2011 06:15 PM, Cristiano Paris wrote:

Hi all,

I've a type problem that I cannot solve and, before I keep banging my
head against an unbreakable wall, I'd like to discuss it with the
list.

Consider the following code:


module Main where

class PRead p where {}
class PWrite p where {}

newtype Sealed p a = Sealed a

instance Monad (Sealed p) where
return = Sealed
(Sealed x)= f = f x

mustRead :: PRead p =  a -  Sealed p a
mustRead = Sealed

mustWrite :: PWrite p =  a -  Sealed p a
mustWrite = Sealed

readLog :: PRead p =  String -  Sealed p String
readLog = mustRead . id

writeLog :: PWrite p =  String -  Sealed p String
writeLog = mustWrite . id

appendLog l e = do l- readLog l
writeLog $ l ++ e


The central type of this code is Sealed, which boxes a value inside a
newtype with a phantom type which represents a set of permissions.

This set of permissions is implemented through a series of type
classes (PRead and PWrite in this case) which are attached to the
permission value p of the Sealed newtype.

This way I can define which set of permissions I expect to be enforced
when trying to peel off the Sealed value. The use of the Monad class
and type classes as permissions behaves nicely when combining
functions with different permission constraints, as it's the case of
appendLog, whose type signature is:

appendLog  :: (PRead p, PWrite p) =  String -  [Char] -  Sealed p String

Very nice, the permissions accumulates as constraints over the p type.
Now for the peel-off part:


unseal :: p -  Sealed p a -  a
unseal _ (Sealed x) = x


Basically this function requires a witness value of the type p to
peel-off the Sealed value. Notice that:


unseal undefined $ appendLog Foo Bar


won't work as the undefined value is unconstrained. That's good,
because otherwise it'd very easy to circumvent the enforcing
mechanism. So, I defined some roles:


data User = User
data Admin = Admin

instance PRead User where {}

instance PRead Admin where {}
instance PWrite Admin where {}


If I try to unseal the Sealed value passing User, it won't succeed, as
the type checker is expecting the value of a type which is also an
instance of the PWrite class:


*Main  unseal User $ appendLog Foo Bar

interactive:1:14:
 No instance for (PWrite User)
   arising from a use of `appendLog' atinteractive:1:14-34


while works perfectly if I pass Admin as a value:


*Main  unseal Admin $ appendLog Foo Bar
FooBar


The idea is to hide the Admin and User constructor from the programmer
and having two factory functions, checkAdmin and checkUser, which
checks whether the current user has the named role, something like:


checkAdmin :: IO Admin
checkUser :: IO User


where role checking happens in the IO Monad (or something similar),
a-là trusted kernel. So far so good and I'm very happy with that.

Now the problem.

I would like to enforce permissions not at the role level, but at the
permissions level. Let's say that I want to leave unseal unchanged,
I'd like to construct a p-value for unseal combining functions
checking for single permissions, that is, in pseudo-code:

unseal (checkPRead .*. checkPWrite) $ appendLog Foo Bar

where .*. is some kind of type aggregation operator.

Or maybe something like:

(checkPRead .*. checkPWrite) $ appendLog Foo Bar

So far I got only frustration. In principle it seems possible to
achieve this result because everything is known at compile time and
the type-checked should have all the information available to enforce
the security constraints.

Anyhow, I couldn't write any usable code.

Any help would be appreciated, even pointers to papers discussing this approach.

Thank you,




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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 18:43, Steffen Schuldenzucker
sschuldenzuc...@uni-bonn.de wrote:
 ...
 let good = appendLog Foo Bar :: Sealed Admin String
 unseal (undefined :: Admin) good
 FooBar

That's true, but putting apart the problem I posed, in my construction
I wouldn't expose unseal directly nor the Sealed constructor. This
way, you should not be able to recreate the unseal function and you'd
be given only specialized unseal functions for each role, like
unsealAsAdmin, unsealAsUser and so on.

Thank you for adding to the discussion.

-- 
Cristiano

GPG Key: 4096R/C17E53C6 2010-02-22
Fingerprint = 4575 4FB5 DC8E 7641 D3D8  8EBE DF59 B4E9 C17E 53C6

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Chris Smith
On Wed, 2011-02-09 at 18:15 +0100, Cristiano Paris wrote:
 I've a type problem that I cannot solve and, before I keep banging my
 head against an unbreakable wall, I'd like to discuss it with the
 list.

If I'm understanding your high-level goals correctly, then you're going
about things the wrong way.  It looks like in your Sealed type, you're
accumulating a list of type class constraints that are needed by a
phantom type, in order to access the value.  But type classes are open;
anyone can make any new type an instance of the type class whenever they
want.

In particular, you say:

 
 unseal :: p - Sealed p a - a
 unseal _ (Sealed x) = x
 
 
 Basically this function requires a witness value of the type p to
 peel-off the Sealed value. Notice that:
 
 
 unseal undefined $ appendLog Foo Bar
 
 
 won't work as the undefined value is unconstrained. That's good,
 because otherwise it'd very easy to circumvent the enforcing
 mechanism.

This is not true, though.  One could just as easily write:

data Dummy
instance PRead Dummy
instance PWrite Dummy

unseal (undefined :: Dummy) $ appendLog Foo Bar

and they've circumvented your security checks.

I think you'll need to back up and rethink your base strategy.  Without
really understanding fully what you want, I'll still point out that
there are tricks with existentials that work when you need someone to
have an authentic token to do something; e.g., see the ST monad.

-- 
Chris Smith


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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Alexey Khudyakov

On 09.02.2011 20:57, Chris Smith wrote:

On Wed, 2011-02-09 at 18:15 +0100, Cristiano Paris wrote:

I've a type problem that I cannot solve and, before I keep banging my
head against an unbreakable wall, I'd like to discuss it with the
list.


If I'm understanding your high-level goals correctly, then you're going
about things the wrong way.  It looks like in your Sealed type, you're
accumulating a list of type class constraints that are needed by a
phantom type, in order to access the value.  But type classes are open;
anyone can make any new type an instance of the type class whenever they
want.



It's possible to have closed type classes. Trick consist in adding 
unsatisfiable constraint. For example:


 -- This type class is not exported
 class Private a
 class Private a = PRead a

If Private is not exported one cannot add instances to PRead.

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Alexey Khudyakov

On 09.02.2011 20:15, Cristiano Paris wrote:

Now the problem.

I would like to enforce permissions not at the role level, but at the
permissions level. Let's say that I want to leave unseal unchanged,
I'd like to construct a p-value for unseal combining functions
checking for single permissions, that is, in pseudo-code:



So far I got only frustration. In principle it seems possible to
achieve this result because everything is known at compile time and
the type-checked should have all the information available to enforce
the security constraints.

Anyhow, I couldn't write any usable code.



Text below is literate haskell

My solution is based on heterogenous lists and require number of
language extensions. I'd recomend to read paper Strongly typed
heterogeneous collections[1] which describe this technique in detail

 {-# LANGUAGE TypeOperators #-}
 {-# LANGUAGE OverlappingInstances #-}
 {-# LANGUAGE FlexibleInstances #-}

So lets start with definition of type classes for permissions and data
types which represent such permissions.

 class PRead  a
 class PWrite a

 data WRead  = WRead
 data WWrite = WWrite

Now interestig part begins. We need to compose different permissons. I
define heterogenous list for that purpose. It's nothing more than a
nested tuple in disguise.

 data a ::: b = a ::: b
 infixr :::

List has instance for some permission if it has corresponding type in
it. Please note that I make use of overlapping here. You may need to
read about it.

Also list need some terminator. WRead is not instance of PRead whereas
WRead ::: () is. I will use () for that purpose. It's OK since all
type classes here are closed.

 instancePRead (WRead ::: b)
 instance PRead b = PRead (a ::: b)

 instance PWrite (WWrite ::: b)
 instance PWrite b = PWrite (a ::: b)

Here is function for checking that everything is working as expected

 withR :: PRead a = a - ()
 withR _ = ()

 withW :: PWrite a = a - ()
 withW _ = ()

 withWR :: (PRead a, PWrite a) = a - ()
 withWR _ = ()

 r  = WRead ::: ()
 w  = WWrite ::: ()
 rw = WRead  ::: WWrite ::: ()

[1] http://homepages.cwi.nl/~ralf/HList/



P.S. You can use phantom types to propagate type information. I feel
that carrying undefined is morally dubious practice.

 data T a = T
 newtype Sealed p a = Sealed a

 unseal :: T p - Sealed p a - a
 unseal _ (Sealed x) = x

 admin :: T (WRead  ::: WWrite ::: ())
 admin = T

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 19:33, Alexey Khudyakov
alexey.sklad...@gmail.com wrote:
 ...
 If Private is not exported one cannot add instances to PRead.

Nice trick. I would have thought of hiding the classes PRead and
PWrite but I'm not sure if it could break the code.

Thank you!

-- 
Cristiano

GPG Key: 4096R/C17E53C6 2010-02-22
Fingerprint = 4575 4FB5 DC8E 7641 D3D8  8EBE DF59 B4E9 C17E 53C6

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 20:14, Alexey Khudyakov
alexey.sklad...@gmail.com wrote:
 ...
 My solution is based on heterogenous lists and require number of
 language extensions. I'd recomend to read paper Strongly typed
 heterogeneous collections[1] which describe this technique in detail

Curious: I read the paper just because I had an idea about how to
solve the problem but it led me to no solution even though it helped
me a lot in understanding some advanced type mechanism.

I'll read your solution later and come back to you with a comment.

Thank you in the meantime.

-- 
Cristiano

GPG Key: 4096R/C17E53C6 2010-02-22
Fingerprint = 4575 4FB5 DC8E 7641 D3D8  8EBE DF59 B4E9 C17E 53C6

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 20:14, Alexey Khudyakov
alexey.sklad...@gmail.com wrote:
 ...
 instance            PRead (WRead ::: b)
 instance PRead b = PRead (a ::: b)

 instance             PWrite (WWrite ::: b)
 instance PWrite b = PWrite (a ::: b)

Brilliant! I was thinking to something like this but as a replacement
of the accumulation mechanism in the Monad. I didn't think of it in
the permission checking part.

Thanks a lot. Now I need to consolidate better my code for
incorporating yours and other people contributions.

Bye,

-- 
Cristiano

GPG Key: 4096R/C17E53C6 2010-02-22
Fingerprint = 4575 4FB5 DC8E 7641 D3D8  8EBE DF59 B4E9 C17E 53C6

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Alexey Khudyakov

On 09.02.2011 23:16, Cristiano Paris wrote:

On Wed, Feb 9, 2011 at 19:33, Alexey Khudyakov
alexey.sklad...@gmail.com  wrote:

...
If Private is not exported one cannot add instances to PRead.


Nice trick. I would have thought of hiding the classes PRead and
PWrite but I'm not sure if it could break the code.

It shouldn't but it would be impossible to write signatures for 
polymorphic functions which use thoose type classes.


foo :: PWrite p = Sealed p Int  -- impossible to write
foo = ...

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


Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Bas van Dijk
On 9 February 2011 19:33, Alexey Khudyakov alexey.sklad...@gmail.com wrote:
 On 09.02.2011 20:57, Chris Smith wrote:

 On Wed, 2011-02-09 at 18:15 +0100, Cristiano Paris wrote:

 I've a type problem that I cannot solve and, before I keep banging my
 head against an unbreakable wall, I'd like to discuss it with the
 list.

 If I'm understanding your high-level goals correctly, then you're going
 about things the wrong way.  It looks like in your Sealed type, you're
 accumulating a list of type class constraints that are needed by a
 phantom type, in order to access the value.  But type classes are open;
 anyone can make any new type an instance of the type class whenever they
 want.


 It's possible to have closed type classes. Trick consist in adding
 unsatisfiable constraint. For example:

 -- This type class is not exported
 class Private a
 class Private a = PRead a

 If Private is not exported one cannot add instances to PRead.

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


Indeed, this is exactly what I use in explicit-iomodes:

http://hackage.haskell.org/packages/archive/explicit-iomodes/0.6.0.2/doc/html/System-IO-ExplicitIOModes.html#t:ReadModes

Bas

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


[Haskell-cafe] coding a queue with reactive

2011-02-09 Thread sam . roberts . 1983

Hi all,

I hope someone is interested in helping me out with the reactive library.
I am trying to implement a function queue in reactive:

queue :: Double - Event a - Event a

This is a simple queue: events from the event stream coming into the queue,
queue up waiting to be processed one by one. Processing an event takes a
constant amount of time for every event. The output of the queue function
is the stream of processed events.

My current (deficient) implementation of the queue function is:

queue dt eventsIn =
do
(a,exitT) - withExitTime eventsIn
_ - atTime exitT
return a
where
withExitTime = scanlE calcExitTime (undefined, -1/0) . withTimeE
calcExitTime (_,prevExitT) (a,inT) = (a, (max inT prevExitT) + dt)

I am having three problems.

1 - I find my implementation of the queue is less clear then an imperative
description of a queue.

2 - I rely on being able to calculate the exit time of an event when it
first arrives at the queue, whereas an imperative queue would simply store
the event in queue and only need to calculate the output time once the event
was popped off the queue. If I want to do something similar with my  
function,

I think I need to make some sort of recursive definition of a queue which
responds to it's own exit events. I've tried to code this up, but have not
managed to wrap my brain around the concept.

3 - The code performs horribly! I am guessing that this is because I have  
not
told reactive that the exit events preserve the ordering of the input  
events,

but I'm not sure how to encode that relationship in reactive.

(It's worth noting here that I actually have a fourth problem too: I get
linker errors while trying to compile a profiling version of the program ...
but that's a separate topic.)

It's also worth noting, from a performance point of view, that a much  
simpler
delay function with similar use of the bind function performs badly as  
well:


delay :: Double - Event a - Event a
delay dt es = do (e,t) - withTimeE es
_ - atTime (t+dt)
return e

I'd appreciate any light that anyone could shed on any of these problems.
If there's a better way of structuring my queue function, or if there's a
better way of changing event times in reactive, I am open to all  
suggestions.


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


Re: [Haskell-cafe] Where is All about monads?

2011-02-09 Thread Henk-Jan van Tuyl
On Wed, 09 Feb 2011 09:21:49 +0100, Magicloud Magiclouds  
magicloud.magiclo...@gmail.com wrote:



Hi,
  Just noticed that the link was deprecated. Googling shows that this
thing does not exist on haskell.org any more?


This is one of the things that weren't transferred to the new server; I  
have a backup on my disk. If you want the HTML-version, I can send it to  
you. There is a PDF-version at  
http://horna.org.ua/books/All_About_Monads.pdf


Regards,
Henk-Jan van Tuyl


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

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


[Haskell-cafe] Haskell Summers of Code retrospective (updated for 2010)

2011-02-09 Thread Gwern Branwen
2 years ago in February 2009, I wrote up a history of Summers of Code
through 2008 
(http://www.haskell.org/pipermail/haskell-cafe/2009-February/055489.html).
But the Wheel turns, and years come and pass, leaving memories that
fade into 404s; a wind rose in Mountain View, whispering of the coming
Summer...

I have considerably expanded and updated the coverage:
http://www.gwern.net/Haskell%20Summer%20of%20Code.html

It now covers the 2009  2010 SoCs, adds scads of links, flips the
appraisal of some of the older SoCs as time passed and more info came
to light, and adds a section discussing 12 proposals from the
subreddit  Trac.

(It's long enough that I don't feel comfortable copying it inline as I
did 2 years ago.)

-- 
gwern
http://www.gwern.net

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


[Haskell-cafe] [Cabal-devel] Cabal license combinations

2011-02-09 Thread Dan Knapp
  I haven't heard anyone mention this yet, and it's a biggie, so I
guess I'd better de-lurk and explain it.  The issue is this:  There is
a legal distinction between static and dynamic linking, or at least
some licenses (the GPL is the one I'm aware of) believe that there is.
 In particular, they assert that you are legally creating a derived
work if you statically link with their library, and that your
library, even if it's just a thin bindings wrapper, must therefore
comply by their license terms.  They make no such claim for dynamic
linking.

  Of course, Haskell on most platforms and default configurations
links everything statically!  So I believe this means that you have to
comply by the licenses of all your dependencies!  Now, there's a
difference between complying by those licenses and being under them
yourself, but for example I believe this means that if we have a
package named hs-save-the-whales that is under the GPL, and a
front-end package hs-redeem-them-for-valuable-cash-prizes which
makes use of the functionality in hs-save-the-whales, the front-end
MUST be offered under the GPL, and, additionally, CANNOT be offered
under BSD (I think).

  I think it would be a very useful and valuable thing for Cabal to
detect this situation and warn appropriately!  Contamination by
undesired licenses is a serious flaw in the packaging of a package; it
just happens to be a legal flaw rather than a technical one.  Indeed,
I would argue that this is far more important than any hypothetical
per-file licensing.


-- 
Dan Knapp
An infallible method of conciliating a tiger is to allow oneself to
be devoured. (Konrad Adenauer)

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


[Haskell-cafe] Haskell Weekly News: Issue 168 - February 09, 2011

2011-02-09 Thread Daniel Santa Cruz
   Welcome to issue 168 of the HWN, a newsletter covering developments in
   the [1]Haskell community. This release covers the week of January 30 to
   February 5, 2011.

Announcements

   Maciej Piechotka [2]announced version 0.1.1 of nanoparsec. Nanoparsec
   is currently simply a port of attoparsec on ListLike (the abstraction
   of lists used by iteratee).

   Graham Hutton [3]announced the availability of studenships in
   Functional Programming at the University of Nottingham, UK.

   Ashley Yakeley [4]made a small update to time (1.2.0.4) that fixes a
   bug in parseTime.

   George Giorgidze [5]announced the release to Hackage of Database
   Supported Haskell (DSH).

   Simon Hengel [6]announced the release of HackageOneFive, a tiny Snap
   app that provides reverse dependency lookup for all packages on
   Hackage.

Quotes of the Week

 * alpounet: map succ/pred is a scandinavian name generator or what?
   ... well, scandinavian and aztec
 * dons: Think of a monad as a spacesuit full of nuclear waste in the
   ocean next to a container of apples. Now, you can't put oranges in
   the space suite or the nuclear waste falls in the ocean, *but* the
   apples are carried around anyway, and you just take what you need.
 * Apocalisp: a unit of clarity is a clarinet
 * roconnor: My coq has failed me
 * roconnor: I mean, I could, and do, say that a lens is just a monoid
   natural transformation from the coalgebra functiors from haskell
   functors to haskell types.
 * Saizan: not being ML is a quite sound principle syntax-wise
 * lpsmith: well, getting rid of airliners certainly *is* one way of
   eliminating their potential use as weapons against larger buildings
 * ddarius: The reason edwardk writes so many Haskell packages is to
   ward the Perl from penetrating his heart.
 * monochrom: most people tend to deny the usefulness of useful
   alternative perspectives --- their entrenched vested interests
   demand it. as they grow older they also have more influence and
   power over the state of the art to preserve their self-fulfilling
   prophecy that the alternative is useless --- by controlling what
   practice looks like, they can control what looks useless.
 * edwardk: i learned to program becaise i'd lied and told a kid that
   i'd written a disassembler, then had to make good on the claim.

Top Reddit Stories

   * Quine Central ... because everyone needs to be able to make nth
order quines
 Domain: blog.sigfpe.com, Score: 40, Comments: 7
 On Reddit:
http://www.reddit.com/r/haskell/comments/fc4cs/quine_central_because_everyone_needs_to_be_able/
 Original: http://blog.sigfpe.com/2011/01/quine-central.html

   * jhc 0.7.7 is out
 Domain: haskell.org, Score: 38, Comments: 0
 On Reddit: http://www.reddit.com/r/haskell/comments/fbqo7/jhc_077_is_out/
 Original: http://www.haskell.org/pipermail/jhc/2011-January/000874.html

   * Hulk: A Haskell IRC server
 Domain: chrisdone.com, Score: 32, Comments: 1
 On Reddit:
http://www.reddit.com/r/haskell/comments/fbrie/hulk_a_haskell_irc_server/
 Original: 
http://chrisdone.com/posts/2011-01-30-hulk-haskell-irc-server.html

   * Status update on {code, trac, projects, planet, community}.haskell.org
 Domain: haskell.org, Score: 25, Comments: 0
 On Reddit:
http://www.reddit.com/r/haskell/comments/fdnjp/status_update_on_code_trac_projects_planet/
 Original: 
http://www.haskell.org/pipermail/haskell-cafe/2011-February/088829.html

   * All about MVars : Inside T5
 Domain: blog.ezyang.com, Score: 23, Comments: 4
 On Reddit:
http://www.reddit.com/r/haskell/comments/fduxb/all_about_mvars_inside_t5/
 Original: http://blog.ezyang.com/2011/02/all-about-mvars/

   * Text: a visual programming language based on Haskell, demo
 Domain: vimeo.com, Score: 21, Comments: 3
 On Reddit:
http://www.reddit.com/r/haskell/comments/fbgxd/text_a_visual_programming_language_based_on/
 Original: http://vimeo.com/19273744

   * [SO] Why is GHC so big?
 Domain: stackoverflow.com, Score: 21, Comments: 10
 On Reddit:
http://www.reddit.com/r/haskell/comments/fczht/so_why_is_ghc_so_big/
 Original: 
http://stackoverflow.com/questions/4858585/why-is-ghc-so-large-big

   * Haskell Weekly News: Issue 167
 Domain: contemplatecode.blogspot.com, Score: 21, Comments: 0
 On Reddit:
http://www.reddit.com/r/haskell/comments/fe63a/haskell_weekly_news_issue_167/
 Original: 
http://contemplatecode.blogspot.com/2011/02/haskell-weekly-news-issue-167.html

   * The F# Team are Hiring (functional programming jobs)
 Domain: haskell.org, Score: 20, Comments: 6
 On Reddit:
http://www.reddit.com/r/haskell/comments/fcvec/the_f_team_are_hiring_functional_programming_jobs/
 Original: http://www.haskell.org/pipermail/haskell/2011-January/022523.html

   * Recently Uploaded: DSH-0.4.2 Natural Sql Queries without the need
to 

Re: [Haskell-cafe] Cabal license combinations

2011-02-09 Thread Vivian McPhail
  It seems then that a package should be the least restrictive
  combination of all the licenses in all the contained modules.

 Omit the words least restrictive and I think you are correct.

 To combine licences, just aggregate them.  There is no lattice of
 subsumption; no more or less restrictive ordering.


I was thinking that the lattice was already flattened into a list of
licences.  Currently the top-level package has a single licence field which
is an arbitrary disjunctive choice.  Much better is a conjunctive
aggregation which is just as or less restrictive than the arbitrary
disjunctive choice.

Cheers,

Vivian

P.S. OK := acknowledge [ACK]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe