By tutorial interpreter, I means something like
an expert system having a list of rules and than
a problem which is solved by using those list of
rules.  The tutorial means the trace of the
"problem state" before and after
each rule is applied along with which parts
of the rule are matched with which part of the
"problem state".  W.R.T. haskell, the "problem
state" would be a haskell expression and each "rule
application" would be simply reducing the haskell expression
(using some rule, which would be cited during the reduction)
to a simpler form until the final answer was achieved.
Obviously the rule applications to be trace should be
user selectable to avoid way too much output, but that
seems similar to setting breakpoints in selected functions;
hence, I guess it wouldn't be hard to do.

The attached file illustrates what I'm after.

I laboriously composed that attached to enable me
to understand what the haskell code was doing.
It would help other novices if such a trace could be
automated.

I'm currently trying to understand:

  sequence (c:cs) = return (:) `ap` c `ap` sequence cs

from p. 2 of:

  http://www.soi.city.ac.uk/~ross/papers/Applicative.pdf

and again I'm having a lot of difficulty what the code is
doing.  So far I've got:

--{--eshell--
Prelude Monad> :t ap
ap :: (Monad m) => m (a -> b) -> m a -> m b
Prelude Monad> :t return (:)
return (:) :: (Monad m) => m (a -> [a] -> [a])
Prelude Monad> (:) 'a' "bc"
"abc"
Prelude Monad> :t return (:) `ap` "a"
return (:) `ap` "a" :: [[Char] -> [Char]]
--}--eshell--

so now I must "manually" figure out what the a and b in
the ap declaration correspond to in the return(:) type:

        m    ( a             ->           b           )
        __     _                          _
     1: []     Char          ->     [Char]->[Char]
     2: []     Char->[Char]  ->          [Char]

IOW, is it choice 1: in the above table for choice 2:?
I'd guess, since application associates to the left, that
it's choice 1:.  But you see, I'm not sure, and I have to
work too hard to figure it all out.  I *may* get it
eventually, but it's a *lot* of work.

I tutorial interpreter would make this so much easier!


-regards,
Larry
Purpose:
  "Trace" the execution of cross function in:
    http://www.muitovar.com/monad/moncow.xhtml#list
Trace:  
  By:
    http://www.muitovar.com/monad/moncow.xhtml#list
  Gives:
    cross "AB" [1,2] = do
      { x <- "AB"
      ; y <- [1,2]
      ; return (x,y)
      }
  By:
    http://www.haskell.org/onlinereport/exps.html#sect3.14
    .Translation
    .do{p<-e;stmts}
  Where:
    p == x
    e == "AB"
    stmts = y<-[1,2];return(x,y)    
  Gives:
    "AB">>=\x-> do 
      { y<-[1,2]
      ; return (x,y)
      }
  By:
    http://www.haskell.org/onlinereport/exps.html#sect3.14
    .Translation
    .do{p<-e;stmts}
  Where:
    p == y
    e == [1,2]
    stmts = return(x,y)    
  Gives:
    "AB">>=\x-> 
      [1,2]>>=\y->
        { return (x,y)
        }
  By:
    http://www.haskell.org/onlinereport/exps.html#sect3.14
    .Translation
    .do{e}
  Where:
    e == return(x,y)    
  Gives:
    "AB">>=\x-> 
      [1,2]>>=\y->
        return (x,y)
  By:
    http://www.haskell.org/onlinereport/standard-prelude.html
    .instance  Monad []  where
    .return x
  Where:
    x == (x,y)
  Gives:
    "AB">>=\x-> 
      [1,2]>>=\y->
        [(x,y)]
  By:
    http://www.haskell.org/onlinereport/standard-prelude.html
    .instance  Monad []  where
    .m >>= k
  Where:
    m == [1,2]
    k == \y -> [(x,y)]
  Gives:
    "AB">>=\x-> 
      concat
      ( map (\y->[(x,y)]) [1,2]
      )
  By:
    http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map
    .map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
  Where:
    f == \y->[(x,y)]
    [x1, x2, ..., xn] == [1,2]
  Gives:
    "AB">>=\x-> 
      concat
      ( [(\y->[(x,y)]) 1
        ,(\y->[(x,y)]) 2
        ]
      )
  By:
    http://en.wikipedia.org/wiki/Lambda_calculus#.CE.B2-reduction
  Where:
    V == y
    E == [(x,y)]
    E' == 1
    E' == 2
  Gives:
    "AB">>=\x-> 
      concat
      ( [ [(x,1)]
        , [(x,2)]
        ]
      )
  By:
    http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aconcat
  Where:
    type a = (Char,Int)
  Gives:
    "AB">>=\x-> 
      [ (x,1)
      , (x,2)
      ]
  By:
    http://www.haskell.org/onlinereport/standard-prelude.html
    .instance  Monad []  where
    .m >>= k
  Where:
    m == "AB"
    k == \x->
      [ (x,1)
      , (x,2)
      ]
  Gives:
    concat
    ( map
      (\x ->
        [ (x,1)
        , (x,2)
        ]
      )
      "AB"
    )
  By:
    http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map
    .map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
  Where:
    f == \x->[(x,1),(x,2)]
    [x1, x2, ..., xn] == ['A','B']
  Gives:
    concat
    ( [ (\x ->
          [ (x,1)
          , (x,2)
          ]
        ) 'A'
      , (\x ->
          [ (x,1)
          , (x,2)
          ]
        ) 'B'
      ]
    )
  By:
    http://en.wikipedia.org/wiki/Lambda_calculus#.CE.B2-reduction
  Where:
    V == x
    E == [(x,1),(x,2)]
    E' == 'A'
    E' == 'B'
  Gives:
    concat
    ( [ [('A',1)
        ,('A',2)
        ]
      , [('B',1)
        ,('B',2)
        ]
      ]
    )
    )
  By:
    http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aconcat
  Where:
    type a = (Char,Int)
  Gives:
    [('A',1)
    ,('A',2)
    ,('B',1)
    ,('B',2)
    ]
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to