Stacking up state transformers

2003-02-04 Thread Guest, Simon
Thanks to Andrew, I'm now backtracking my state correctly.

Now what I want to do is have two elements of state, an element that gets backtracked,
and an element that doesn't.

My monad now looks like this:

type NondetState bs ns a = StateT bs (NondetT (StateT ns Maybe)) a

where bs is my backtracked state, and ns my non-backtracked state.

I can still access my backtracked state using Control.Monad.State.{get,put}, but
I can't access my non-backtracked state.

How do I burrow through the stack of monad transformers to get and put the 'ns' state?

Supplementary question: What documentation should I be reading?

cheers,
Simon

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.



Now solved [was RE: Problem with backtracking monad transformer]

2003-01-31 Thread Guest, Simon
Andrew Bromage wrote:

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

I finally understand.  This was exactly my problem.  I had to discard my state monad,
and use a state monad transformer on the simple backtracking monad (not the 
backtracking monad transformer on the state monad).

Now it works fine (of course).  Thanks for the help.

cheers,
Simon

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-31 Thread Guest, Simon
Hi,

> On Thu, Jan 30, 2003 at 01:55:50PM -0000, 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.

Andrew Bromage wrote:
> 
> I've compared it with my own
> well-tested implementation and it seems identical modulo renamings.

The similarity is explained by the fact that I looked at your example on the
Haskell Wiki as well as Ralf's paper, so thanks for that useful page.

> 
> In case you want to compare:
> 
>   http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/mtl/

I will have a look at try to see what I am doing wrong.

> 
> 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.

This bit I don't understand.  I only have one monad transformer, which I use to 
transform my SM monad.

I have an uneasy feeling that my observe is in the wrong place (passed to runSM), 
but again, I can't see what else I should have done.

Thanks for the assurance, but I'm still head scratching for now.

cheers,
Simon

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.



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.



Question about use of | in a class declaration

2002-08-21 Thread Guest, Simon

Hello all,

Please could someone explain the meaning of | in this class declaration (from Andrew's 
example):

class (Ord k) => Map m k v | m -> k v where
  lookupM :: m -> k -> Maybe v

I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
Haskell 98 report.  Any references?

cheers,
Simon

-Original Message-
From: Andrew J Bromage [mailto:[EMAIL PROTECTED]]
Sent: 21 August 2002 04:19
To: [EMAIL PROTECTED]
Subject: Re: Question about sets


G'day all.

On Tue, Aug 20, 2002 at 10:57:36AM -0700, Hal Daume III wrote:

> Lists with arbitrary
> elements are possible, but not very useful.  After all, what could you do
> with them?

It's often useful to have containers of arbitrary _constrained_ types,
because then you can do something with them.  For example, given the
class of partial mappings on orderable keys:

class (Ord k) => Map m k v | m -> k v where
  lookupM :: m -> k -> Maybe v


instance (Ord k) => Map (FiniteMap k v) k v where
  lookupM = lookupFM

instance (Ord k) => Map [(k,v)] k v where
  lookupM m k = case [ v | (k',v) <- m, k == k' ] of
[]-> Nothing
(v:_) -> Just v

instance (Ord k) => Map (k -> Maybe v) k v where
  lookupM   = id

You can make a list of elements, which can be any type so long as
they are a member of that class:

data MAP k v = forall m. (Map m k v) => MAP m

type ListOfMap k v = [MAP k v]

Then you can do things with it:

lookupLom :: (Ord k) => ListOfMap k v -> k -> [ Maybe v ]
lookupLom xs k = [ lookupM a k | MAP a <- xs ]

test :: [Maybe Int]
test
  = lookupLom maps 1
  where
maps = [ MAP finiteMap, MAP assocListMap, MAP functionMap ]
finiteMap = listToFM [(1,2)]
assocListMap = [(1,3)]
functionMap = \k -> if k == 1 then Just 4 else Nothing

It's a little unfortunate that you have to introduce the MAP type here.
You can in fact construct a list of this type:

type ListOfMap k v = [ forall m. (Map m k v) => m ]

But then you can't use the elements in the list because the Haskell
type checker can't find the (Map m k v) constraint.

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


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.