Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Ronald Guida
On Sat, Aug 14, 2010 at 12:33 PM, Bill Atkins watk...@alum.rpi.edu wrote:
 Try this one (http://gist.github.com/524460)

I noticed that Bill's solution doesn't seem to work if the input text
is infinite.  I found a different solution, which avoids the use of
reverse, and will work even if the input is infinite, as long as the
words themselves are finite in length.

(http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29048)

module Main where

import Data.List

combineNonEmpty :: (t - Bool) - t - ([t] - t) - [t] - [t]
combineNonEmpty isNull zero cat [] = []
combineNonEmpty isNull zero cat xs =
  let (ys, zs) = break isNull xs
  rest = if null zs
 then []
 else zero : combineNonEmpty isNull zero cat (tail zs)
  in if null ys then rest else cat ys : rest

textToParagraphs :: String - [String]
textToParagraphs = combineNonEmpty null [] (concat . intersperse'  ) . lines

intersperse' :: a - [a] - [a]
intersperse' a [] = []
intersperse' a (x:xs) = x : (if null xs then [] else a : intersperse' a xs)

wordWrap :: Int - [String] - [[String]]
wordWrap maxLineLength [] = []
wordWrap maxLineLength ws =
  let lengths = scanl1 (\a b - a + b + 1) $ map length ws
  wordCount = length $ takeWhile (= maxLineLength) lengths
  wordCount' = if wordCount = 1 then wordCount else 1
  (xs, rest) = splitAt wordCount' ws
  in xs : wordWrap maxLineLength rest

wrapParagraph :: Int - String - [String]
wrapParagraph maxLineLength str =
  let ws = words str
  in if null ws
 then []
 else map unwords $ wordWrap maxLineLength ws

wrapText :: Int - String - String
wrapText maxLineLength =
  unlines . concat . map (wrapParagraph maxLineLength) . textToParagraphs

main :: IO ()
main = interact (wrapText 72)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Weird behavior with arrow commands

2010-07-23 Thread Ronald Guida
I am trying to figure out how to use GHC's arrow commands, and I found
some extremely weird behavior.

In GHC's manual, there is a description of arrow commands, which I
don't really understand.
http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html#id667303
(Primitive Constructs)

I have two questions:
1. What are arrow commands supposed to do?
2. What is this code supposed to do?

-- start of code --

{-# LANGUAGE Arrows #-}
module Main where

import Control.Arrow

foo :: (b - String) - b, Int), Float), Double) - String) - (b - String)
foo f g b = f b ++   ++ g (((b, 8), 1.0), 6.0)

bar :: (t - String) - ((Double, Int) - String) - t - String
bar f g  = proc x - do
  (f - x) `foo` \n m - g - (n)

main = do
  putStrLn $ foo show show 17
  putStrLn $ bar show show 17
  putStrLn $ foo show show 42
  putStrLn $ bar show show 42

-- end of code --

Output from GHCi:

17 (((17,8),1.0),6.0)
17 (6.730326920298707e-306,0)
42 (((42,8),1.0),6.0)
42 (6.730326920298707e-306,0)

Output after compiling with GHC:

17 (((17,8),1.0),6.0)
17 (5.858736684536801e-270,0)
42 (((42,8),1.0),6.0)
42 (5.858736684536801e-270,0)

GHC Version:
The Glorious Glasgow Haskell Compilation System, version 6.12.3

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


[Haskell-cafe] Randomized N-Queens

2010-03-26 Thread Ronald Guida
Hi,

I'm trying to solve the N-queens problem, but with a catch: I want to
generate solutions in a random order.

I know how to solve the N-queens problem; my solver (below) generates all
possible solutions.  What I am trying to do is generate solutions in a
random order by somehow randomizing the order in which nextRow considers
the unused columns.  I tried adding a random number generator to the
solution state; the problem with this approach is that whenever the solver
backtracks, the state of the random number generator backtracks along with
it.  In effect, I am selecting a random, but fixed, permutation for each
row, and then I am applying that same set of permutations along all
computational paths.  Whenever I consider row R, regardless of which path I
have taken, I am applying row R's permutation to the unused columns.

This is not the behavior I want.  I want each computational path to use a
new, different permutation for each row.  On the other hand I also want to
be able to take the first few solutions without waiting for all possible
solutions to be generated.  How might I go about doing this?

-- Ron


module Main
where

import Control.Monad.State
import Data.List
import System.Environment
import System.Random
import System.Random.Shuffle -- from package random-shuffle

newtype Location = Location {unLocation :: (Int, Int)}
  deriving (Show)

isAttacked :: Location - Location - Bool
isAttacked (Location (row1, column1)) (Location (row2, column2)) =
or [ (row1 == row2)
   , (column1 == column2)
   , ((row1 - row2) == (column1 - column2))
   , ((row1 - row2) == (column2 - column1))
   ]

newtype Board = Board {unBoard :: [Location]}
  deriving (Show)

data (RandomGen g) = SolutionState g = SolutionState
{ solnBoard :: Board
, solnUnusedColumns :: [Int]
, solnRandomGen :: g
}

nextRow :: (RandomGen g) = Int - Int - StateT (SolutionState g) [] ()
nextRow n row  = do
  (SolutionState (Board locs) unusedColumns gen) - get
  let (ps, gen') = randShuffleSeq (length unusedColumns) gen
  column - lift $ shuffle unusedColumns ps
  let loc = Location (row, column)
  guard $ all (not . isAttacked loc) locs
  let remainingCols = unusedColumns \\ [column]
  put $ (SolutionState (Board (loc : locs)) remainingCols gen')

randShuffleSeq :: (RandomGen g) = Int - g - ([Int], g)
randShuffleSeq 0 g = ([], g)
randShuffleSeq 1 g = ([], g)
randShuffleSeq n g = (x:xs, g2)
where
  (x, g1) = randomR (0, n-1) g
  (xs, g2) = randShuffleSeq (n-1) g1

allRows :: (RandomGen g) = Int - StateT (SolutionState g) [] ()
allRows n = mapM_ (nextRow n) [1..n]

solve :: (RandomGen g) = Int - g - [Board]
solve n gen = map solnBoard $
  execStateT (allRows n) (SolutionState (Board []) [1..n] gen)

formatSolution :: Board - String
formatSolution = show . map unLocation . unBoard

main :: IO ()
main = do
  args - getArgs
  let boardSize = read $ args !! 0
  maxSolns = if length args  1 then read (args !! 1) else 10
  allSolns = solve boardSize (mkStdGen 42)
  putStrLn $ unlines $ map formatSolution $ take maxSolns allSolns
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-24 Thread Ronald Guida
Those are some very interesting visual languages, Miguel!

I remember drawing some diagrams when I was teaching myself Haskell, but I
never actually tried to create a formal visual language.  Since my
background is in hardware engineering, I would naturally gravitate toward
schematic diagrams.  I am also familiar with the graphical programming
language of LabView.

After reading Miguel's exposition, I thought about how I might draw a
picture of map1.

map1 :: (a - b) - [a] - [b]
map1 f [] = []
map1 f (x:xs) = (f x) : map1 f xs

[image: map1.png]
(Image created with Inkscape)

Here is what I'm thinking:
* Green boxes represent inputs and outputs.
* Inputs are always on the left, outputs are always on the right.
* Inputs appear in top-to-bottom order.
* Data always flows left to right.
* Arrows represent data flow.
* A named white rectangle represents application of the named function.
* A gray rectangle represents a function that arrives through data flow.
* A filled-in arrowhead means the data in the arrow is to be unpacked
and used as a function.
* A named light-blue rectangle (such as on the left, with a colon in it)
represents a pattern match operation.

In thinking about this, I can sense that there are MANY issues with using a
visual language to represent Haskell.  Some issues I can think of:
* How to represent pattern matching?
* How to represent partial application?
* How to represent data types or class constraints in the diagram?
* How to represent a list comprehension or a do statement? (These might
require special visual syntax)
* Will the data flow always take the form of a directed acyclic graph, so
that data never has to flow right-to-left?  (Perhaps there's a way to tie
the knot and get a cycle in the data flow graph.)
* Whether to create special symbols for certain commonly used functions? (In
digital circuit schematics, AND, OR, and NOT gates have special symbols, but
most compound circuits are represented with labeled rectangles.)

Also, if I want to automatically generate an image from a Haskell function,
then my image generator needs to automatically place and route all those
boxes.

I'll have to give more thought to the other versions of map, and maybe make
some more diagrams.

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


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-24 Thread Ronald Guida
On Wed, Mar 24, 2010 at 9:47 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:


 On Mar 25, 2010, at 2:33 PM, Ronald Guida wrote:
 ... a version of map as text ...
 ... a diagram ...

 The thing that strikes me forcibly is that the diagram
 is much bigger than the text.  Not only that, but if
 I am reading it correctly, the text has three lines,
 a type specification and two cases, and the diagram
 covers only one of the two cases.


I agree, absolutely!  One of the things I don't like about schematics (for
digital circuits anyway) is the fact that a schematic is often bigger than
the corresponding VHDL code, and VHDL is a *very* verbose hardware design
language.  On the other hand, sometimes one can visually read a schematic
faster than reading the corresponding code.  My preference is to describe
digital circuits using hardware design language.


 This isn't Ronald Guida's fault.  In fact his is a very
 nice looking diagram, and I could figure it out without
 his explanation of the notation, *given* the textual
 version to start from.

 I've seen several visual programming tools, including
 e-Toys in Squeak, and they tend to be really cool ways
 to quickly build programs with trivial structures.

 (I did not say trivial programs: you can build useful
 programs that do highly non-trivial things, when the
 things that are primitives _for the notation_ are
 capable enough.  Some data mining products have visual
 wire-up-these-tools-into-a-workflow, for example.)


I find it easier to type what I want to do, using a textual programming
language, rather than having to drag and drop and then draw lots of
wires.  I feel the bigger (rhetorical) question is: At the level of code,
what good are visual programming languages?  (To clarify, I know that
diagrams are indispensable for describing designs.  The question pertains to
actual source code.)

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


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-22 Thread Ronald Guida
On Mon, Mar 22, 2010 at 7:02 PM, Dupont Corentin
corentin.dup...@gmail.com wrote:
 Hello, I’m relatively new to Haskell.
 I’m wondering if it exist a tool to graphically represent Haskell code.
...
 Let’s try to do it on a simple example, as an exercise:
 f = Map (+1)

Your graphic for f = map (+1) seems much more complex than the
corresponding code.  I would agree with Ivan Miljenovic:
 I'm of the opinion that unless you just use it on small snippets,
 the generated images will be too large and unwieldy.

The first question I would ask is /why/ would you like to visualize
some Haskell code?  If you want to see the high-level structure of
a complex program, try SourceGraph. (I have never used it though.)

On the other hand, if you are trying to visualize Haskell as part of
your efforts to learn the language, then I believe it would be best to
draw diagrams by hand, rather than relying on an automated tool.
The kinds of things that you'll want to depict are probably going to
vary considerably, depending on what you're trying to understand.

Consider a few different implementations of the map function:

  -- version 1: recursion
  map1 :: (a - b) - [a] - [b]
  map1 f [] = []
  map1 f (x:xs) = (f x) : map1 f xs

  -- version 2: fold
  map2 :: (a - b) - [a] - [b]
  map2 f = foldr ((:) . f) []

  -- version 3: continuation passing style
  map3 :: (a - b) - [a] - [b]
  map3 f xs = map' (\x y - f x : y) xs
where
  map' k [] = []
  map' k (y:ys) = k y  (map' k ys)

  -- version 4: list comprehension
  map4 :: (a - b) - [a] - [b]
  map4 f xs = [f x | x - xs]

  -- version 5: list monad
  map5 :: (a - b) - [a] - [b]
  map5 f xs = xs = (return . f)

These all do exactly the same thing, but each one uses different
techniques.  If I'm trying to learn (or teach) Haskell, I would
probably need a slightly different visual language for each one
in order to capture the most relevant concepts in a useful way.
How would you visualize them?

@Mihai Maruseac:
I think a visual debugger would be a wonderful idea.  You may want
to consider how a visual debugger would work with each of these
versions of map.

:-) You might also consider several versions of factorial :-)
http://www.willamette.edu/~fruehr/haskell/evolution.html

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


Re: [Haskell-cafe] Newbie: Replacing substring?

2008-07-22 Thread Ronald Guida
2008/7/22 Dmitri O.Kondratiev [EMAIL PROTECTED]:
 On the side: The more I use Haskell - the more I like it ! It helps me think
 about the problem I solve much more clearly then when I use imperative
 language.

If I want to replace a substring in a string, then I would search my
string left to right, looking for any occurrence of the substring.  If
I find such an occurrence, I would replace it and continue searching
from immediately after the replacement.  This algorithm can be
directly expressed in Haskell.  More efficient algorithms do exist.

replaceStr :: String - String - String - String
replaceStr [] old new = []
replaceStr str old new = loop str
  where
loop [] = []
loop str =
  let (prefix, rest) = splitAt n str
  in
if old == prefix-- found an occurrence?
then new ++ loop rest   -- yes: replace it
else head str : loop (tail str) -- no: keep looking
n = length old
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Existential quantification problem

2008-07-10 Thread Ronald Guida
On Thu, 10 July 2008, Marco Túlio Gontijo e Silva wrote:
 how do I unbox a existential quantificated data type?

Dan Doel wrote:
elim :: L a - (forall l. l a - r) - r
elim (L e) f = f e

Just one catch: You can't actually write a function 'f' of type
(forall l. l a - r) without knowing something about the forgotten
type of l.

One way to deal with this is by restricting the type of l in the data
declaration.  For example, you could restrict it to the typeclass
Foldable, and then you have access to the methods of that typeclass.

\begin{code}
{-# LANGUAGE ExistentialQuantification #-}

module Main
where

import qualified Data.Foldable as F

data L a = forall l. (F.Foldable l) = L (l a)

toList :: L a - [a]
toList (L x) = F.foldr (:) [] x

main :: IO ()
main = do
  let x = L [1..10]
  print $ toList x
\end{code}

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


Re: [Haskell-cafe] Inductive graphs memory usage

2008-07-10 Thread Ronald Guida
On Thu, Jul 10, 2008 at 4:57 PM, Andre Nathan [EMAIL PROTECTED] wrote:
 Hello

 I'm trying to create a directed graph using the Data.Graph.Inductive.
 The graph is a random graph using the G(n, p) model, that is, each of
 the n nodes is linked to every other node with probability p.

So the average degree of a single node is p * n, and the expected
number of edges in the entire graph will grow as O(n ^2).

 I'm seeing a large increase of memory usage when n grows (this is using
 p = 0.1):

 n = 1000 -  96MB
 n = 2000 - 283MB
 n = 3000 - 760MB

 So, I'm probably doing something very stupid :)

Your ratios are about 1 : 3 : 8.
That pretty close to quadratic growth, 1 : 4 : 9, so I think all is well.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Lazy IO

2008-07-09 Thread Ronald Guida
Suppose I have a lazy function f :: [Int] - [Int], and I happen to
know that for all n, the n-th element of the output may only depend on
the first (n-1) elements of the input.

I want to print a number from f's output list, and then ask the user
for the next number in f's input list, and then loop until the user
stops providing valid numbers.  I also need to be able to do IO after
my loop exits.

Consider the following code:
--
module Main
where

import Control.Monad.Fix
import System.IO.Unsafe

promptInt :: String - IO (Maybe Int)
promptInt p = do
  putStr p
  s - getLine
  let rs =  reads s
  if not $ null rs
then return $ Just $ fst $ head rs
else return $ Nothing

promptInts :: [String] - IO [Int]
promptInts [] = return []
promptInts (p:ps) = do
  m - promptInt p
  case m of
Just n - do
   ns - unsafeInterleaveIO $ promptInts ps
   return $ n:ns
Nothing - return []

-- assume accumulator is an opaque function
accumulator :: [Int] - [Int]
accumulator = scanl (+) 0

makeAccPrompt :: Int - String
makeAccPrompt n = [Acc =  ++ show n ++ ] ? 

main :: IO ()
main = do
  xs - mfix $ promptInts . map makeAccPrompt . accumulator
  seq (length xs) $ print xs
--

Question: If I can't change my function f (in this case, accumulator),
then is it possible to get the effect I want without having to resort
to unsafeInterleaveIO?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Bug in Emacs Haskell Mode

2008-06-24 Thread Ronald Guida
Emacs Haskell Mode has the following useful feature: when Haskell -
Load File is used to load a file into GHCi from Emacs, Haskell Mode
automatically looks for a *.cabal file in an attempt to find the
project directory.

When Haskell Mode finds the *.cabal file, it fails to check whether it
has found a file or a folder.  As a result, if I want to load a
Haskell file that has no corresponding .cabal file, then Haskell Mode
locates my ~/.cabal *folder* and assumes that it's my project
directory.

I have a ~/.cabal folder because Cabal-Install puts it there.
Cabal-Install is part of Haskell's new package management system.

Now I don't know very much Emacs Lisp, but I figured out a fix for the
problem.  In Haskell-Mode-2.4, in the file haskell-cabal.el, I changed
the function haskell-cabal-find-file so that it explicitly checks to
make sure that any *.cabal file is in fact a file and not a folder.

I don't know if comparing the first letter of the file mode string to
'd' is the right way to diferentiate a folder from a file, but so far
it appears to work for me, so I thought I'd share it.

(defun haskell-cabal-find-file ()
  Return a buffer visiting the cabal file of the current directory, or nil.
  (catch 'found
(let ((user (nth 2 (file-attributes default-directory)))
  ;; Abbreviate, so as to stop when we cross ~/.
  (root (abbreviate-file-name default-directory))
  files)
  (while (and root (equal user (nth 2 (file-attributes root
(let ((files (directory-files root 'full \\.cabal\\')))
  (if (and files
   (not (equal 100 (aref (nth 8
   (file-attributes (car files))) 0
  (throw 'found (find-file-noselect (car files)))
(if (equal root
   (setq root (file-name-directory
   (directory-file-name root
(setq root nil
nil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haddock compilation problem

2008-06-20 Thread Ronald Guida
I have added ticket #18 to the Haddock Trac.
http://trac.haskell.org/haddock/wiki
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haddock compilation problem

2008-06-19 Thread Ronald Guida
I just upgraded to ghc-6.8.3, using a linux binary, and I am having a
problem compiling Haddock.  Haddock 2.1.0 and Haddock 2.0.0.0 both
fail to build under ghc-6.8.3, but they both build successfully with
ghc-6.8.2.  I don't know if this is a Haddock problem, or a GHC
problem, or perhaps something else entirely?

Here is the error I'm getting.  It is the same error for either
version of Haddock.

[15 of 24] Compiling Haddock.GHC.Typecheck (
src/Haddock/GHC/Typecheck.hs,
dist/build/haddock/haddock-tmp/Haddock/GHC/Typecheck.o )

src/Haddock/GHC/Typecheck.hs:82:4:
Constructor `HsModule' should have 7 arguments, but has been given 8
In the pattern: HsModule _ _ _ _ _ mbOpts _ _
In a pattern binding: HsModule _ _ _ _ _ mbOpts _ _ = unLoc parsed
In the definition of `mkGhcModule':
mkGhcModule (mod, file, checkedMod) dynflags
  = GhcModule
  {ghcModule = mod, ghcFilename = file,
ghcMbDocOpts = mbOpts,
   ghcHaddockModInfo = info, ghcMbDoc = mbDoc,
ghcGroup = group,
   ghcMbExports = mbExports,
   ghcExportedNames = modInfoExports modInfo,
   ghcNamesInScope = fromJust $
modInfoTopLevelScope modInfo,
   ghcInstances = modInfoInstances modInfo}
  where
  HsModule _ _ _ _ _ mbOpts _ _ = unLoc parsed
  (group, _, mbExports, mbDoc, info) = renamed
  (parsed, renamed, _, modInfo) = checkedMod
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Printing a random list

2008-06-08 Thread Ronald Guida
Bryan Catanzaro wrote:
 However, when I ran my random list generator, the interpreter had a stack
 overflow.  Here's my code again:
 ---
 module Main
where
  import IO
  import Random

  randomList :: Random a = a - a- [IO a]
  randomList lbound ubound = randomRIO(lbound, ubound) : randomList
 lbound ubound


  main = do
myRandomList - sequence(randomList (0::Int) 255)
putStrLn(show(take 10 myRandomList))
 ---

 It seems that this code somehow tries to evaluate every element of the
 infinite list defined by randomList.

You are correct.

 Can you tell me why it is not lazily evaluating this list?

Whenever you use IO, there is a baton being passed along behind the
scenes.  The baton is called RealWorld# and it represents the fact
that interactions with global state and the outside world have to be
serialized.

In particular, whenever you use the global random number generator, a
global state variable has to be updated.  This has to be serialized,
thus the baton has to be passed along from one action to the next.

When you sequence a list of IO actions, you are effectively sending
the baton along that list, and you don't get it back until the end of
the list is reached.  Your code is sending the baton into an infinite
list of actions, never to be returned.

  I can get around this by changing main to do this
 instead:

 ---
  main = do
myRandomList - sequence(take 10 (randomList (0::Int) 255))
putStrLn(show(myRandomList))
 ---

Now you are sending the baton into a list of only 10 actions.  The
baton comes back, and the program goes on.

If you don't know in advance how many random numbers you need, and if
you are satisfied with the global random number generator, then Don
Stewart's solution is a better approach.

Don Stewart wrote:
   main = do
 g - newStdGen
 print (take 10 (randomRs (0,255) g :: [Int]))

If you want to be able to reproduce the same sequence of random
numbers, for example for testing and debugging purposes, then you can
use mkStdGen to create your own random number generator, independent
of the global one.  The catch is that you will have to thread the
state of the random number generator through your code.  Once you
learn about monads (if you haven't already), you'll recognize that you
can use the State monad for your random number generator.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Teaching Monads

2008-06-07 Thread Ronald Guida
Monads in Haskell are a topic that I, like most beginners, find
difficult and mind-twisting.  Now that I think I understand monads,
they seem to be very simple; I've read that this is a common
experience.

So I wonder, what would it take to help beginners catch on with a
minimum of fuss or frustration?  The plethora of monad tutorials out
there is clear evidence that plenty of others have wondered the same
thing.

What made monads click for me is when I understood the following
things:

1. When monads are being used, closures are almost always involved.

2. These closures naturally arise when desugaring do-syntax.

 do x1 - m1   m1 = (\x1 -
x2 - m2   m2 = (\x2 -  [Eq1]
x3 - m3   m3 = (\x3 -
return (f x1 x2 x3)return (f x1 x2 x3

3. These closures are extremely similar to the closures that arise
   when desugaring let-syntax.

 let x1 = f1 inf1 -$ (\x1 -  Where:
   let x2 = f2 in  f2 -$ (\x2 -  (-$) :: a - (a - b) - b
 let x3 = f3 inf3 -$ (\x3 -  x -$ f = f x
   f x1 x2 x3  f x1 x2 x3)))

4. While I can think of a monad as a fancy container that holds an
   element of type t, it might be more accurate to think of a monad
   as a container that merely displays the type t as a label for its
   contents. The container might hold one object of type t, or it
   might hold several.  It might not be holding any at all.  Perhaps
   the container /never/ holds an object of type t, but instead it
   holds a set of instructions to produce such an object.
   (e.g. Reader, State).

Naturally, it's hard to illustrate nested closures, higher-order
functions, and objects that aren't really there.  It's easy to
illustrate a sequential scheme where a single thing passes through a
series of operations, while some related data travels in parallel.

   m1 = f1 = f2 = f3[Eq2]

In any case, the extreme similarity between desugared do and
desugared let leads me to think of the concepts of a manual
plumbing system and a monadic plumbing system.

Basically, a manual plumbing system is what I have if I'm threading
information down through a series of nested function calls in a
certain stereotypical way.  A monadic plumbing system is what I get
when I introduce the appropriate monad to encapsulate my threading.

In fact, if I look at Wadler [*], there are three examples of an
evaluator that use what I'm calling manual plumbing.  In section
2.5, the operations required of a monad (return, bind) pretty much
just drop right out.  Wadler even points out the similarity between
bind and let.

Now that I finally get it, I feel that the Wadler paper, section 2.5
in particular, is probably a better introduction than many of the
monad tutorials out there.  Moreover, I feel that for /some/ of
the tutorials out there, they spend too much time and too many
illustrations explaining things like [Eq2], and then they quickly
present do-notation and gloss over [Eq1].

For me, I found that that the concepts of manual plumbing and
monadic plumbing were key to actually grasping the Wadler paper and
understanding what monads are.  In particular, I feel that these two
concepts might be a way to help other beginners catch on as well.

OK, so before I attempt to write a monad tutorial based on manual
plumbing and monadic plumbing, I would like to know, does anyone
else think this is a good idea?

[*] Monads for Functional Programming.
(http://homepages.inf.ed.ac.uk/wadler/papers/marktoberdorf/baastad.pdf)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: appending an element to a list

2008-06-03 Thread Ronald Guida
Thank you, apfelmus.  That was a wonderful explanation; the debit
method in [1] finally makes sense.

[1]: Chris Okasaki. Purely Function Data Structures.
 http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Laziness leaks

2008-06-03 Thread Ronald Guida
I was looking at the real time queues in [1] and I wanted to see what
would happen if I tried to write one in Haskell.  The easy part was
translating the real time queue from [1], p43 into Haskell.

The hard part is testing to see if the rotations really happen what
they should.  Basically, I decided to use Debug.Trace.trace to see
when rotations were actually occurring.

I pushed the numbers 1 to 10 into the queue, and then I popped the
queue ten times.  What I found is that none of the rotations would
actually take place until the first time I actually tried to /display
the value/ of a popped element.  What I realized is that my test
driver is lazy.  I figured out that I could put a bunch of 'seq'
functions in the test driver to get the rotations to happen.

My demonstration code is in:
http://hpaste.org/8080

This leads to two questions:

1. If I find a laziness leak, is 'seq' the appropriate way to plug it?

2. Is there any way to systematically search for or detect laziness
   leaks?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Laziness leaks

2008-06-03 Thread Ronald Guida
Don Stewart wrote:
 2. Is there any way to systematically search for or detect laziness
leaks?

 Profiling, and looking at the Core. Being explicit about the
 evaluation strategy you want is a fine idea though.

Albert Y. C. Lai wrote
 A true cause of laziness is in accumulating a chain of tail's and
 snocs without intermediate forcing, as observed.

So I just thought of something.  If laziness leads to laziness leaks,
then is there such a thing as a strictness leak?  I realized that the
answer is yes.

A lazy leak is a situation where I'm wasting resources to delay a
sequence of calculations instead of just doing them now.  But in a
strict language, I might waste resources to compute things that I'll
never need.  I would call that a strictness leak.

Now I could ask the dual question, How do I detect strictness leaks,
and I would probably get the same answers: profiling, looking at
object code, and being explicit about the evaluation strategy.

Both types of leaks share a lot in common.  In both cases, I'm wasting
resources.  If I have a real-time system, then either type of leak can
cause me to a miss a deadline.

With a strict evaluation strategy, I might miss a nearby deadline
because I'm busy calculating things that I don't need until the
distant future.

With a lazy evaluation strategy, I might miss a distant deadline
because I'm lazily putting off a calculation now.

If I were a college student, then this would be a laziness leak:

  Professor X assigns a report, due in a month.  Two days before the
  report is due, I'll head to the drugstore, load up on caffeine, and
  work for 48 hours straight to get it done.

And this would be a strictness leak:

  Professor X assigns a report, due in a month.  As soon as I leave
  the classroom, I'll head to the drugstore, load up on caffeine, and
  work for 48 hours straight to get it done.

And this would be an effective solution:

  Professor X assigns a report, due in a month.  I'll select 15 days,
  spaced out over the next month, and allocate four hours per day to
  work on the report.

By default, a lazy language will procrastinate.  By default, a strict
language will anticrastinate.  Either way, I can waste resources by
blindly accepting the default time management plan.

So the real question is How do I avoid laziness leaks or strictness
leaks and apparently, the real answers are (1) learn how to
recognize when the default plan will waste resources, and (2) learn
how to express reasonable evaluation strategies in code.

I would ask, how do I examine the evaluation order of my code, but
the answer is already available: use a debugger.  Haskell already has
debugging tools that do exactly what I need.
(http://www.haskell.org/haskellwiki/Debugging)

In particular, HOOD looks extremely interesting.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A simple beginner question

2008-06-03 Thread Ronald Guida
Adam Smyczek wrote:
 data SampleType = A | B Int | C String | D --  etc.

 sampleTypes = [A, B 5, C test] :: [SampleType]

 How do I find for example element A in the sampleTypes list?

Here's one way to do it:

filter (\x - case x of A - True; otherwise - False) sampleTypes
  == [A]

filter (\x - case x of B _ - True; otherwise - False) sampleTypes
  == [B 5]

filter (\x - case x of C _ - True; otherwise - False) sampleTypes
  == [C test]

Your idea works just as well:
 isA :: SampleType - Bool
 isA A = True
 isA _ = False

filter isA sampleTypes
  == [A]

There is a third possibility:  Have you learned about the maybe
function or the either function yet?
  maybe :: b - (a - b) - Maybe a - b
  either :: (a - c) - (b - c) - Either a b - c

I would call these mediating morphisms, where morphism is techno-
babble for function. You could write your own version of one of these
for SampleType.  Assuming you have:

  data SampleType = A | B Int | C String

You could write:

  sampletype :: t
- (Int - t)
- (String - t)
- SampleType - t
  sampletype a bf cf s =
 case s of
   A - a
   B n - bf n
   C s - cf s

  isA = sampletype True (const False) (const False)
  isB = sampletype False (const True) (const False)
  isC = sampletype False (const False) (const True)

filter isA sampleTypes
  == [A]

This (the mediating morphism) is probably overkill for what you want
to do, though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Images and GUIs in Haskell

2008-05-31 Thread Ronald Guida
Two questions:

1. In a Haskell program, if all I want to do is output an image, like
a graph or chart, what is the simplest library to use?

N.B. Simpler := easier to get minimal functionality. I really don't
want to wade through a bunch of boilerplate or climb a steep learning
curve just to be able to plot a few lines or circles.

2. Suppose I want interactivity.  For example, I want to plot a line
graph, and then let the user click and drag the data points.  From
what I understand about GUIs, I would need to track mouse buttons (up
and down), mouse movements, and possibly keystrokes.  (I know this is
the complete opposite extreme from my first question)

In this case, what would be the best (not necessarily simplest)
library to use?  What would you recommend?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Images and GUIs in Haskell

2008-05-31 Thread Ronald Guida
I wrote:
 1. In a Haskell program, if all I want to do is output an image, like
 a graph or chart, what is the simplest library to use?

Achim Schneider wrote:
 http://hackage.haskell.org/packages/archive/pkg-list.html#cat:Graphics

OK, Chart (the first package under Graphics) is obviously the answer to (1).

I wrote:
 2. Suppose I want interactivity.  For example, I want to plot a line
 graph, and then let the user click and drag the data points.  ...
 the complete opposite extreme from my first question

So I have a choice: OpenGL, HGL, SDL, ObjectIO(?), or even straight X11/Win32 :/
Let me ask both ways:

2a. Which of these (or perhaps something else) is the simplest/easiest
to get started with?

2b. Could someone please point me to some advice to help me decide
which of these would be the best for me to use.  I'm just trying to
avoid the need to invest gobs of time into investigating libraries.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Ronald Guida
It looks like a simple race condition to me.  You are using
waitForProcess pid to wait for runInteractiveCommand to finish, but
you don't seem to have anything that waits for createDefFile to
finish.

 main :: IO ()
 main = do
   (file:_) - getArgs
   (_, out, _, pid) - runInteractiveCommand $ dumpbin /EXPORTS  ++ file
   forkIO (createDefFile file out)
   waitForProcess pid
   hClose out
   hFlush stdout
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Commutative monads vs Applicative functors

2008-05-14 Thread Ronald Guida
David Menendez wrote:
 To summarize: some applicative functors are commutative, some
 applicative functors are monads, and the ones that are both are
 commutative monads.

OK, so commutativity is orthogonal to idiom vs monad.  Commutativity
depends on whether or not the order of side effects is important.
Being a monad or just an idiom depends on whether or not join is
supported.  Examples can be constructed for all 4 possibilities of
{idiom,  monad} (x) {non-commutative, commutative}.

Thank you all for clearing this up for me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad vs ArrowChoice

2008-05-14 Thread Ronald Guida
I have read that Monad is stronger than Idiom because Monad lets me
use the results of a computation to choose between the side effects of
alternative future computations, while Idiom does not have this
feature.  Arrow does not have this feature either.

ArrowChoice has the feature that the sum type, Either, can be used to
choose between alternative computations, including their side effects.
 I know that Monad is supposed to be stronger than ArrowChoice, but I
have to ask, what exactly can Monad do that ArrowChoice can't do?

Let me set up an example to illustrate where I'm coming from.

 import Control.Monad.Writer
 import Control.Applicative
 import Control.Arrow hiding (pure)

The missileControl function accepts a flag to determine whether
missiles actually get launched, and it returns the number of
casualties.

 missileControl :: Bool - IO Integer
 missileControl b = do
  showFlag b
  casualties - if b
  then launchMissiles
  else doNotLaunch
  return casualties

 showFlag :: Bool - IO Bool
 showFlag b = (putStrLn $ Launch flag =  ++ show b)  return b

 launchMissiles :: IO Integer
 launchMissiles = do
   putStrLn Missiles have been launched.
   putStrLn Casualties = 6,700,000,000.
   return 67

 doNotLaunch :: IO Integer
 doNotLaunch = putStrLn Missiles not launched.  return 0

If I try to use an Idiom, or even an Arrow, instead of a Monad, then I
don't get to choose between the alternative side effects, and the
results will be similar to this:

 missileControl' :: Bool - IO Integer
 missileControl' b = do
   showFlag b
   casualties - launchMissiles
   casualties' - doNotLaunch
   if b
 then return casualties
 else return casualties'

If I use ArrowChoice, then I can do this:

 missileControl2 :: Bool - IO Integer
 missileControl2 b = runKleisli a b
 where a = (Kleisli $ showFlag)  (arr boolToEither) 
   ((Kleisli $ const launchMissiles) |||
(Kleisli $ const doNotLaunch))

 boolToEither :: Bool - Either () ()
 boolToEither True = Left ()
 boolToEither False = Right ()

GHCi missileControl2 True
Launch flag = True
Missiles have been launched.
Casualties = 6,700,000,000.
67

GHCi missileControl2 False
Launch flag = False
Missiles not launched.
0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Commutative monads vs Applicative functors

2008-05-13 Thread Ronald Guida
I have a few questions about commutative monads and applicative functors.

From what I have read about applicative functors, they are weaker than
monads because with a monad, I can use the results of a computation to
select between alternative future computations and their side effects,
whereas with an applicative functor, I can only select between the
results of computations, while the structure of those computations and
their side effects are fixed in advance.

But then there are commutative monads.  I'm not exactly sure what a
commutative monad is, but my understanding is that in a commutative
monad the order of side effects does not matter.

This leads me to wonder, are commutative monads still stronger than
applicative functors, or are they equivalent?

And by the way, what exactly is a commutative monad?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hangman game

2008-01-21 Thread Ronald Guida
Thank you for the positive responses.  The best kind of feedback is
the kind that makes me have to think, and I've done alot of thinking.

_Regarding monads and interfaces_

Paul Johnson wrote:
 1: Your GameState type can itself be made into a monad. Take a look
 at the All About Monads tutorial, especially the State
 monad. Think about the invariants in GameState; can you produce a
 new monad that guarantees these invariants through a limited set of
 actions. How do these actions correspond to user perceptions?

 2: You can layer monads by using monad transformers. Extend the
 solution to part 1 by using StateT IO instead of just State.

OK, Here's the new monad and the corresponding transformer.
 type Hangman = State GameState
 type HangmanT = StateT GameState

And here's an interface for the Hangman monad.
 newHangmanGame :: (MonadState GameState m) = String - m ()
 newHangmanGame = put . newGameState
 
 renderHangmanGame :: (MonadIO m, MonadState GameState m) = m ()
 renderHangmanGame = get = return . renderGameState
 = liftIO . putStrLn
 
 guessLetter :: (MonadState GameState m) = Char - m ()
 guessLetter = modify . handleGuess
 
 getWonLost :: (MonadState GameState m) = m (Maybe Bool)
 getWonLost = get = return . gsWonLost
 
 getAnswer :: (MonadState GameState m) = m String
 getAnswer = get = return . gsAnswer

This all seems a little pointless :) for a simple game, nevertheless I
proceeded to modify startNewGame and gameLoop to use the Hangman
interface.  The modifications were trivial.  The type signatures for
startNewGame and gameLoop become:
 startNewGame :: HangmanT IO ()
 gameLoop :: HangmanT IO ()

_Regarding random numbers_

Yitzchak Gale wrote:
 You can add one more field to GameState that holds a random
 generator.

I tried it; it was very easy.

Paul Johnson wrote:
 Can you make your game a function of a list of random numbers?

Yitzchak Gale wrote:
 I would advise against that technique. In more complex games, you
 may need to do many different kinds of random calculations in
 complex orders. Keeping a random generator inside a state monad is
 perfect for that. And since Ronald already set up the plumbing for
 the state monad, he is already home.

I simply modified startNewGame and gameLoop to accept a list of
integers.  In startNewGame, I use the first integer in the list to
choose a word, and then I pass the rest of the list to gameLoop.  In
gameLoop, I simply pass the list along to every recursive call to
startNewGame or gameLoop.

 main :: IO ()
 main = do
   ...
   g - getStdGen
   let rs = randomRs (0,length wordList - 1) g
   runStateT (startNewGame rs) undefined
   return ()
 
 startNewGame :: [Int] - HangmanT IO ()
 startNewGame (r:rs) = do
   let word = wordList !! r
   newHangmanGame word
   renderHangmanGame
   gameLoop rs
 
 gameLoop :: [Int] - HangmanT IO ()
 gameLoop rs = ...

I suppose I could easily push the list of random numbers into
GameState to avoid manually threading it around my program.  If I did
that, then the only difference between the two techniques would be (1)
adding a field to hold a random number generator, vs (2) adding a
field to hold an infinite list of random numbers.  If I store a list
of numbers, then I have to choose a probability distribution at
initialization time.  If I store the generator, then I am free to
change the probability distribution on the fly.

For a Hangman game, the only time I need to change the probability
distribution is if I load a new word list.  If I wanted to be able to
load a new word list, then perhaps I need to carry the word list
inside the GameState as well?

_Random numbers continued_

So let me create a HangmanRand monad to encapsulate the process of
selecting random words.

 type HangmanRand = State RandState
 type HangmanRandT = StateT RandState
 
 data RandState = RandState {
   rsRandGen :: StdGen,-- the random number generator
   rsWordList :: [String]  -- the word list
 }
 
 initHangmanRand :: (MonadState RandState m) = [String] - StdGen - m
()
 initHangmanRand words g = put $ RandState{
 rsRandGen = g,
 rsWordList = words}
 
 getRandomWord :: (MonadState RandState m) = m String
 getRandomWord = do
   rs - get
   let words = rsWordList rs
   let (n, g) = randomR (0,length words - 1) $ rsRandGen rs
   put $ rs{rsRandGen = g}
   return $ words !! n

I can easily modify the game to use HangmanRand.  My gameLoop doesn't
have to change at all (apart from the type signature).

 main :: IO ()
 main = do
   hSetBuffering stdout NoBuffering
   putStr Welcome to Hangman!\n\n
   putStr instructions
   let seed = 5
   let g = mkStdGen seed
   runStateT (runStateT (initGame wordList g) undefined) undefined
   return ()
 
 initGame :: [String] - StdGen - HangmanT (HangmanRandT IO) ()
 initGame words g = do
   lift $ initHangmanRand words g
   startNewGame
 
 startNewGame :: HangmanT (HangmanRandT IO) ()
 startNewGame = do
   word - 

[Haskell-cafe] Smart Constructor Puzzle

2007-12-20 Thread Ronald Guida

I'm playing around with smart constructors, and I have encountered a
weird puzzle.

My goal is to do vector arithmetic.  I'm using smart constructors so
that I can store a vector as a list and use the type system to
staticly enforce the length of a vector.

So my first step is to define Peano numbers at the type level.

 data PZero   = PZero   deriving (Show)
 data PSucc a = PSucc a deriving (Show)

 type P1 = PSucc PZero
 type P2 = PSucc P1
 type P3 = PSucc P2
 -- etc

Next, I define a vector type and tag it with a Peano number.

 data Vec s t = Vec [t] deriving (Eq, Ord, Show, Read)

Now I can define a few smart constructors.

 vec0 :: Vec PZero t
 vec0 = Vec []

 vec1 :: t - Vec P1 t
 vec1 x = Vec [x]

 vec2 :: t - t - Vec P2 t
 vec2 x y = Vec [x, y]

 vec3 :: t - t - t - Vec P3 t
 vec3 x y z = Vec [x, y, z]

Now here's the puzzle.  I want to create a function vecLength that
accepts a vector and returns its length.  The catch is that I want to
calculate the length based on the /type/ of the vector, without
looking at the number of elements in the list.

So I started by defining a class that allows me to convert a Peano
number to an integer.  I couldn't figure out how to define a function
that converts the type directly to an integer, so I am using a
two-step process.  Given a Peano type /t/, I would use the expression
pToInt (pGetValue :: t).

 class Peano t where
 pGetValue :: t
 pToInt :: t - Int

 instance Peano PZero where
 pGetValue = PZero
 pToInt _ = 0

 instance (Peano t) = Peano (PSucc t) where
 pGetValue = PSucc pGetValue
 pToInt (PSucc a) = 1 + pToInt a

Finally, I tried to define vecLength, but I am getting an error.

 vecLength :: (Peano s) = Vec s t - Int
 vecLength _ = pToInt (pGetValue :: s)

 Could not deduce (Peano s1) from the context ()
   arising from a use of `pGetValue'
 Possible fix:
   add (Peano s1) to the context of the polymorphic type `forall s. s'
 In the first argument of `pToInt', namely `(pGetValue :: s)'
 In the expression: pToInt (pGetValue :: s)
 In the definition of `vecLength':
 vecLength _ = pToInt (pGetValue :: s)

Any suggestions?
-- Ron

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


[Haskell-cafe] Space and time leaks

2007-10-03 Thread Ronald Guida

I need some help with space and time leaks.

I know of two types of space leak.  The first type of leak occurs when
a function uses unnecessary stack or heap space.

GHCi sum [1..10^6]
*** Exception: stack overflow

Apparently, the default definition for sum has a space leak.
I can define my own sum in terms of strict foldl ...

 sum' xs = foldl' (+) 0 xs

... and it doesn't overflow the stack.

GHCi sum' [1..10^6]
5050
(0.27 secs, 112403416 bytes)

GHCi sum' [1..10^7]
500500
(2.73 secs, 1161223384 bytes)

GHCi sum' [1..10^8]
50005000
(27.83 secs, 11645261144 bytes)

I think there's still a space leak; I don't understand why GHCi using
10^8, 10^9, 10^10 bytes of memory for these calculations.

The other type of space leak I know of is when I have a chunk of data
in memory that I no longer need, such that the data is still being
referenced somewhere.  Since, in theory, I might still access the
data, the garbage collector can't reclaim the memory.  I'm not sure
how to construct an example though.

Regarding time leaks, I only know of one kind of leak.  If I have a
calculation that accumulates data over time, and I don't ask for any
results until the end, then, due to laziness, that calculation might
accumulate a chain of unevaluated thunks.  When I get the the end and
demand the final result, I have to wait for it while the RTS
evaluates a long chain of thunks.

The chain of unevaluated thunks is a space leak.  The time leak occurs
because the capture process and the accumulate process are supposed to
be interleaved, such that I perform some computations after I capture
each piece of data.  If I have to wait around at the end, then it
means the capture process and the accumulate process happened in
sequence.

As far as I know, every time leak has a companion space leak; it's not
possible to create a time leak without a space leak to go with it.  Is
this really true?

Now for the hard questions.
1. How do I go about detecting space and time leaks?
2. Once I find a leak, how do I fix it?
3. Are there any programming techniques I can use to avoid leaks?

-- Ron

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


Re: [Haskell-cafe] what is f=f (not) doing ?

2007-09-23 Thread Ronald Guida

Peter Verswyvelen wrote:
 I though it was impossible to detect a deadlock (and a black hole is
 something like a deadlock no?) *before* it occurred, but in this
 case, we're talking about detecting it *when* it occurs, no? And
 then raising an error instead of just blocking?

Generally, it's not possible to prevent a deadlock before it occurs;
it's actually equivalent to the halting problem.

When a deadlock is about to occur, it /is/ possible, is principle, to
detect the condition and raise an error.  What you would need to do is
keep track, for each thread, of everything that thread may depend on.
Whenever a thread tries to allocate a resource, you need to scan the
dependency graph and determine whether or not the new allocation is
safe.  Sometimes you might raise a false alarm, though.

Once a deadlock has /already/ occurred, it becomes easier to detect,
but detection still depends on being able to determine everything a
thread might depend on.

Now in GHC, apparently, when a thread needs a value that hasn't been
calculated yet, the thread blocks, waiting for that value to be
calculated.  If the Haskell code creates an infinite loop, then a
thread may block waiting for itself.  The example given is f = f.
Well, before we ask for self-blocking detection, lets try a bigger
loop like (f = g ; g = f) and suppose that the computations of f and g
get assigned to different threads.  Self-blocking detection won't help
you here.  You need some kind of loop-blocking detection.

At this point, I would assume that as we take more things into
account, the problem of detecting deadlock becomes increasingly
complicated and the detection algorithms consume more and more
resources.  That's why many major operating systems don't have
deadlock detection.

On the other hand, perhaps deadlock detection is the wrong way to look
at this.  I think we are casting a net that's too big for the problem
that we're really trying to solve.

A deadlock happens whenever two (or more) threads are blocked on each
other.  Deadlocks can be extremely hard to detect, especially if they
occur intermittently.

On the other hand, we as programmers can detect, at design-time, that
f = f is an algebraic loop.  We know that some loops are just tying
the knot and they're perfectly fine, while other loops involve
self-dependency and evaluate to bottom.

 fib = 1 : 1 : zipWith (+) fib (tail fib)  -- tying the knot
 foo = 1 : zipWith (+) foo (tail foo)  -- algebraic loop

Looking closer at foo, if we let x = (foo !! 1), then we have the
equation x = 1 + x.  The result is that x = bottom.

To detect an algebraic loop, we would need to express a computation as
a dependency graph and then look for any loops in the graph.  As long
as we are looking at a /pure/ computation, my intuition tells me that
in many cases it should be possible, through static analysis, to build
the dependency graph and check for any loops.

Moreover, my intuition tells me that the static analysis involved in
building these dependency graphs might already be available as part of
an existing optimizer.

Even if we don't detect an algebraic loop at compile-time, I think we
could definitely detect it at run-time if we have enough computational
resources.

-- Ron

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


Re: [Haskell-cafe] Win32 Open GL / Glut Applications

2007-09-23 Thread Ronald Guida

Sven Panne wrote:
 On Friday 21 September 2007 20:19, Ronald Guida wrote:
 John Wicket wrote:
   yea, that is probably what I need.  Can you post in a 
step-by-step way.


 Here is a set of instructions for what I had to do to get FreeGLUT
 working with GHCi [...].

 Oh dear, a long a sad story... :-(

And frustrating too.  :-)

 [...]  Although I just don't understand why freeglut, the
 Haskell GLUT library, and GHCi won't work together in the first place.

 That statement is not correct, they *do* work together. The problem 
you are
 experiencing is that the GLUT version used to build the GHC 
installer/binary
 distro is obviously not freeglut, but classic GLUT. As long as you 
only
 use classic GLUT features, this is OK. Things get really hairy when 
you

 want to use freeglut-only features and still have a GHC installer/binary
 distro which is guaranteed to run with classic GLUT as well (with
 restricted features in the latter case, of course). To do this 
properly, the

 GLUT package has to resolve freeglut-only API entries dynamically, but
 glutGetProcAddress is not contained in lots of GLUT DLLs out in the wild
 (it's in GLUT API version 5 plus freeglut). This is really a pity and 
a big
 design flaw in GLUT IMHO, but there is not much one can do about 
that.The

 only thing left is to load the GLUT/freeglut dynamic library,
 well, dynamically and resolve the freeglut API entries by hand. 
Doing this
 is not hard, but a little bit tricky to get right portably: Use 
dlopen/dlsym
 on most *nices, LoadLibrary/GetProcAddress on Windoze, something else 
on Mac
 OS, take care of possible leading underscores, etc. etc. I really 
wanted to

 avoid doing this, but it looks like there is no way around it. Given the
 current time frame for the GHC 6.8.1 release, I don't think that it is
 feasible to get this into that release, because I would need feedback 
from

 lots of platforms to be sure things work.

In fact, when I compiled freeglut with MSVC, it compiled successfully
out of the box.  When I tried to use my new freeglut.dll with GHCi,
I got linker errors all over the place and I eventually discovered
that the problem involves leading underscores.

 [...] darcs-1.0.9
   http://darcs.net/darcs-1.0.9.tar.gz [...]

 There are darcs binaries for Windows, so there is no need to build it 
and the

 libraries it needs:

 
http://wiki.darcs.net/DarcsWiki/CategoryBinaries#head-c7910dd98302946c671cf63cb62712589b392074


Ooo, Thank you!  ;-)

 Furthermore, darcs itself is not needed for what you want to do.

 [...] Freeglut-2.4.0
   http://freeglut.sourceforge.net/index.php#download [...]

 The freeglut project currently doesn't provide prebuilt binaries, so 
this is
 hardly the GLUT package's fault. ;-) Furthermore, the official way to 
build
 the project on Windows is via MSVC, and there are projects files for 
this.
 Building a DLL via MinGW/MSYS would be nice, too, so perhaps you 
could post
 your patches in the freeglut-developer mailing list. I think that 
there will
 be a new freeglut release soon, perhaps I can push people to make at 
least a
 simple ZIP file with the binaries for Windows available on the 
project pages.


 GLUT-2.1.1
   You need to use darcs to download GLUT-2.1.1.
 [...]
Locate the line start starts with build-depends: and remove
the dependencies array and containers

 Now you enter the great world of Cabal versionits and the Big Library 
Splitup

 (tm). ;-) If you want to use a bleeding edge version of GLUT, you need a
 bleeding edge version of GHC and the libraries coming with it. A 
released

 version is available via hackage.haskell.org.

Rumor: Version-itis and the big library splitup are going to break
everyone's existing code!  :-O

   [...] 6. Modify GLUT-2.1.1/Graphics/UI/GLUT/Extensions.hs as 
follows:


Look at the last two lines:

 foreign import ccall unsafe hs_GLUT_getProcAddress 
hs_GLUT_getProcAddress


:: CString - IO (FunPtr a)

Change hs_GLUT_getProcAddress to glutGetProcAddress

   7. Modify GLUT-2.1.1/cbits/HsGLUT.c as follows:

Look for void* hs_GLUT_getProcAddress(char *procName) and
remove the whole function.

 Huh? If you *really* compile against the freeglut header, these steps 
are

 unnecessary. What is the reason for this change?

The reason for this change is that I had reached the point where I had
one remaining linker error.  I found that hs_GLUT_getProcAddress is a
stub that calls the real glutGetProcAddress, and I figured out that
this call to the real glutGetProcAddress was refusing to link.  I made
the determination that (1) the stub is there to fix a broken
glutGetProcAddress, and (2) mine isn't broken.  Therefore, instead of
trying to find the cause of the linker error, I decided to avoid the
error entirely by removing the stub and calling directly to the real
thing.

 {...]
   11. In GHC's directory, there is a file named package.conf.  This
   file contains one extremely long line.  You need

Re: [Haskell-cafe] what is f=f (not) doing ?

2007-09-23 Thread Ronald Guida

Miguel Mitrofanov wrote:
 A deadlock happens whenever two (or more) threads are blocked on each
 other.  Deadlocks can be extremely hard to detect, especially if they
 occur intermittently.

 Isn't that so much different from garbage collection? Replace
 thread with chunk of data, and waits for with has a pointer
 to and these two problems look very similar. And we all know there
 ARE efficient garbage collectors.

Actually, I think the two problems look /extremely/ similar.

When doing garbage collection, one BIG problem is determining what's
really a pointer and what's just data.  There are conservative garbage
collectors that assume just about anything can be a pointer, and then
there are precise garbage collectors that use knowledge of the layout
of chunks of data to identify the pointers to follow.

All garbage collectors have one thing in common, though.  They all
depend on being able to identify, for each chunk of data, what else it
has pointers to.  If all else fails, a conservative GC can simply
assume that everything is potentially a pointer and try to follow it.

Now, a deadlock detector would need to be able to identify, for each
blocked thread, what that thread is waiting for.  The OS already
tracks this information and uses it to determine when a blocked thread
becomes un-blocked and ready to run.

Now, if we could make sure that /all/ locks go through the OS, then
the OS would be able to build a complete dependency table.  When a
deadlock is about to occur, the OS would be able to detect it
immediately.

Back to reality: Not all locks go through the OS.

Suppose I'm using fibers.  That means I have one OS thread running
many routines at the same time, and I'm doing my own cooperative
multitasking.  GHC does this.  The OS has no idea what's going on.

Even if I had an OS that could track all locks, I can still get into
deadlock situations.

Suppose I have a programming error that causes two of my threads to
deadlock.  Furthermore, suppose that when the deadlock is detected, I
make both threads roll back and start again with the same pre-
conditions.  Now they will go back into the same deadlock.  This cycle
will repeat indefinitely, and it's beyond the OS's ability to detect.

Regarding deadlock detection, I think the real questions to ask are
(1) Do deadlocks occur often enough for us to care?
(2) When they do occur, are they severe enough for us to care?

If the answers are both no, then deadlock detection is not worth the
trouble of implementation.  My opinion is that for typical commercial
end-user software, the answers are both no.

For critical computing systems, like flight computers and life
support systems, the answers are obviously yes; a deadlock that
occurs once per million years is still a problem if it can bring down
a multi-million dollar aircraft with hundreds of passengers on board.

For these types of systems, the developers tend to spend extra
development resources to try to design fool-proof systems.  In some
cases, they may even go to heroic lengths to /prove/ that their
software is correct.

It /is/ possible to design a system that cannot deadlock.  It turns
out that one of the necessary conditions for deadlock is the hold and
wait condition.  If a process that's already holding resources is
/not/ allowed to request additional resources, then deadlocks are
impossible.  If we really, absolutely don't want any deadlocks, then
we can design a system in which a process that needs a resource is
required to release all its resources and then re-allocate its updated
list of resources.

-- Ron

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


Re: [Haskell-cafe] Win32 Open GL / Glut Applications

2007-09-21 Thread Ronald Guida

John Wicket wrote:
 yea, that is probably what I need.  Can you post in a step-by-step way.

Here is a set of instructions for what I had to do to get FreeGLUT
working with GHCi.

RANT
Just a little warning: my instructions could be wrong in some places.
Normally, in order to verify my instructions, I would uninstall
everything, start from scratch, follow my instructions step by step,
and verify that they work.

Unfortunately:
* I have low confidence in the accuracy of the following instructions.
* I have only one machine.
* I went through lots of frustration to get freeglut to work with GHCi.
* I am not willing to risk breaking my current installation.
* I do not know of any easy way to preserve my current installation
  and still start over from scratch to test my instuctions.
/RANT

If my instructions are wrong, then please let me know, and I might
attempt to fix it.  Although I just don't understand why freeglut, the
Haskell GLUT library, and GHCi won't work together in the first place.

Here's what I would have to do if I were starting from scratch:

7-Zip
 http://www.7-zip.org/

 This is an open source file archiver for Windows that can handle
 *.gz and *.bz2 files.  Download the Windows version and install it.

GHC 6.6.1
 http://haskell.org/ghc/download_ghc_661.html#windows

 This is the version of GHC that I'm using.  Download and install it.

MinGW/MSYS
 Download all three files, then install them in the order I have
 listed them.  Note: MinGW and MSYS need to live in different
 directories.

 http://sourceforge.net/project/showfiles.php?group_id=2435

   Automated MinGW installer   MinGW-5.1.3.exe
 ** When you run the installer, it will download several more
files for you.

   MSYS: Minimal SystemMSYS-1.0.10.exe

 
http://sourceforge.net/project/showfiles.php?group_id=2435package_id=67879


   MSYS Supplementary ToolsmsysDTK-1.0.1.exe
 ** Scroll down to find Current Release: msysDTK-1.0.1 and
expand this tab.  Select msysDTK-1.0.1.exe

zlib-1.2.3
 http://www.zlib.net/

 The links for zlib source code are about halfway down the page.

 After downloading, the process (IIRC) is
   1. Unzip the source code.
   2. Start MSYS and cd to the source-code directory.
   3. Execute ./configure
   4. Execute make
   5. Execute make install
 I don't remember having any problems with zlib.

cURL-7.16.4
 http://curl.haxx.se/download.html

 Note: It appears that cURL just had a minor revision on Sept 13.  I
 guess you can just try the latest version and see of things work.

 IIRC, the process is exactly the same as the zlib install process,
 and I didn't have any problems here either.

darcs-1.0.9
 http://darcs.net/darcs-1.0.9.tar.gz

 Dependencies that you'll need: cURL and zlib  :-)
 Your darcs installation will have some holes, for example it won't
 support SSL because we didn't satisfy the SSL dependency.

 IIRC, the process here is
   1. Unzip the source code.
   2. Start MSYS and cd to the source-code directory.
   3. Execute autoconf
   4. Execute ./configure
   5. Execute make
   6. Execute make install

Freeglut-2.4.0
 http://freeglut.sourceforge.net/index.php#download

 Here's where the hackery starts.

 1. Download the Freeglut source code and unzip it.
 2. Start MSYS and cd to the source-code directory.
 3. Execute ./configure

 4. Download this custom makefile and put in in the ./src directory.
   http://hpaste.org/2841

 5. Download this custom def file and put in in the ./src directory.
   http://hpaste.org/2842

 6. Cd to the ./src directory and then execute make.
 7. Copy the freeglut.dll to GHC's bin directory (ghc-6.6.1/bin).
 8. Copy the *.h files from freeglut-2.4.0/include/GL
  to ghc-6.6.1/include/mingw/GL.
  Note that glut.h will be overwritten.

GLUT-2.1.1
 You need to use darcs to download GLUT-2.1.1.

 1. Start MSYS, create a directory for the GLUT source code,
  and cd to it.
 2. Execute darcs get http://darcs.haskell.org/libraries/GLUT/;
  and wait a while.
 3. Cd to your new source directory.
 4. Execute autoreconf and wait a while.
 5. Modify GLUT.cabal as follows:

  Locate the line start starts with build-depends: and remove
  the dependencies array and containers

 5. Execute runghc Setup.hs configure and wait.
 6. Modify GLUT-2.1.1/Graphics/UI/GLUT/Extensions.hs as follows:

  Look at the last two lines:

foreign import ccall unsafe hs_GLUT_getProcAddress hs_GLUT_getProcAddress
  :: CString - IO (FunPtr a)

  Change hs_GLUT_getProcAddress to glutGetProcAddress

 7. Modify GLUT-2.1.1/cbits/HsGLUT.c as follows:

  Look for void* hs_GLUT_getProcAddress(char *procName) and
  remove the whole function.

 8. Execute runghc Setup.hs build and wait.

 9. Execute ghc-pkc unregister GLUT.  This unregisters the existing
GLUT haskell library.  Also, search through GHC's directories,
locate any glut library files (*.a, *.o, *.hi) that are in there
and remove them.  You are deleting the existing 

Re: [Haskell-cafe] Win32 Open GL / Glut Applications

2007-09-21 Thread Ronald Guida

Oops, one slight omission:

4. Download this custom makefile and put in in the ./src directory.
  http://hpaste.org/2841
   ** Call this file Makefile, with no extension.

5. Download this custom def file and put in in the ./src directory.
  http://hpaste.org/2842
   ** Call this file freeglut.def.

-- Ron

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


Re: [Haskell-cafe] Win32 Open GL / Glut Applications

2007-09-20 Thread Ronald Guida

John Wicket wrote:
 I can take any of these opengl applications or other examples on the
 web, but I can't get the application to run on Win32?

 They will compile(except for the GLU ones) but when I launch them,
 the windows just closes?  Is HOpenGL supported well on Win32?

 http://www.haskell.org/HOpenGL/

 I have ghc 6.6

John, I also have a Win32 box (I'm using Windows XP) and I wanted to
try some OpenGL as well.

I have news for you, good, bad, and ugly.

First, the bad news: The HOpenGL site is outdated.  Look at [1] and
note the date of the most recent release: September 9, *2003*.

[1] http://www.haskell.org/HOpenGL/releases.html

Now, the good news:

I believe the GHC 6.6.1 prepackaged Windows installer comes with
OpenGL and GLUT libraries built in.  The catch is that the GLUT
library was compiled /without/ support for the FreeGLUT library.  If
standard OpenGL and standard GLUT meet your needs, then go for it.

Lastly, the ugly news:

If you need or want FreeGLUT, then you just need to compile FreeGLUT
itself and then recompile the Haskell GLUT library.  As an alternative
to GLUT, you could also try GLFW.

Be warned, though: I had to resort to major hackery (and a learning
curve) to get either of these to work.  First, I managed to hack GLFW
into partially working.  I took what I learned, applied it to
FreeGLUT, and made some progress there.  I went back and forth,
hacking one library and then the other, accumulating what I had
learned.  In the end, I got FreeGLUT (both the C library and the
Haskell bindings) to compile and I successfully installed them into
GHC.  I made one last hacking attempt with GLFW, but I was unable to
successfully install it, and finally I gave up on it in favor of my
newly working FreeGLUT installation.

If you want to use FreeGLUT, just ask, and I will gladly post how I
got it working.

-- Ron

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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-15 Thread Ronald Guida

SevenThunders wrote:
 OK so check out what really happens with liftM2.  Suppose I have an IO
 containing an involved matrix computation called s.  For simplicity 
we might

 assume that

 s :: IO (Int)  


 and the Int is an index into an array containing a bunch of matrices in C
 land.  Assume that s is determined by a succession of many IO operations
 that have lots of side effects and are fairly computationally intensive.
 Also assume that s is unevaluated.

 Now do an operation like

 q = liftM2 MultMatrix s s

 What happens is that s is 'evaluated' twice when q is evaluated

 e.g.
 do
 qint - q


 That becomes evident when we look at liftM2's definition
 liftM2 f  =  \a b - do { a' - a; b' - b; return (f a' b') }

 the statements
 a' - a   and b' - b will cause s to be evaluated twice.

 Therein lies my problem.

Here's your solution:

 do
-- Compare this to liftM2 and your definition of q
s' - s   -- this evaluates s once and for all
qint - return $ MultMatrix s' s'

-- Ron

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


Re: [Haskell-cafe] Sequencing Operations in a Monad

2007-09-14 Thread Ronald Guida

SevenThunders wrote:

I have a matrix library written in C and interfaced into Haskell
with a lot of additional Haskell support.


[snip]


Unfortunately if I wrap my matrix references in the IO monad, then
at best computations like S = A + B are themselves IO computations
and thus whenever they are 'invoked' the computation ends up getting
performed repeatedly contrary to my intentions.


Here's some thoughts:

First, the IO monad already does sequencing, and it already has the
ability to execute an action once only.

Let's look at an example:


test1 = do
  putStr What is your name? 
  n - getLine
  putStrLn $ Hello,  ++ n ++ !
  return n



getName :: IO String - IO String
getName nameAction = do
  n - nameAction-- execute the action
  return n



getNameLength :: IO String - IO Int
getNameLength nameAction = do
  n - nameAction-- execute the action
  return $ length n



test2 = do
  let nameAction = test1 in do
n - getName nameAction
putStrLn $ Name =  ++ n
len - getNameLength nameAction
putStrLn $ Length =  ++ show len



test3 = do
  n - test1
  putStrLn $ Name =  ++ n
  putStrLn $ Length =  ++ show (length n)



test4 = do
  let nameAction = test1 in do
n - nameAction
n' - getName (return n)
putStrLn $ Name =  ++ n'
len - getNameLength (return n)
putStrLn $ Length =  ++ show len


GHCi test1
What is your name? Ron
Hello, Ron!
Ron

GHCi test2
What is your name? Alice
Hello, Alice!
Name = Alice
What is your name? Bob
Hello, Bob!
Length = 3

GHCi test3
What is your name? Ron
Hello, Ron!
Name = Ron
Length = 3

GHCi test4
What is your name? Ron
Hello, Ron!
Name = Ron
Length = 3

Notice that in test2, I am asked for my name twice.  This behavior is
expected because the functions GetName and getNameLength each
accept an action and execute it to get a name.

In test3, I am only asked for my name once.  I only want to execute
the action once, so I have to code it that way.

Before I explain test4, let's look at your example code:


let S = A += B in
  do
  (r,c) -  size S
  k  - matindex S


If S is being executed twice, then clearly S is an action.  Perhaps
the type of S is IO MatrixIO ?  If that's true, then presumably the
functions size and matindex have signatures:

size :: IO MatrixIO - IO (Int, Int)
matindex :: IO MatrixIO - IO Int

Each function takes an IO action as its first argument, executes that
action, and then computes a result.

My two functions getName and getNameLength are similar to size
and matindex: each function takes an IO action, executes the action,
and computes a result.

Now, look at test4.  That's how I can work around the behaviour of
getName and getNameLength while ensuring that I am only asked for
my name one time.  This works because return creates an IO action
that does nothing and simply returns its argument.

I could translate your example to the following:


let S = A += B in
  do
  s - S
  (r,c) -  size (return s)
  k  - matindex (return s)


This should only perform action S one time.

In fact, functions like getNameLength are poorly designed functions
because they fail on Separation of concerns.  The getNameLength
function is doing two different things: (1) it executes an IO action
to get a name, and then (2) it computes and returns the name's length.
In test4, I am bypassing the execution of an IO action by passing the
non-action return n to the getNameLength function.

A simple design rule would be: A function should not take an IO action
as an input if that action is to executed exactly once and only once.

Let's move on to chained binary operations.


If you arrange the types to try to do all the operations inside the
IO monad you can't chain together more than 1 binary operation.


Using your example, suppose I want to compute S := Q * (A + B), but I
don't have a function that computes A + B.  Instead, what I have is a
function that computes A += B by modifying A in place.

If I want to compute S, and I don't care about preserving A, then I
would perform the following steps:
A += B;  S := Q * A

If I do want to preserve A, then I need to copy it first.
A' := copy A; A' += B; S := Q * A'

No matter what, I cannot escape the need to explicitly sequence the
operations.

In C++, I could play some very sophisticated games with templates and
operator overloading to coax the C++ compiler to accept an expression
with chained operations like S = Q * (A + B) and do the right
thing.  In Haskell, I'm pretty sure the corresponding techniques
involve using arrows.

If you don't want that level of sophistication, then you are best off
coding what you mean, as in:

do
-- compute S := Q * (A + B)
C - A + B
S - Q * C

Now, there's just one more thing [emphasis added].


Moreover I manage my matrices on a stack in C, since it makes it
easy to handle memory allocation and deallocation.  *The stack*
*configuration tends to be highly fluid so there are always side*
*effects going on.*  Right now my 

Re: [Haskell-cafe] Basic FFI with GHC

2007-09-12 Thread Ronald Guida

Ronald Guida wrote:
 How do I create C-libraries that I can load into GHCi?  I am trying to
 do some basic FFI, and it's not working.

So, after more searching on the internet and some RTFM, I think I
found my answer, and it seems to work, but I don't know if it's the
right answer to generalize from.

1. I can leave test_foo.lhs and foo.cpp as-is.

2. I need to change foo.h to the following:

--
// foo.h

#if BUILD_DLL
#define DECLSPEC __declspec(dllexport)
#else
#define DECLSPEC __declspec(dllimport)
#endif

extern C
{
 DECLSPEC __stdcall int foo(int x);
}
--

3. I need to create a DEF file and list the functions to be exported
  in a DLL.

--
 foo.def
--
LIBRARY foo
DESCRIPTION Foo Library
EXPORTS
  foo
--

Note: The library name on the first line must match the dll name.
  LIBRARY foo corresponds to foo.dll

4. The build process is as follows.

(1) gcc -DBUILD_DLL -c foo.cpp

(2) gcc -shared -o foo.dll foo.o foo.def \
   -Wl,--enable-stdcall-fixup,--out-implib,libfoo.a

5. At this point, I'll have foo.dll and libfoo.a.  I can load my
  foo library, as a DLL, into GHCi with the command:
$ ghci -lfoo
  In reality, I would use:
$ ghci test_foo.lhs -lfoo

6. Once I'm satisfied and ready to compile:

   ghc --make test_foo.lhs -L. -lfoo

Notes:
(1) -L. directs GHC to look in the current directory for
libraries.  GHCi seems to look there by default.

(2) The resulting test_foo.exe will dynamicly load foo.dll.

7. If I want a staticly linked executable instead:

   ar rcs libfoo_static.a foo.o
   ghc --make test_foo.lhs -L. -lfoo_static

8. Finally, I can put the build steps into a makefile.

--
# Makefile for foo

test_foo.exe : test_foo.lhs libfoo.a foo.dll
   ghc --make test_foo.lhs -L. -lfoo

test_foo_static.exe : test_foo.lhs libfoo_static.a
   ghc --make test_foo.lhs -L. -lfoo_static -o test_foo_static.exe

libfoo.a : foo.dll

foo.dll : foo.o foo.def
   gcc -shared -o foo.dll foo.o foo.def \
   -Wl,--enable-stdcall-fixup,--out-implib,libfoo.a

libfoo_static.a : foo.o
   ar rcs libfoo_static.a foo.o

foo.o : foo.cpp foo.h
   gcc -DBUILD_DLL -c foo.cpp

.PHONY: clean
clean:
   rm -f *.[oa]
   rm -f *.dll
   rm -f *.hi
   rm -f *.exe
--

-- Ron

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


[Haskell-cafe] Basic FFI with GHC

2007-09-11 Thread Ronald Guida

How do I create C-libraries that I can load into GHCi?  I am trying to
do some basic FFI, and it's not working.

Here's the background.  I created three files, foo.h, foo.cpp, and
test_foo.lhs. (source code below)

Note: I am using MinGW/Msys under Windows XP.

If I compile foo.cpp and then try to load test_foo into GHCi, I get an
error.  OTOH, if I compile test_foo with GHC, it works.  I just don't
understand why it works one way and not the other.

What am I doing wrong?

-- Ron

--
Shell commands
--

$ gcc -c foo.cpp

$ ghci test_foo.lhs foo.o
  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading object (static) foo.o ... done
final link ... done
[1 of 1] Compiling Main ( test_foo.lhs, interpreted )

During interactive linking, GHCi couldn't find the following symbol:
 foo
This may be due to you not asking GHCi to load extra object files,
[snip]

$ ghc --make test_foo.lhs foo.o
[1 of 1] Compiling Main ( test_foo.lhs, test_foo.o )
Linking test_foo.exe ...

$ test_foo.exe
Entering main
y = 22
Exiting main

$ ar rcs libfoo.a foo.o

$ ghc --make test_foo.lhs -lfoo

$ test_foo.exe
Entering main
y = 22
Exiting main

$ ghci test_foo.lhs -lfoo
  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading object (dynamic) foo ... failed.
Dynamic linker error message was:
  addDLL: unknown error
Whilst trying to load:  (dynamic) foo
Directories to search are:
: user specified .o/.so/.DLL could not be loaded.

--
Source code
--

// foo.h

extern C
{
 __stdcall int foo(int x);
}

--

// foo.cpp
#include foo.h

__stdcall int foo(int x)
{
 return 3 * x + 1;
}

--

test_foo.lhs

 {-# OPTIONS_GHC -fglasgow-exts #-}
 module Main
 where
 import Foreign
 import Foreign.C

 foreign import stdcall unsafe foo
   c_Foo :: Word32 - IO Word32

 main = do
   putStrLn Entering main
   let x = 7::Word32
   y - c_Foo(x)
   putStrLn $ y =  ++ show y
   putStrLn Exiting main


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


Re: [Haskell-cafe] Can somebody give any advice for beginners?

2007-09-11 Thread Ronald Guida

Dan Piponi wrote:
 On 9/11/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 you can fall down a monad and not be able to escape...

 It's not so bad. It's in the nature of monads that after you've fallen
 in once, you can never get trapped any deeper.

But you can climb higher...
(Note: Best viewed in mono-space!)


Programmer's
 Nirvana plane
 ---
   Categoric plane
 ---
  Co-Monadic plane
(Co- everything)
 -
  Applicative plane
--
  Pointless-pointfree plane
--
  Monadic plane  (don't get trapped)
------
  Functional plane  (Haskell et al!)
------
  Imperative plane  ASM, C#, Java :)
------
  Physical plane  (e.g. Silicon)


-- Ron

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


Re: [Haskell-cafe] Installation of GLUT package

2007-09-09 Thread Ronald Guida

Paul L wrote:
 But again, why stuck with GLUT? Now there is at least one alternative,
 GLFW (http://glfw.sourceforge.net) a cross-platform framework for
 OpenGL applications, for which I recently wrote a Haskell interface,
 downloadable at http://www.haskell.org/soe/software1.htm. It's
 certainly experimental though. The GLFW C library itself is well
 documented, but the Haskell module still isn't. The only example so
 far is the soe.hs in the SOE package.

Good news:

I abandoned GLUT and looked at GLFW.  I had similar problems getting
GLFW to work with GHC and GHCi.  After a bunch of hacking, I got GLFW
to work for me.

I have to invoke GHCi with the command line [1] and I have to invoke
the compiler like [2], but hey, it works :)

[1] ghci myfile.hs glfw_hack.o -lopengl32 -lglu32
[2] ghc --make myfile.hs glfw_hack.o -lopengl32 -lglu32

-- Ron


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


Re: [Haskell-cafe] Serial Communications in Haskell

2007-09-08 Thread Ronald Guida

On 8/28/07, Ronald Guida wrote:
 I'm on a Windows box and I'm looking for a way to talk to a serial
 port (for example, RS-232) from Haskell.  I couldn't find a library to
 do this, so I am wondering how to create one.

I figured out FFI and marshaling, and I got my serial port to work in
Haskell.  See http://ronguida.home.mindspring.com/ for a simple
demonstration.  To test this program, I connected my COM1 and COM2
ports with a null-modem cable and I used Hyperterminal to talk to
COM2.

The demo only does a few things: open a serial port, configure it,
write to it, and read from it.

I have some questions regarding this demonstration:

1. In the DCB and COMMTIMEOUTS datatypes and their marshaling code,
  is it better to convert Win32 datatypes to Haskell equivalents
  (e.g. DWORD to Int), like I did with DCB, or is it better to leave
  things in machine types like I did with COMMTIMEOUTS (e.g. DWORD to
  Word32) ?

2. Can anyone tell me whether I am making proper use of
  unsafeInterleaveIO in my implementation of getContentsSerialPort?

I am interested in creating a library for serial ports under Win32,
and I'm wondering, how should I proceed?

-- Ron

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


Re: [Haskell-cafe] Installation of GLUT package

2007-09-08 Thread Ronald Guida

Update:

I downloaded MinGW and MSYS and tried to install the GLUT library.  I
just can't get the thing to work, and I feel like I'm sitting in my
own little section of Hell.

I have tried everything I could think of so far, and it still doesn't work.

Today I tried to sanitize my machine and start over.  Here is my
sequence of steps.  Can anyone tell me what I'm doing wrong?

-- Ron

1. Try to sanitize the machine.
 * Uninstall GHC, then delete C:\ghc and C:\Program Files\Haskell
 * Uninstall MSYS-DTK, MSYS, MinGW, then delete C:\MinGW and C:\MSYS
 * Verify that there is no glut*.dll in C:\Windows\System[32]
 * Delete C:\freeglut and C:\GLUT

2. Reboot.

3. Obtain the following files:

 Note: If I already downloaded a file, I saved it to avoid
 downloading again.

[1] GHC windows executable
   http://haskell.org/ghc/dist/6.6.1/ghc-6.6.1-i386-windows.exe

[2] FreeGlut
   
http://superb-west.dl.sourceforge.net/sourceforge/freeglut/freeglut-2.4.0.tar.gz


[3] Haskell GLUT library
   http://hackage.haskell.org/packages/archive/GLUT/2.0/GLUT-2.0.tar.gz

[4] Automated MinGW installer
   
http://downloads.sourceforge.net/mingw/MinGW-5.1.3.exe?modtime=1168811236big_mirror=1


[5] MSYS: Minimal System installer
   
http://downloads.sourceforge.net/mingw/MSYS-1.0.10.exe?modtime=107947big_mirror=1


[6] MSYS: Supplementary Tools installer
   
http://downloads.sourceforge.net/mingw/msysDTK-1.0.1.exe?modtime=1041430674big_mirror=1


[7] The RotatingCubes example, modified by adding an actionOnWindowClose
   in order to verify that FreeGlut is actually being used.
   http://hpaste.org/2632

3. Install GHC by running [1].

4. Open a command window (Start-Run, type cmd, click OK)

5. See what packages came with GHC.

C:\Documents and Settings\Ron ghc-pkg list
C:/ghc/ghc-6.6.1\package.conf:
   Cabal-1.1.6.2, GLUT-2.1.1, HUnit-1.1.1, OpenGL-2.2.1,
   QuickCheck-1.0.1, Win32-2.1.1, base-2.1.1, cgi-3001.1.1, fgl-5.4.1,
   filepath-1.0, (ghc-6.6.1), haskell-src-1.0.1, haskell98-1.0,
   html-1.0.1, mtl-1.0.1, network-2.0.1, parsec-2.0, regex-base-0.72,
   regex-compat-0.71, regex-posix-0.71, rts-1.0, stm-2.0,
   template-haskell-2.1, time-1.1.1, xhtml-3000.0.2

** Puzzle: Why does GHC have GLUT-2.2.1 if the latest verion of the
  GLUT library [3] is GLUT-2.0?

6. Try to run the modified RotatingCubes example [7], it should fail
  because I have neither GLUT not FreeGlut installed.

C:\Documents and Settings\Ron cd C:\RotatingCube

C:\RotatingCubeghci RotatingCube.lhs
  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
[1 of 1] Compiling Main ( RotatingCube.lhs, interpreted )
Ok, modules loaded: Main.
*Main :main
Loading package haskell98 ... linking ... done.
Loading package OpenGL-2.2.1 ... linking ... done.
Loading package GLUT-2.1.1 ... can't load .so/.DLL for: glut32 (addDLL: 
unknown

error)
*Main :q
Leaving GHCi.

7. Unzip the freeglut package [2] into C:\freeglut and then open the
  C:\freeglut\freeglut-2.4.0\freeglut.dsw file with Microsoft Visual
  Studio 2003.  Select Yes to all when asked to convert to 2003
  format.

8. In VS 2003 main menu: select Build - Batch Build, then click
  Select All, then click Build.

 VS 2003: Build: 4 succeeded, 0 failed, 0 skipped

9. Close VS 2003.

10. Copy and rename
   from: C:\freeglut\freeglut-2.4.0\Release\freeglut.dll
   to:   C:\WINDOWS\SYSTEM32\glut32.dll

11. Try to run the modified RotatingCubes example [7] again.

C:\RotatingCubeghci RotatingCube.lhs
  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
[1 of 1] Compiling Main ( RotatingCube.lhs, interpreted )
Ok, modules loaded: Main.
*Main :main
Loading package haskell98 ... linking ... done.
Loading package OpenGL-2.2.1 ... linking ... done.
Loading package GLUT-2.1.1 ... linking ... done.
*** Exception: user error (unknown GLUT call glutSetOption, check for 
freeglut)

*Main :q
Leaving GHCi.

12. Copy C:\freeglut\freeglut-2.4.0\include\GL\*.h
   to   C:\ghc\ghc-6.6.1\include\mingw\GL\
   Note: glut.h will be overwritten

13. Try to run the modified RotatingCubes example [7] again.
   (It fails, exactly as in step 11.)

14. Run the MinGW installer [4].  Select Full Install, leave
   everything else at its default value.

15. Run the MSYS installer [5].  Leave everything at default values.
 * Post Install Q  A:
 Do you wish to continue with the post install? [yn ] y

 Do you have MinGW installed? [yn ] y

 Please answer the following in the form of c:/foo/bar.
 Where is your MinGW installation? c:/MinGW

16. Run the MSYS Supplementary Tools installer [6].  

Re: [Haskell-cafe] Installation of GLUT package

2007-09-08 Thread Ronald Guida

Paul L wrote:
 I believe it's caused by the different versions of GLUT you have.

 On 9/8/07, Ronald Guida [EMAIL PROTECTED] wrote:
 [...]
 Loading package OpenGL-2.2.1 ... linking ... done.
 Loading package GLUT-2.1.1 ... linking ... done.

 The above message was after you have installed GLUT-2.0, but GHC was
 still loading GLUT-2.1.1. The later errors were caused by your forced
 copy of 2.0 lib over the default 2.1.1.

I noticed this myself.  The problem is, I don't know where to get
GLUT-2.1.1.  If I look on Hackage [1] and select GLUT from the
Graphics category, I am directed to GLUT-2.0.
[1] http://hackage.haskell.org/packages/archive/pkg-list.html

 I suggest you get the cabal version of latest GLUT, which is 2.1.1,
 and build it from source. I did the same on Linux some time ago, and I
 was able to use freeGLUT and openGLUT as a result.

Clearly, I'm missing something here.  Where do I have to go to get the
latest version of GLUT?

Also, after I built freeglut with VS-2003, I copied the include files,
the lib file, and the dll to the correct places (relative to VS-2003)
and I could successfully compile the examples that came with freeglut.
MinGW/MSYS doesn't know about VS-2003 include directories, so where am
I supposed to put the freeglut include and lib files relative to
MinGW/MSYS?

Thank you
-- Ron

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


[Haskell-cafe] Serial Communications in Haskell

2007-08-28 Thread Ronald Guida

I'm on a Windows box and I'm looking for a way to talk to a serial
port (for example, RS-232) from Haskell.  I couldn't find a library to
do this, so I am wondering how to create one.

I have a fairly thorough understanding of how to open and use a serial
port with the Windows API.  In particular, to open a serial port, I
have to use CreateFile, which is the same API call that opens files.
In fact, if I call openFile from GHC, and pass COM1: as the
filename, then I can get a writable serial port.

 module Serial
 where
 import System.IO

 main = do
   h - openFile COM1: ReadWriteMode
   hPutStrLn h Hello World

I can't read from the port (I always get an immediate EOF), and I have
no way of configuring things like the baud rate or the parity
settings.  Nevertheless, this demonstrates that openFile can at least
open the serial port.

What I would like to do is create some functions that would allow me
to open and configure a serial port, and get a Handle back so that I
can use the existing IO functions like hGetChar and hPutChar.  I am
assuming that hGetChar eventually calls win32::ReadFile and hPutChar
eventually calls win32::WriteFile.  These same two API calls would
work for serial ports.

In Windows, there are 23 API functions that apply specifically to
serial ports.  Out of these 23 functions, only a few of them are
actually necessary if I just want to send and receive data.

Of course, I don't know how to call Windows API functions from Haskell,
and I have no idea how to hook things to the IO library so that I can
use a Handle for a serial port.  I'm looking for some advice on how to
proceed.

-- Ron

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


Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-23 Thread Ronald Guida

I'm trying to understand lazy evaluation as well.  I created an
example for myself and I'm wondering if I've got it right.

 let adder n = \x - n + x in (map (adder 12) [1,2,3]) !! 1

So the first thing I did is draw a graph to represent my expression.

 (map (adder 12) [1,2,3]) !! 1 =
   |
  (!!)
 /\
/  1
   map
  /   \
 / \
  adder(:)--(:)--(:)
|   ||| \
   12   123  []

In order to proceed, I need definitions for adder, map and (!!).

 adder n = \x - n + x

 map f [] = []
 map f (x:xs) = (f x) : xs

 (x:xs) !! 0 = x
 (x:xs) !! n = xs !! (n-1)

Here is how I think the evaluation would proceed:

0 = (map (adder 12) [1,2,3]) !! 1

The top node is (!!).  In order to evaluate (!!), I need to
expand the left hand side to get at least the first node of a
list.  I'll expand map.

1 = ( (adder 12 1) : (map (adder 12) [2,3]) ) !! 1

I evaluated map once to get a list with an expression for the
head and an expression for the tail.
   head: adder 12 1
   tail: map (adder 12) [2,3]

I proceed to evaluate (!!) for one step; this time n /= 0 so I
extract the tail of the list and recursively call (!!).

2 = ( (map (adder 12) [2,3]) ) !! 0

The top node is (!!) again.  I need to expand map again.

3 = ( (adder 12 2) : (map (adder 12) [3]) ) !! 0

I evaluate (!!) and this time n == 0 so I match the base case for
(!!) and take the head of the list.

4 = adder 12 2
 = (adder 12) 2

In order to proceed, I need to expand (adder 12).  The adder
function take one argument, 12, and produces a closure.  I'll
express it as a let expressions.

Note: It is at this point (steps 4 to 7) that I'm confused about
what's supposed to happen with closures and let expressions.

5 = (let n = 12 in \x - n + x) 2

I'll substitute 2 into the let statement.

6 = (let n = 12 in n + 2)

I'll substitute 12 for n.

7 = 12 + 2
8 = 14

Can anyone tell me if I've got this right?

-- Ron

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


Re: [Haskell-cafe] Explaining monads

2007-08-13 Thread Ronald Guida

Ronald Guida wrote:
 Given the question What is a Monad, I would have to say A Monad is
 a device for sequencing side-effects.

peterv [EMAIL PROTECTED] wrote:
 Side-effects is a piece of linguistic cruft played fast-and-loose
 by too many people in this game. Sequencing suffers the same
 disease.

Gregory Propf wrote:
 I made this mistake myself at first too.  It seems that the Monad =
 side effect machine error is common to Haskell newbies.  Probably
 to do with the fact that the first thing every programmer wants to
 do is write a hello world program and for that you need the IO Monad
 which requires some explanation of how a Monad can allow for side
 effects (at least the IO Monad). - Greg

Eariler in this thread, I had a conversation with several people
regarding monads and arrows.  My goal was to try to come up with a
brief explanation.  I realized that sequencing side-effects is a
simplistic and incorrect view, so now I'm thinking in terms of DSELs.

I have heard that writing a monad tutorial is something people do when
they finally understand monads.  I interpret this observation to mean
that either (1) monads (and arrows) are just difficult things, or (2)
most of the existing explanations and tutorials are somehow inadequate
or incomplete.

My present goal is to understand monads well enough to be able to
explain them to others.  I wonder if it's possible to create a
tutorial that explains monads well enough so that they just make
sense or click for people.

Here is the brief explanation I came up with:
 Arrows and monads are abstract data types used to construct Domain
 Specific Embedded Languages (DSELs) within Haskel.  A simple arrow
 provides a closed DSEL.  A monad is a special type of arrow that
 creates an open DSEL by allowing users to embed arbitrary Haskel
 within it.

Is this an accurate explanation?  I hate to feed a fire, but is
Domain Specific Embedded Language a well-defined phrase, or is it
just another example of linguistic cruft? If DSEL is cruft, then is
there a better way to briefly explain monads and arrows?

Also, is this a /useful/ explanation, or have I simply hidden the
complexity by invoking the concepts of ADTs and DSELs?

-- Ron

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


Re: [Haskell-cafe] Explaining monads

2007-08-12 Thread Ronald Guida

Stefan O'Rear wrote:
 On Sat, Aug 11, 2007 at 03:00:04PM -0400, Ronald Guida wrote:
 The question remains: What is special about Monad or ArrowApply,
 compared to Arrow? or What is more general about Arrow, compared
 to Monad or ArrowApply?

 If all you have is an Arrow, then you must make up your mind what
 you're going to do ahead of time.

 ArrowChoice gives you the ability to make basic yes or no
 decisions at run time.

 ArrowApply gives you arbitrary computed jumps.

OK, so I thought this through.

To summarize the classes of arrows:

1. Arrow is a device for sequencing side-effects in a fixed order.

 If all you have is an Arrow, then you must make up your mind what
 you're going to do ahead of time.

2. ArrowChoice is a device for sequencing side-effects in a fixed
  order with options.  Some effects can be selected at run-time, but
  (1) the available choices are fixed at compile-time and (2) options
  have to be selected before running the arrow computation.

 ArrowChoice gives you the ability to make basic yes or no
 decisions at run time.
BUT, you have to make these decisions before you run the arrow
computation.

3. ArrowApply is a device for sequencing side-effects, such that
  functions can dynamically choose side-effects at run-time based on
  intermediate results of arrow computations.

 ArrowApply gives you arbitrary computed jumps.

---

We know that ArrowApply is equivalent to Monad.

 Imagine trying to write an interpreter for a toy language with I/O,
 and IO is a plain Arrow and not a Monad.  You can read input and
 parse it, but you can't actually do IO because the IO you need to
 do, depends on the input you read - precisely what Arrow forbids!

Here's a toy language, described by a regular expression:
 0(10)*110

I want to read characters, one at a time, and eventually decide to
Accept or Reject a string.

Let me try to understand my options.

* With a simple Arrow, I can create a fixed sequence of read
  operations, and I can't act on the results (i.e. by choosing
  whether or not to keep reading) at run-time.

* With ArrowChoice, I can create a set of alternative paths for
  read operations, and I can choose a path at run-time, but I have
  to choose a fixed path /before/ I get to see any results.

* With ArrowApply, I can read one character and act on that
  character to choose what actions to perform next.  I can read
  characters until I can render an Accept or Reject decision.

Clearly, I need ArrowApply (or Monad) to get the job done.

In conclusion:

What is special about Monad or ArrowApply, compared to Arrow?
Arrow lets me sequence side-effects in a fixed order.  Monad lets me
dynamically choose side effects at run-time based on intermediate
results of previous side-effects.

-- Ron

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


Re: [Haskell-cafe] Explaining monads

2007-08-12 Thread Ronald Guida

Tillmann Rendel wrote:
 Ronald Guida wrote:
 Here's a toy language, described by a regular expression:
  0(10)*110

 I want to read characters, one at a time, and eventually decide to
 Accept or Reject a string.

 Let me try to understand my options.

 * With a simple Arrow, I can create a fixed sequence of read
   operations, and I can't act on the results (i.e. by choosing
   whether or not to keep reading) at run-time.

 Nothing stops your Arrow-based RegExp-library from defining suitable
 combinators to implement choices in RegExp's without using
 ArrowChoice or ArrowApply. But if your Arrow-type is abstract, the
 users of your library can only use the combinators you provided, so
 you can safely assume they do only RegExp parsing, and optimize your
 Arrows in the runRegExp-function for the special case of
 RegExp-matching.

So it seems I was thinking too narrowly of arrows...

If I think of an arrow as defining a Domain Specific Embedded Language
(DSEL), then with a plain arrow, users can't embed Haskel inside the
DSEL.

 But if you decide to expose ArrowApply-functionality to the users of
 your RegExp-library, they are able to define arbitrary string
 matching on top of your RegExp library, so you can't do any
 optimizations because you never know what your users decided to do.

If I think of a monad (ArrowApply) as defining a Domain Specific
Embedded Language (DSEL), then users can embed anything they want
within the DSEL.

 From a software engineering point of view, the idea of
 Arrow-and-only-Arrow is to encode the whole computation in the
 internal structure of the arrow, independent of the interpreting
 language Haskell. This internal structure could be as expressible as
 Haskell. In contrast, ArrowApply and Monad use regular Haskell
 expressions for everything Haskell can do (like if-then-else,
 recursion, ...) and only encode special operations into the internal
 structure (like access to state, nondeterminism, ...).

 This distinction is reflected in the treatment of variables in
 arrow-based vs. monadic code. monadic code can use normal Haskell
 variables, arrow-based code has to keep the variables inside the
 arrow in some structure.

So if I want to explain arrows and monads as concisely as possible:

Arrows and monads are abstract data types used to construct Domain
Specific Embedded Languages (DSELs) within Haskel.  A simple arrow
provides a closed DSEL.  A monad is a special type of arrow that
creates an open DSEL by allowing users to embed arbitrary Haskel
within it.

-- Ron

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


Re: [Haskell-cafe] Explaining monads

2007-08-11 Thread Ronald Guida

David Menendez wrote:
 Be sure to read sigpfe's You could have invented monads! and the
 Wadler paper.

 
http://sigfpe.blogspot.com/2006/08/you-could-have-invented-monads-and.html

 http://homepages.inf.ed.ac.uk/wadler/papers/marktoberdorf/baastad.pdf

 Most tutorials try to explain what a monad *is*, but these focus
 more on why they're a useful way to organize code. In my experience,
 being able to use a monad is more important than understanding the
 theory.

Hey, now I know what a monad is!  What I missed in all those tutorials
is that a monad is an *abstract base class*.  With this realization,
which I had after reading the sigfpe tutorial, everything makes sense
for me.

To review a basic OOP example, I can't illustrate what a Vehicle *is*
in general terms.  I can illustrate a Bicycle, a Car, a Boat, a Plane,
a Submarine, a Hovercraft, a LARC-V, and many other examples of
instances of /subclasses/ of Vehicle, but I can't find anything that's
/just/ a Vehicle.  In OOP, Vehicle is an abstract base class.

The same thing applies for a Monad.  I can look at lots and lots of
instances, like Maybe, Either, List, State, Reader, Writer, IO, and
lots of others, but I can't produce an example that's /just/ a Monad.
Monad is an abstract base class, too.

Now if I had to explain What is a Vehicle, I would have to say A
Vehicle is a device that provides transportation.  When asked for
more details, I can specify the interface and provide examples of
instances.

 Interface for Vehicle: load, unload, goto
 Instances of Vehicle: Bicycle, Car, Plane, Boat, etc.

Given the question What is a Monad, I would have to say A Monad is
a device for sequencing side-effects.  When asked for more details, I
can specify the interface and provide examples of instances.

 Interface for Monad: return, bind
 Instances of Monad: Maybe, Either, List, State, etc.

What is particularly stupefying for me is that I missed the fact that
Monad is obviously an abstract base class: Monad is declared as a
type-class!

Now the hard part.  As far I currently know - and I could be wrong:

(1) Monad, Comonad and Arrow are all abstract base classes.

(2) Monad, Comonad and Arrow are all devices for sequencing
   side-effects.

(3) Monad and Comonad are both specializations of Arrow.

Given the question What is an Arrow, I would have to say An Arrow
is a device for sequencing side-effects.  When asked for more
details, I can specify the interface and provide examples of
instances.

This leads directly to the question What makes a Monad special,
compared to an Arrow?  Right now, the clues I have are:

(1) Every monad is equivalent to a Kleisli arrow.

(2) The ArrowApply class is equivalent to the Monad class.

I can restate the question: What is special about ArrowApply,
compared to Arrow?  I see that an arrow accepts some inputs, performs
a computation, possibly with side-effects, and generates some outputs.

In particular, suppose I create instances of Arrow that accept two
inputs (as a pair) and produce one output.  Some of these instances
(i.e. ArrowApply) are special: I can provide, as the two inputs, (1)
an Arrow that accepts one input and one output, and (2) an input
suitable for that Arrow.  The output that I get is the result of
feeding input (2) to input (1) to get a result, *and* somehow
combining the side-effects of both arrows.

The only way an ArrowApply can combine the side effects of two arrows
and still obey the Arrow laws is through an operation that takes an
(arrow nested inside an arrow) and collapses it into a sigle arrow.
That's exactly what join does for monads.  So, ArrowApply is
special, compared to Arrow, because ArrowApply has a join operation,
but Arrow doesn't.  Clear as mud!

The question remains: What is special about Monad or ArrowApply,
compared to Arrow? or What is more general about Arrow, compared to
Monad or ArrowApply?

-- Ron

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


Re: [Haskell-cafe] Explaining monads

2007-08-10 Thread Ronald Guida

Brian Brunswick wrote:
   g  f   ???  g ??? f

 application  a a-b  flip ($) b
 monad bind   m a   a-m b=  m b
 comonad cobind   w a   w a-b=  w b
 arrowarr a b   arr b c arr a c

Kim-Ee Yeoh wrote:
 Fmap's missing: m a, a-b, flip fmap, m b. You might want to throw in
 Applicative there too: m a, m (a-b), flip (*), m b.

Here's my interpretation of the table:

--
Structure   | Subject  |  Action|  Verb  |  Result
+--+++--
function|  a   |  a-b  |  flip ($)  |  b
Functor |  f a |  a-b  |  $   |  f b
Applicative |  f a |  f (a-b)  |  flip *  |  f b
Monad   |  m a |  a-m b|  =   |  m b
Comonad |  w a |  w a-b|  =   |  w b
Arrow   |  a b c   |  a c d | |  a b d
--

Kim-Ee Yeoh wrote:
 ... I think you'll find that each of those structures have their
 privileged place in your code.

Agreed.  I'm still a beginner; I'm not sure how to choose one
structure over another, at least not yet.  But that's because ...

 Monads are undoubtedly more pervasive, and that could be because there
 aren't as many arrow and comonad tutorials, atomic ones or otherwise.

Moreover, Comonad isn't even in the standard libraries (Hoogle returns
no results for it).

When I searched for tutorials on monads, I found lots of them.  In
fact, I have heard that writing (yet another) monad tutorial is part
of standard Haskell initiation.

In my case, I have started to formulate my own idea for what a monad
tutorial should be; I might attempt to write one, too.

I read several monad tutorials, but I could not understand them at
first.  Monad transformers are even worse.  I had to sit, *think*,
draw diagrams, *think* some more, review several advanced tutorials,
and *think* even more.  I also looked up comonads, arrows, and
category theory.  Finally, monads (and monad transformers) started to
make sense for me.

I still don't understand monads just yet; but that's because my
self-test for understanding something is whether I feel I could
explain it to someone else and have it make sense.

I suppose that in order to understand monads, I need to actually *use*
some monads, and see them in action on something real (like an actual
algorithm) that I can relate to.  Learning feels like climbing a
mountain; much time and hard work is spent on the ascent, but new
understanding is achieved in the process.  Once I reach the top of the
mountain, the question is how to make the mountain easier to climb for
the next person.

My thinking is that the ultimate goal is to /invert/ the mountain,
such that the people can /ride/ the mountain (which still requires
some work) and gain new understanding in the process.  What I obtain
on the way up the mountain, future people would obtain, far more
efficiently, on the way /down/ the (inverted) mountain.

What I would like to see in a monad tutorial are some good real-use
examples that demonstrate /just/ monads.  I found it extremely helpful
to see an example of monads being used to compute probabilities and
drug test false-alarm rates.  This application seemed to used /just/
monads, without a lot of extra programming complexity on top, and it
provided a real example.  This is the sort of thing, combined with
the background of what is a monad, that I think would make a really
good tutorial.

The monadic lovers story, in my opinion, provides an example that's
too contrived and simplistic.

On the other extreme, I found an example of arrows being used in a
digital circuit simulator.  As a tutorial on arrows, I would find this
too complex because there is too much stuff built up on top of the
arrows.  The concept of an arrow is lost in the complexity of
special classes like the ArrowCircuit class that was actually used
to simulate a circuit.  (Note: The circuit used in the example was
trivial, moreover my background is electrical engineering with a focus
on digital circuits.)

I found an example of a comonad being used to simulate a cellular
automaton; I found this example helpful, although it might be a little
too complex.

I think that what would make a truly great tutorial would be a
tutorial (or a series of tutorials) that starts with a real area of
exploration and proceeds to incrementally develop programs.  Each
increment would incorporate a new bite from the area of exploration,
which would cause an increase in complexity.  As the programs get
complicated, the monad (or comonad, or arrow) is introduced by
factoring the appropriate pattern out the code and then simplifying.

The tutorial might (1) state the monad laws and say this is what
defines a monad, (2) say something like let's look for this pattern
in the code and find the 

[Haskell-cafe] Monad for Set?

2007-08-06 Thread Ronald Guida

Hi,

I'm pondering, is it possible to define a Set monad analogous to the 
List monad?


My thinking is as follows:
*  fmap f x would apply f to each element in a set x
*  return x would create a singleton set {x}
*  join x, where x is a set of sets: x = {x1, x2, ... xn},
 would form their union (x1 U x2 U ... U xn)

The advantage of Set over List is that duplicate elements would be
removed automatically.

There is just one /slight/ problem: In order to implement set
operations, I need to be able to test elements for equality; that is,
I need to impose the restriction (Eq a) = Set a.  This is a problem
because return really needs to work for any type; I have no way to
guarantee (Eq a).

In my search for answers, I came across restricted monads.  I don't
like the idea of restricting the types I can return, and here's why.
Suppose I had a way to impose (Eq a).  Then I start to wonder:

* What happens when I use a monad transformer like StateT s Set a
  or ContT r Set a, but the types s and r are not equatable?

* What happens when I want to define the monad transformer SetT
  because I need to put the IO monad inside it?

In both cases, I feel I'm screwed if I really have to impose the
constraint (Eq a) = Set a.

This leads me think of a different solution: What if I could define a
Set monad that's smart enough to know, for any type a, whether or
not (Eq a) holds, and degenerate to a blind list if the elements can't
be equated.  Ultimately, what I would need is a way to overload join
(or bind) with two different implementations, one for types that
satisfy (Eq a), and another implementation for all other types.

In my searching so far, I found ways to overload a function when all
overloads share a common typeclass, and I have found ways to overload
a function for disjoint types, provided that every type to be overload
is an instance of some typeclass.  All of the methods I have found so
far are deficient in the sense that there is no way to provide a
default implementation for types that don't fit into any typeclass.  I
have not been able to find a way to overload a function such that one
implementation works for a special class of types, and another
implementation works for *all* other types.

Question: Is it possible to define join :: [[a]] - [a], with
(1) a special implementation that requires (Eq a) and removes duplicate
   elements, and
(2) a general implementation to fall back on for *any* type that fails
   the constraint, and
(3) a way to make f fully generic, such that the correct
   implementation is chosen automatically from the type variable a?

If I had a way to do this, then I could define a Set monad that
performs set operations when it can (i.e. when the elements are
equatable), but which automatically degenerates to a simple List when
it has to (i.e. when there's no equality test).  I almost suspect that
I might need to use Haskell Templates (I currently know nothing about
Haskell Templates).

Even better, if this problem is solvable, then the next step would be to
overload again to use an efficient implementation when set elements are
comparable (Ord a). 


Any ideas?

-- Ron

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


[Haskell-cafe] Installing FreeGLUT

2007-08-01 Thread Ronald Guida

Hi,

I am trying to use freeglut with GHCi 6.6.1, and I'm stuck.  I 
downloaded freeglut 2.4.0 and compiled it.  I am on a Windows XP 
machine, and I found that freeglut compiled out of the box in MS 
Visual Studio.Net 2003.


My difficulty is that GHCi is finding GLUT 2.2.1 and not freeglut.  How 
do I get GHC and GHCi to recognize and use freeglut instead?


Note: I'm using Windows XP; an upgrade to Linux is not an option.

Thank you
-- Ron

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


[Haskell-cafe] Hints for Euler Problem 11

2007-07-19 Thread Ronald Guida

Hi, again.

I started looking at the Euler problems [1].  I had no trouble with
problems 1 through 10, but I'm stuck on problem 11.  I am aware that
the solutions are available ([2]), but I would rather not look just
yet.

In Problem 11, a 20x20 grid of numbers is given, and the problem is to
find the largest product of four numbers along a straight line in the
grid.  The line can be horizontal, vertical, or diagonal.

I figured out how to handle the horizontal and vertical products, but
I'm stuck on how to approach the problem of extracting the diagonals.

Here is what I have so far; it does the horizontal and vertical cases:

 module Main
 where

 import Data.List

 gridText = 08 02 22 97 38 15 00 40 00 75 04 05 07 78 52 12 50 77 91 
08\n\

 \49 49 99 40 17 81 18 57 60 87 17 40 98 43 69 48 04 56 62 00\n\
 \81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65\n\
 \52 70 95 23 04 60 11 42 69 24 68 56 01 32 56 71 37 02 36 91\n\
 \22 31 16 71 51 67 63 89 41 92 36 54 22 40 40 28 66 33 13 80\n\
 \24 47 32 60 99 03 45 02 44 75 33 53 78 36 84 20 35 17 12 50\n\
 \32 98 81 28 64 23 67 10 26 38 40 67 59 54 70 66 18 38 64 70\n\
 \67 26 20 68 02 62 12 20 95 63 94 39 63 08 40 91 66 49 94 21\n\
 \24 55 58 05 66 73 99 26 97 17 78 78 96 83 14 88 34 89 63 72\n\
 \21 36 23 09 75 00 76 44 20 45 35 14 00 61 33 97 34 31 33 95\n\
 \78 17 53 28 22 75 31 67 15 94 03 80 04 62 16 14 09 53 56 92\n\
 \16 39 05 42 96 35 31 47 55 58 88 24 00 17 54 24 36 29 85 57\n\
 \86 56 00 48 35 71 89 07 05 44 44 37 44 60 21 58 51 54 17 58\n\
 \19 80 81 68 05 94 47 69 28 73 92 13 86 52 17 77 04 89 55 40\n\
 \04 52 08 83 97 35 99 16 07 97 57 32 16 26 26 79 33 27 98 66\n\
 \88 36 68 87 57 62 20 72 03 46 33 67 46 55 12 32 63 93 53 69\n\
 \04 42 16 73 38 25 39 11 24 94 72 18 08 46 29 32 40 62 76 36\n\
 \20 69 36 41 72 30 23 88 34 62 99 69 82 67 59 85 74 04 36 16\n\
 \20 73 35 29 78 31 90 01 74 31 49 71 48 86 81 16 23 57 05 54\n\
 \01 70 54 71 83 51 54 69 16 92 33 48 61 43 52 01 89 19 67 48

 readGrid :: (Read a) = String - [[a]]
 readGrid = (map ((map read) . words)) . lines

 grid :: [[Integer]]
 grid = readGrid gridText

 makeGroups :: Int - [a] - [[a]]
 makeGroups 0 _ = []
 makeGroups n xs = let ys = take n xs in
  if n == length ys
then ys : (makeGroups n $ tail xs)
else []

 maxHorizontal :: (Ord a, Num a) = Int - [[a]] - a
 maxHorizontal length = maximum . map product . concat . map 
(makeGroups length)


 maxVertical :: (Ord a, Num a) = Int - [[a]] - a
 maxVertical length = maxHorizontal length . transpose

 main :: IO()
 main = do
   print $ maxHorizontal 4 grid
   print $ maxVertical 4 grid

To handle the diagonals, my plan is to try to extract each diagonal as
a list of elements and put all the diagonals into a list; then I can
use maxHorizontal.

I came up with this function to try to extract the main diagonal.

 getDiag :: [[a]] - [a]
 getDiag = map (head . head) . iterate (tail . map tail)

The problem is, this function doesn't work unless I have an infinite
grid.

Could anyone provide me with some hints to lead me in the right direction?

Thank you
-- Ron

References:

[1] http://projecteuler.net/index.php?section=view

[2] http://www.haskell.org/haskellwiki/Euler_problems

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


Re: [Haskell-cafe] Lazy Lists and IO - Redux

2007-07-13 Thread Ronald Guida

[Ronald Guida, 07/11/07]
 Suppose I have a function f that reads a lazy list, such that f
 only consumes as much of the list as it needs to.  Laziness allows me
 to apply f to an infinite list without creating an infinite loop.

 Now I want to connect the console to f, such that the list of inputs
 to f comes from the console, one item at a time.


How do I do this?

[Stefan O'Rear]
 Not very nicely.

Apparently, the solution gets ugly.

[Stefan O'Rear]
 Option 1. Ignore purity [using unsafeInterleaveIO]
 Option 2. Ignore lists

[Felipe Almeida Lessa]
 Option 3. Use continuations

I would like to understand *why* it gets ugly, and I think I figured it
out.

[Ronald Guida, 07/11/07]
 To create a specific example, lets suppose I want to read and
 accumulate the contents of a list, and I want to stop when the sum
 reaches or exceeds a specified cutoff.

 I can write this as a function that reads elements from an infinite list:

 [Snipped: Ronald Guida's newb implementation of accumUntilCutoff]

[Stefan O'Rear, 07/11/07, Improved implementation]

 accumUntilCutoff :: (Ord a, Num a) = a - [a] - (a, [a])
 accumUntilCutoff cutoff xs =
 findAcceptLast ((= cutoff) . fst) (zip (scanl (+) 0 xs) (inits xs))

 findAcceptLast :: (a - Bool) - [a] - a
 findAcceptLast pred lst = fromMaybe (last lst) (find pred lst)


First, if I start with an arbitrary pure function, then I can build a
dependency graph to determine what to evaluate.  Since pure functions
are referentially transparent, I am free to evaluate the nodes of my
dependency graph in any order, provided that I respect the
dependencies.

On the one hand, suppose I want to read a list with IO.  In order to
use IO, or any monad for that matter, I have to pass a baton[1] from
one operation to the next.  If a create a complicated function that
involves a monad, then every time I use the bind operator, I am
adding an edge to my dependency graph.  Since I receive a baton from
the outside, and I have to return it, I end up threading that baton
through my dependency graph.  Now when my function is evaluated, the
evaluation order, at least for monadic actions, is locked down.

On the other hand, I can compare a lazy list function, such as
accumUntilCutoff, to a multi-layer perceptron[2].  The input layer of
this perceptron receives the contents of a lazy list.  List processing
functions, such as init, zipWith, and map, construct hidden layers of
neurons.  For example, zipWith (+) xs $ tail xs builds a hidden
layer such that each neuron computes the sum of two adjacent inputs.

The major contrast between a lazy list function and a multi-layer
perceptron is that for some functions, such as filter, takeWhile,
dropWhile, and find, I can't build the corresponding neural
interconnections until runtime, since these connections depend on the
actual *data* that is presented to the inputs.

A complicated function, like accumUntilCutoff, is almost a
multi-layer perceptron, except for the fact that parts of the
dependency graph are constructed at runtime based on the input data.
This makes it very hard to thread a baton through the dependency
graph.

So I want to make accumUntilCutoff read its input, lazily, from the
console.  That means:

1. I need to provide a way to hand the IO baton to accumUntilCutoff
   and get it back at the end.

2. The baton must be passed, sequentially, to each element of the
   input list, up to and including the last element that I need.

Here is my key observation -- Suppose that:
1. I have two functions f and g that both process a lazy list.
2. I feed the same lazy list from the console to both functions.
3. Function f consumes part of the list, and g consumes more than f.
4. I choose to print the result of f, then interact with the user,
   and later, based on user input, possibly print the result of g.

Then:
1. In order to print the result of f, I must pass the baton through f,
   so the baton will be sequenced through a prefix of my lazy list.
2. In order to determine whether to evaluate g, I must get the baton
   back from f and use it to interact with the user.
3. If I later need to print the result of g, then I need to pass the
   baton through g, and the baton must be sequenced *starting in the
   middle* through my lazy list of user input.
As a result, I have to interleave IO operations.

Example pseudo-code:

1.  main :: IO
2.  main = do
3. putStrLn Hello.
4. xs - getLazyListOfNumbersFromUser
5. let ys = zipWith (+) xs $ tail xs
6. print (ys !! 0)-- depends on xs !! 0 and 1
7. b - askUserBool Would you like to continue? 
8. if b
9.   then print (ys !! 1) -- depends on xs !! 1 and 2
10.  else return ()
11.putStrLn Goodbye.

We *must* ask the user for the first two elements of xs because we
have to print the result before asking the user a question.  We
*can't* ask the user for the third element of xs at this time because
the user gets to decide whether we need it.  As a result, we must
interleave

[Haskell-cafe] Lazy Lists and IO

2007-07-10 Thread Ronald Guida

Hi Everyone,

A few weeks ago, I started learning Haskell (and functional
programming) on my own from the wealth if information on the internet.
I recently read the paper Why Functional Programming Matters [1] and
it led me to wonder how to input a lazy list.

Suppose I have a function f that reads a lazy list, such that f
only consumes as much of the list as it needs to.  Laziness allows me
to apply f to an infinite list without creating an infinite loop.

Now I want to connect the console to f, such that the list of inputs
to f comes from the console, one item at a time.

To create a specific example, lets suppose I want to read and
accumulate the contents of a list, and I want to stop when the sum
reaches or exceeds a specified cutoff.

I can write this as a function that reads elements from an infinite list:

 accumUntilCutoff :: Integer - [Integer] - (Integer, [Integer])
 accumUntilCutoff cutoff xs = accumHelper cutoff 0 id xs
 where
   accumHelper :: {- cutoff  -} Integer -
  {- sum so far  -} Integer -
  {- elements so far -} ([Integer] - [Integer]) -
  {- remaining list  -} [Integer] -
  {- outputs -} (Integer, [Integer])
   accumHelper cutoff sum elems [] = (sum, elems [])
   accumHelper cutoff sum elems (x:xs) =
   if sum  cutoff
 then accumHelper cutoff (sum + x) (elems . (x:)) xs
 else (sum, elems [])

Example:
  GHCi accumUntilCutoff 20 [1..]
== (21,[1,2,3,4,5,6])
  GHCi accumUntilCutoff 20 ([1..6] ++ repeat undefined)
== (21,[1,2,3,4,5,6])
[This demonstrates that accumUntilCutoff is lazy)

Alternatively, I can write a function that (1) prompts the user to
enter numbers until the running sum reaches the cutoff, and then (2)
returns the results in the IO monad.

 readUntilCutoff :: Integer - IO (Integer, [Integer])
 readUntilCutoff cutoff = readHelper cutoff 0 id
 where
   readHelper :: {- cutoff  -} Integer -
 {- sum so far  -} Integer -
 {- elements so far -} ([Integer] - [Integer]) -
 {- outputs -} IO (Integer, [Integer])
   readHelper cutoff sum elems = do
 if sum  cutoff
   then do
 putStr Enter an integer: 
 ln - getLine
 let x = read ln
 readHelper cutoff (sum + x) (elems . (x:))
   else return $ (sum, elems [])

Example:
  GHCi readUntilCutoff 20
  Enter an integer: 1
  Enter an integer: 2
  Enter an integer: 3
  Enter an integer: 4
  Enter an integer: 5
  Enter an integer: 6
== (21,[1,2,3,4,5,6])

Here's my puzzle:

I am dis-satisfied with the fact that I have to embed IO code in the
middle of accumulation code.  Is there some way to separate
readUntilCutoff into two parts (e.g. functions), such that one part
would look extremely similar to accumUntilCutoff, while the other
part would handle the user interaction associated with getting the
next number?

Thank you
-- Ron

Reference:
[1] http://www.cs.chalmers.se/~rjmh/Papers/whyfp.html

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