[Haskell-cafe] State separation/combination pattern question

2006-12-21 Thread Reto Kramer
I'm looking for a pattern to use for "state separation" in my  
application.


I need to write two "stateful libraries". One is a partitioned in- 
memory store, the other a disk based store with an in-memory cache  
fronting it. Both store modules need the IO and State monad.


My aim is to write the libraries independently from one another in  
such a way that they are not aware of the context they will be used  
in. Both stores are called from a breadth first search loop.


The example below extracts the essence of my current approach. foo is  
function in one of the store modules, bar is from the other type of  
store. Both manipulate their type of state (StateA, StateB).  They  
extract their slice of the "global" application level state  
(AppStateRec). What I don't like is that the code in foo and bar know  
about the AppStateRec and that they need to get the "a", or "b" slot  
respectively. The store modules should not have such coupling with  
their client code.


I've tried to thread the two states (StateA and StateB) using a chain  
of StateT ... StateT ..., but couldn't really make that work. It  
seems rather arbitrary in this case which state to make the inner/ 
outer one and depending on this ordering the "lifts" have to go with  
one or the other set of store calls.


What I'm really looking for is not so much the chaining of StateT  
compositions, but rather the isolation of StateA from StateB while  
they both flow from the search loop into the respective library calls  
(foo, bar) transparently to the application programmer.  I'm hoping  
there's a way to have the loop be in a State monad whose content is  
the sum of the two states that are needed for the foo and bar call  
made to the stores from inside the loop. The calls sites for foo and  
bar should then extract the right component of the global state and  
thread only that state through into the modules. Sounds like magic,  
but how close can I get?


I've been unable to find a pattern on the WIKI or the web that refers  
to this type of "state composition" (or I may not have recognized the  
match).  I trust many of you have run into this and there's an  
obvious and straight forward best way to address this type of state  
handling.


Thanks,
- Reto

--
-- ghci -fglasgow-exts ...
--
type StateA = [Integer]
type StateB = [Integer]

data AppStateRec = AppStateRec { a :: StateA, b :: StateB } deriving  
Show


foo :: MonadState AppStateRec m => m ()
foo = do st <- get
 put $ st { a = 1:(a st) }

bar :: MonadState AppStateRec m => m ()
bar = do st <- get
 put $ st { b = 2:(b st) }

type Eval a = StateT AppStateRec Identity a

exec :: Eval ()
exec = do foo
  bar
  foo
  foo
  bar

go = runIdentity $ runStateT exec AppStateRec { a = [], b = [] }

Prints: ((),AppStateRec {a = [1,1,1], b = [2,2]})
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Class annotation on datatype ineffective in function

2006-12-18 Thread Reto Kramer
The code below does not compile unless the "bar" function is  
annotated with a suitable constraint on the class of the formal  
parameter.


> module Main where
>
> class (C a)
> data (C foo) => XY foo = X foo | Y foo
>
> bar :: a -> XY a
> bar aFoo = X aFoo
>
> main = return ()

I get:

> $ ghc Test.hs
>
> Test.hs:8:8:
>No instance for (C a)
>  arising from use of `X' at Test.hs:8:8-10
>Possible fix: add (C a) to the type signature(s) for `foo'
>In the expression: X a
>In the definition of `foo': foo a = X a

As suggested, this works:

> bar :: (C a) => a -> XY a

Can someone explain to me why the compiler can not infer that "a" (in  
bar) must be (C a) from the bar result type "XY a" (by way of the "C  
class" provided for the datatype)?


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


Re: [Haskell-cafe] Parsec operator with letter problem

2006-03-31 Thread Reto Kramer
Great!  Thanks for the revision Daniel.  If you're ever in San  
Francisco, please do ping me - I sure owe you lunch!


- Reto

On Mar 31, 2006, at 3:14 PM, Daniel Fischer wrote:


Am Freitag, 31. März 2006 15:24 schrieb Daniel Fischer:

Hi,

probably somebody else has already come up with something better, but
still...

I surmise that you have two kinds of infix-operators,
1. dot-like operators, made up entirely of symbols (^!$%&/\,.:;#+- 
~* ...)

2. LaTeX-command-like operators, starting with a backslash and then
followed by a nonempty sequence of letters (or possibly alphanumeric
characters).

Then the following helps:

import Data.Char (isAlpha)

lexer = lexer0{P.reservedOp = rOp}
  where
lexer0  = P.makeTokenParser testdef
resOp0  = P.reservedOp lexer0
resOp1 name =
  case name of
('\\':cs@(_:_))

| all isAlpha cs -> do string name

   notFollowedBy letter 
("end of " ++ show  
name)

_   -> fail (show name ++ " no good reservedOp")
rOp name = lexeme $ try $ resOp0 name <|> resOp1 name
lexeme p = do { x <- p; P.whiteSpace lexer0; return x }


Noho, that's not right, that parses "a\inn" as
InfixExpr OP_In (Ident "a") (Ident "n"),
because resOp1 is never used, which we don't want, so:

lexer = lexer0{P.reservedOp = rOp}
  where
lexer0  = P.makeTokenParser testdef
resOp0  = P.reservedOp lexer0
resOp1 name = do string name
 notFollowedBy letter  ("end of " ++  
show name)

rOp name = lexeme $ try $
  case name of
('\\':cs@(_:_)) | all isAlpha cs ->  
resOp1 name

_ -> resOp0 name
lexeme p = do { x <- p; P.whiteSpace lexer0; return x }

Now:
[EMAIL PROTECTED]:~/Documents/haskell/Reto> cat input
a.n
[EMAIL PROTECTED]:~/Documents/haskell/Reto> reto input
InfixExpr OP_Dot (Ident "a") (Ident "n")
[EMAIL PROTECTED]:~/Documents/haskell/Reto> cat input
a\inn
[EMAIL PROTECTED]:~/Documents/haskell/Reto> reto input
Ident "a"
[EMAIL PROTECTED]:~/Documents/haskell/Reto> cat input
a\in n
[EMAIL PROTECTED]:~/Documents/haskell/Reto> reto input
InfixExpr OP_In (Ident "a") (Ident "n")

That's better.


testdef = emptyDef
{ P.identStart  = letter <|> char '_'
, P.identLetter = alphaNum <|> char '_'
, P.opStart = oneOf $ nub $
map (\s -> head s) $ P.reservedOpNames  
testdef

 -- , P.opLetter= oneOf (concat (P.reservedOpNames testdef))
, P.opLetter = oneOf symbs
, P.reservedOpNames = [ ".", "\\in" ] }
where
  symbs = filter (not . isAlpha) . concat $ P.reservedOpNames  
testdef

-
[EMAIL PROTECTED]:~/Documents/haskell/Reto> cat input
a.n
[EMAIL PROTECTED]:~/Documents/haskell/Reto> reto input
InfixExpr OP_Dot (Ident "a") (Ident "n")

If you have more complicated infix operators (e.g.  
\foo#bar:, :ouch:),

it won't be so easy, anyway, you have to change the definition of
reservedOp.

Cheers,
Daniel


--

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
-- Blair P. Houghton



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


[Haskell-cafe] Parsec operator with letter problem

2006-03-30 Thread Reto Kramer
I ran into the following problem with parsec's handling of operators.  
I hope someone on the list can show me a trick that resolve my  
current issue. At the end of this message is the full code for the  
reproducer.


The language I'm parsing has infix operators of two forms. Some are  
special characters (e.g. a dot) and some are LaTeX like (e.g. \in).  
The letters that appear in the e.g. \in lead to problems with  
expression parsing.


The following is what I expect:
  $ cat input1
  a.b
  $ ./test input1
  InfixExpr OP_Dot (Ident "a") (Ident "b")
Good!

Then I try (change the b to an n)
  $ cat input2
  a.n
  $ ./test input2
  Ident "a"
OUTSCH!  Changing the name of an identifier changed the expression!

Then I try (add a space right after the dot)
  $ cat input3
  a. n
  $ ./test input2
  InfixExpr OP_Dot (Ident "a") (Ident "n")
Good!

What is going on?

The 'n' is part of the "\in" operator (see reservedOpNames in test.hs  
program at the end of message) and confuses the parsec expression  
parser's ability to determine the end of expressions/identifiers.   
Adding a space right after the '.' operator resolves the issue, but  
that's not a suitable option for my users.


Unfortunately I cannot remove the "\in" operator from the  
reservedOpNames list since otherwise "\in" is not recognized as an  
infix operator itself anymore.


QUESTION:
how can I get parsec's expression parser to work with infix operators  
of the form "\in"?


Thanks,
- Reto


-- complete reproducer (test.hs)
-- compile with: ghc -o test -package parsec test.hs

module Main where

import List (nub)
import System (getArgs)
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Expr
import Text.ParserCombinators.Parsec.Language( emptyDef )
import qualified Text.ParserCombinators.Parsec.Token as P

main :: IO ()
main = do{ args <- getArgs
 ; let fname = args !! 0
 ; input <- readFile fname
 ; case parse spec fname input of
 Left err -> do{ putStr "parse error at "
   ; print err
   }
 Right x  -> print x
 }

data Op = OP_Dot | OP_In deriving (Show, Eq, Ord)
data Expr = InfixExpr Op Expr Expr
  | Ident String
  | Number Integer deriving (Show, Eq, Ord)

spec :: Parser Expr
spec = do { whiteSpace
  ; e <- expression
  ; return e
  }

expression :: Parser Expr
expression = buildExpressionParser table basicExpr  "expression"

op_infix :: Op -> Expr  -> Expr -> Expr
op_infix op a b = InfixExpr op a b

table :: OperatorTable Char () Expr
table = [ [binary "."  (op_infix OP_Dot) AssocLeft]
, [binary "\\in" (op_infix OP_In) AssocLeft] ]
binary  name fun assoc = Infix (do{ reservedOp name; return fun }) assoc

basicExpr :: Parser Expr
basicExpr = choice [
  do{ i <- identifier
; return $ Ident i
}
]

lexer = P.makeTokenParser testdef

testdef = emptyDef {
  P.identStart  = letter <|> char '_'
, P.identLetter = alphaNum <|> char '_'
, P.opStart = oneOf $ nub $
map (\s -> head s) $ P.reservedOpNames testdef
, P.opLetter= oneOf (concat (P.reservedOpNames testdef))
, P.reservedOpNames = [ ".", "\\in" ] }

dot = P.dot lexer
parens  = P.parens lexer
braces  = P.braces lexer
squares = P.squares lexer
semiSep = P.semiSep lexer
semiSep1= P.semiSep1 lexer
commaSep= P.commaSep lexer
commaSep1   = P.commaSep1 lexer
brackets= P.brackets lexer
whiteSpace  = P.whiteSpace lexer
symbol  = P.symbol lexer
identifier  = P.identifier lexer
reserved= P.reserved lexer
reservedOp  = P.reservedOp lexer
integer = P.integer lexer
natural = P.natural lexer
charLiteral = P.charLiteral lexer
stringLiteral   = P.stringLiteral lexer

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