[Haskell-cafe] Expanding do notation

Bulat Ziganshin bulatz at HotPOP.com
Sun Jan 8 10:54:56 EST 2006


Hello Lennart,

Sunday, January 08, 2006, 5:45:16 PM, you wrote:

>> Cool. So let's see if I got it.
>> If I have
>> 
>> n <- readIO
>>      ...
>> mapM_ (func n) list
>>      ...
>> 
>> in my programme, the runtime system will/might build object code for

not "object code" itslef. haskell program in compiled form is a large
tree which nodes contain object code. run-time compilation can
substitute instead of node which computes "func n" the node which will
compute concrete "func 2" value. it is the partial case of
"calculation" of lazy program by substitution evaluation results
instead of function calls. the key may be just what haskell functions
are curreied, so you can see fucntion "f a b" as function with two
arguments returning Int, or as function with one argument returning
"Int->Int". for example

regexpr <- getStrLn
filtered <- filterM (match regexpr) lines

with definition

match "*"    = const True
match regexp = \str -> ...

when your input is "*" it will compute {match "*"} as "const True" and
pass this argument to the filterM call (to be exact, it will pass
unevaluated thunk {match "*"}, which will be evaluated to "const True"
on first use)

>> func n that is then used instead of using the general code for func and 
>> supplying both arguments to that?

yes. i don't know how to guarantee it. i just define my
time-critical functions as having one arguments. you can see an
example on those hawiki page, another example is my regexpr code:

data RegExpr = RE_End
             | RE_Anything                
             | RE_FromEnd RegExpr         
             | RE_AnyChar RegExpr         
             | RE_Char    Char RegExpr    
             | RE_FullRE  Regex           

is_wildcard s  =  s `contains_one_of` "?*["

translate_RE re = "^"++ (replaceAll "*" ".*"
                        .replaceAll "?" "."
                        .replaceAll "$" "\\$"
                        .replaceAll "[[[" "[^"  
                        .replaceAll "^" "\\^"
                        .replaceAll "[^" "[[["  
                        .replaceAll "+" "\\+"
                        .replaceAll "." "\\.") re ++"$"

compile_RE s  =  case s of
  ""     -> RE_End
  "*"    -> RE_Anything
  '*':cs -> if ('*' `elem` cs) || ('[' `elem` cs)
              then RE_FullRE  (mkRegex$ translate_RE$ s)
              else RE_FromEnd (compile_RE$ reverse$   s)
  '[':cs -> RE_FullRE   (mkRegex$ translate_RE$ s)
  '?':cs -> RE_AnyChar  (compile_RE cs)
  c  :cs -> RE_Char   c (compile_RE cs)

match_RE re s  =  case re of
  RE_End        -> null s
  RE_Anything   -> True
  RE_FullRE   r -> isJust (matchRegex r s)
  RE_FromEnd  r -> match_RE r (reverse s)
  RE_AnyChar  r -> case s of
                     ""   -> False
                     _:xs -> match_RE r xs
  RE_Char   c r -> case s of
                     ""   -> False
                     x:xs -> x==c && match_RE r xs

match re {-s-}  =  match_RE (compile_RE re) {-s-}


third example is the functions used in my program to combine tests for
many regexprs. this also work in "run-time compilation" manner

-- |Map on functions instead of its' arguments!
map_functions []     x  =  []
map_functions (f:fs) x  =  f x : map_functions fs x

all_functions []  = const True
all_functions [f] = f
all_functions fs  = and . map_functions fs

any_function []  = const False
any_function [f] = f
any_function fs  = or . map_functions fs


>> That'd be wow, triple wow!
>> And run-time compilation is a fitting name for that.

more or less :)

LA> Well, it's possible to do that.  But I don't know of any Haskell
LA> implementation that does.  Sure, you might get a little bit of
LA> that if func is defined suitably, like
LA>    func 0 = foo
LA>    func 1 = bar
LA>    func n = baz
LA> Implementations that have the "full laziness" property will handle
LA> one argument at a time to a function, and may do some work with just
LA> one argument to func.  But it's nothing like having real run-time code
LA> generation.

of course, it's just graph reduction. and by explicitly moving last
argument to the right part of function definition i help compiler to
properly optimize such code

-- 
Best regards,
 Bulat                            mailto:bulatz at HotPOP.com





More information about the Haskell-Cafe mailing list