List comprehensions

2003-01-30 Thread Rijk J. C. van Haaften
Hello,

Recently, I came accross this
expression:
[ x + y | x - xs | y - ys ]

As far as I can see (Haskell Report),
this is not allowed by the haskell 98
standard. So I assume it to be an ex-
tension. Where can I find information
about this?

Thanks,

Rijk

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: List comprehensions

2003-01-30 Thread Oliver Braun
* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]:

 Recently, I came accross this expression:
 [ x + y | x - xs | y - ys ]
^
Put a comma ',' here.

Regards,
 Olli
-- 
obraun@ -+-[ informatik.unibw-muenchen.de ]-+-[ IIS _ INF _ UniBwM ]
 |-[ FreeBSD.org  ]-+-[ FreeBSD Commmitter ]
 |-[ unsane.org   ]-+-[ everything __ else ]



msg02488/pgp0.pgp
Description: PGP signature


Re: List comprehensions

2003-01-30 Thread Rijk J. C. van Haaften


* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]:

 Recently, I came accross this expression:
 [ x + y | x - xs | y - ys ]
^
Put a comma ',' here.


That's something totally different. Two examples:
1. Comma
  [ x + y | x - [1,2], y - [3,4] ]
= [4,5,5,6]

2. Bar
  [ x + y | x - [1,2] | y - [3,4] ]
= [ x + y | (x,y) - zip [1,2] [3,4] ]
= zipWith (+) [1,2] [3,4]
= [4,6]

The first is according to the standard. No problems so far.
However, I couldn't find a description of the semantics of
the second (and it is clearly non-standard), though I think
the semantics given above using zip and zipWith are correct.

Rijk

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: List comprehensions

2003-01-30 Thread Ross Paterson
On Thu, Jan 30, 2003 at 11:41:49AM +0100, Rijk J. C. van Haaften wrote:
 Recently, I came accross this
 expression:
 [ x + y | x - xs | y - ys ]
 
 As far as I can see (Haskell Report),
 this is not allowed by the haskell 98
 standard. So I assume it to be an ex-
 tension. Where can I find information
 about this?

It's not Haskell 98, but is implemented in GHC and Hugs (with extensions
turned on).  It's a parallel list comprehension, and is equivalent to

zipWith (+) xs ys

See the GHC User's Guide for more.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: List comprehensions

2003-01-30 Thread Oliver Braun
* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 12:06 +0100]:

 * Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]:
 
  Recently, I came accross this expression:
  [ x + y | x - xs | y - ys ]
 ^
 Put a comma ',' here.

 That's something totally different. Two examples:
 1. Comma
   [ x + y | x - [1,2], y - [3,4] ]
 = [4,5,5,6]

 2. Bar
   [ x + y | x - [1,2] | y - [3,4] ]
 = [ x + y | (x,y) - zip [1,2] [3,4] ]
 = zipWith (+) [1,2] [3,4]
 = [4,6]

 The first is according to the standard. No problems so far.
 However, I couldn't find a description of the semantics of
 the second (and it is clearly non-standard), though I think
 the semantics given above using zip and zipWith are correct.

Ok, I see. Sorry, this was just my first thought.
Unfortunately I cannot help you with the Bar thing.

Regards,
 Olli
-- 
obraun@ -+-[ informatik.unibw-muenchen.de ]-+-[ IIS _ INF _ UniBwM ]
 |-[ FreeBSD.org  ]-+-[ FreeBSD Commmitter ]
 |-[ unsane.org   ]-+-[ everything __ else ]



msg02492/pgp0.pgp
Description: PGP signature


RE: List comprehensions

2003-01-30 Thread Jan de Wit

 Hello,
 
 Recently, I came accross this
 expression:
 [ x + y | x - xs | y - ys ]
 
 As far as I can see (Haskell Report),
 this is not allowed by the haskell 98
 standard. So I assume it to be an ex-
 tension. Where can I find information
 about this?
This is a parallel list comprehension, a GHC extension. See 
http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#PA
RALLEL-LIST-COMPREHENSIONS
for more info. The code above does the same as zipWith (+) xs ys, basically.


Cheers, Jan
###

This message has been scanned by F-Secure Anti-Virus for Microsoft Exchange.
For more information, connect to http://www.F-Secure.com/

###
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Problem with backtracking monad transformer

2003-01-30 Thread Guest, Simon
I'm trying to make a backtracking state monad using Ralf Hinze's
backtracking monad transformer.  My problem is that it won't backtrack
very far.

Suppose I try ( a  b ) `mplus` c.

If b fails, it should try c, but it doesn't rewind past a.

My sample code is below.

GHCI c [0,1] match_1-- (1 or 0) then 1, OK
GHCI c [1,0] match_2-- (1 then 0) or (1,1), OK
GHCI c [1,1] match_2-- (1 then 0) or (1,1), fails

What have I misunderstood?

cheers,
Simon
(A disclaimer in an attachment?  - it wasn't my idea.)


-- backtracking state monad
-- requires -fglasgow-exts

import qualified Monad as M
import qualified Control.Monad.Trans as MT

-- turn tracing on and off by uncommenting just one of the following lines
import Debug.Trace( trace )
--trace s x = x

--
-- Ralf Hinze's efficient backtracking monad transformer
--

newtype BACKTR m a
  = BACKTR { mkBACKTR :: (forall b. (a - m b - m b) - m b - m b) }

instance (Monad m) = Monad (BACKTR m) where
  return a = BACKTR (\c - c a)
  m = k  = BACKTR (\c - mkBACKTR m (\a - mkBACKTR (k a) c))

-- We don't use a Backtr class, but do it with the MonadPlus class,
-- mzero is false (fail),
-- mplus is ¦ (orelse)
instance (Monad m) = M.MonadPlus (BACKTR m) where
  mzero = BACKTR (\c - id)
  m1 `mplus` m2 = BACKTR (\c - mkBACKTR m1 c . mkBACKTR m2 c)

-- standard MonadTrans class has lift for promote, and doesn't have observe
instance MT.MonadTrans BACKTR where
  lift m = BACKTR (\c f - m = \a - c a f)

observe :: (Monad m) = BACKTR m a - m a
observe m = mkBACKTR m (\a f - return a) (fail false)



--
-- State Monad
--

data SM st a = SM (st - (a,st)) -- The monadic type

instance Monad (SM st) where
   -- defines state propagation
   SM c1 = fc2 = SM (\s0 - let (r,s1) = c1 s0
  SM c2 = fc2 r in
 c2 s1)
   return k = SM (\s - (k,s))

-- extracts the state from the monad
readSM :: SM st st
readSM = SM (\s - (s,s))

-- updates the state of the monad
updateSM :: (st - st) - SM st () -- alters the state
updateSM f = SM (\s - ((), f s))

-- run a computation in the SM monad
runSM :: st - SM st a - (a,st)
runSM s0 (SM c) = c s0


-- backtracking state monad
--
type NDSM st a = BACKTR (SM st) a

readNDSM :: NDSM st st
readNDSM = MT.lift readSM

updateNDSM :: (st - st) - NDSM st ()
updateNDSM f = MT.lift (updateSM f)

--run a computation in the NDSM monad
runNDSM :: st - NDSM st a - (a,st)
runNDSM s0 m = runSM s0 (observe m)



--
-- the state
--
type Bit = Int

data CState = CState
 { ok:: Bool,
   remaining_data:: [Bit],
   history   :: [String] -- log, kept in reverse
 } deriving Show

initState xs = CState True xs []

-- prepend a message in the log
logit :: CState - String - CState
logit s logmsg = s { history = logmsg : (history s) }

--
-- matching action
--
match_bits :: [Bit] - NDSM CState ()
match_bits xs = do
   s - readNDSM
   let s' = logit s (attempt match_bits  ++ show xs
 ++  remaining:  ++ show (remaining_data s))

   s'' = if xs == take (length xs) (remaining_data s')
 then
s' { remaining_data = drop (length xs) (remaining_data s') }
 else
s' { ok = False }
   if ok s''
  then updateNDSM (\s - s'')
  else trace (unlines $ MATCH FAILED:(reverse $ history s'')) M.mzero

--
-- test routines
--

-- just fine
match_1 =
   (match_bits [1] `M.mplus` match_bits [0]) 
match_bits [1]

-- this one only rewinds past the [0] attempt, not the [1] attempt
match_2 =
   (  (match_bits [1]  match_bits [0])
  `M.mplus` match_bits [1, 1] )


c :: [Bit] - NDSM CState () - ([Bit], [String])
c h hspec = 
   let (v, s) = runNDSM (initState h) hspec in
   case (ok s) of True - ([], ok:(reverse $ history s))
  _- ([(negate)1], [fail])

Registered Office: Roke Manor Research Ltd, Siemens House, Oldbury, Bracknell, 
Berkshire. RG12 8FZ

The information contained in this e-mail and any attachments is confidential to Roke 

Manor Research Ltd and must not be passed to any third party without permission. This 

communication is for information only and shall not create or change any contractual 

relationship.



Re: Problem with backtracking monad transformer

2003-01-30 Thread Andrew J Bromage
G'day all.

On Thu, Jan 30, 2003 at 01:55:50PM -, Guest, Simon wrote:

 I'm trying to make a backtracking state monad using Ralf Hinze's
 backtracking monad transformer.  My problem is that it won't backtrack
 very far.
 
 Suppose I try ( a  b ) `mplus` c.
 
 If b fails, it should try c, but it doesn't rewind past a.

I added this to your source file:

testBACKTR :: (Monad m) = BACKTR m Int
testBACKTR
= ( return 1  M.mzero ) `M.mplus` (return 2)

main :: IO ()
main = putStrLn (show (observe testBACKTR :: Maybe Int))

The result is Just 2, so I don't think there's anything wrong with
your implementation of BACKTR.  I've compared it with my own
well-tested implementation and it seems identical modulo renamings.

In case you want to compare:

http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/mtl/

I didn't follow the rest of the code, so I suspect the problem is
elsewhere.  One place to look is here:

 -- backtracking state monad
 --
 type NDSM st a = BACKTR (SM st) a

You may have meant to stack the monad transformers in a different
order.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: List comprehensions

2003-01-30 Thread Jon Fairbairn
On 2003-01-30 at 11:08GMT Ross Paterson wrote:
 On Thu, Jan 30, 2003 at 11:41:49AM +0100, Rijk J. C. van Haaften wrote:
  Recently, I came accross this
  expression:
  [ x + y | x - xs | y - ys ]
  
  As far as I can see (Haskell Report),
  this is not allowed by the haskell 98
  standard. So I assume it to be an ex-
  tension. Where can I find information
  about this?
 
 It's not Haskell 98, but is implemented in GHC and Hugs (with extensions
 turned on).

As far as I can tell ghc 5.04 accepts this without
complaint. Is this a bug, or should I pass some argument to
turn extensions off?

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



``Cannot instantiate a type variable with a forall-type''

2003-01-30 Thread Jon Cast

Why does GHC place this constraint?  I would expect forall to be
predicative, and a type variable to range over all types, but obviously
I'm missing something.

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Global variables?

2003-01-30 Thread Pavel G. Zhbanov
Hello,
Is it even possible to make a global variable in Haskell? 
If yes, how?
Thanks.

-- 
Zhbanov Pavel
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-30 Thread Glynn Clements

Pavel G. Zhbanov wrote:

 Is it even possible to make a global variable in Haskell? 
 If yes, how?

The usual fudge is:

import IORef
import IOExts

globalVar :: IORef Int
globalVar = unsafePerformIO $ newIORef 0

However, beware of creating more than one global variable of the
same type. If you enable optimisation, common subexpression
elimination may result in both names referring to the same IORef.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe