[Haskell-cafe] Re: Josephus problem and style

2007-04-04 Thread apfelmus
Malcolm Wallace wrote:
 Anthony Chaumas-Pellet [EMAIL PROTECTED] wrote:
 Why is tail recursion a bad thing for a finite function?
 Is tail recursion simply not the most common Haskell idiom, or is
 there some technical reason I fail to see?
 
 Tail recursion tends to create space-leaks, which in turn hurt time
 performance.

That's only part of the truth. Take for example the ordinary version of

   and :: (a - Bool) - [a] - Bool

   and p []= False
   and p (x:xs)= p x  and xs

and it's tail-recursive cousin

   and' p [] b = b
   and' p (x:xs) b = and' p xs (b  p x)

Apparently, the function is True if there is some element in the list
that fulfills the condition p. Clearly, we can stop traversing the list
when we find the first element that satisfies p. Now, the tail-recursive
version is doomed to traverse the entire list, but thanks to lazy
evaluation, the ordinary version stops as soon as an element x with p x
is found.

Of course, one could alter the definition of and' to achieve early stopping

   and' _ _  True  = True
   and' p (x:xs) False = and' p xs (p x)
   and' _ [] False = False

but this is not advisable: we unfolded the definition of (). In the
ordinary case however, () already contains all the magic of early
stopping, the recursion scheme has nothing to do with it.

Thus, the most common Haskell idiom about tail recursion is to not think
about it (and hence not use it). Instead, return values as early as
possible (in some cases () can return a definite answer by looking at
the first argument only). Note that this is very different from strict
functional languages.

Regards,
apfelmus

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


[Haskell-cafe] Which pretty printer?

2007-04-04 Thread Joel Reymont
Should I prefer Daan Leijen's pretty printer [1] to the Hughes-SPJ  
one that comes with GHC?


Has anyone looked at both and is able to tell the difference?

I need to pretty-print a Pascal-like language as well as C#.

Thanks, Joel

[1] http://www.cs.uu.nl/~daan/download/pprint/pprint.html

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] ANN: Atom - Yet another Haskell HDL

2007-04-04 Thread Bill Wood
On Tue, 2007-04-03 at 23:18 -0500, Tom Hawkins wrote:
 Hi,
 
 Haskell has a rich history of embedded hardware description languages.
  Here's one more for the list.
 
 Inspired by the work of Arvind, Hoe, and all the sharp folks at
 Bluespec, Atom is a small HDL that compiles conditional term rewriting
 systems down to Verilog RTL.  In Atom, a circuit description is
 composed of a set of state elements (registers) and a set of rules.
 Each rule has two components: an enabling condition and a collection
 of actions, or state updates.  When a rule is enabled, it's actions
 may be selected to execute atomically.  In contrast to Verilog
 always blocks, multiple rules can write to the same state element.

Just curious, how does this relate to Guryevitch's Evolving Algebras
(renamed Abstract State Machines?)

 -- Bill Wood


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


[Haskell-cafe] Re: Which pretty printer?

2007-04-04 Thread Joel Reymont

Also, are there examples of using either pretty printer?

On Apr 4, 2007, at 9:57 AM, Joel Reymont wrote:

Should I prefer Daan Leijen's pretty printer [1] to the Hughes-SPJ  
one that comes with GHC?


Has anyone looked at both and is able to tell the difference?

I need to pretty-print a Pascal-like language as well as C#.


--
http://wagerlabs.com/





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


[Haskell-cafe] ReadP - take first succesful parser ?

2007-04-04 Thread Marc Weber
Brief:
I want to make the parser 
choice [string dummy, anystring ]
where anystring = many get

return the first match. 
(Thus if dummy matches disregarg all following
parsers)
..)

details:

I want to parse some wmii events.
They all look this way
ClientFocus 2
ClientFocus 2
LeftBarClick 1 web

At this moment I only need two of them (FocusTag and UnfocusTag)
So I've created the data type

type O = String
data WMIIEvent = FocusTag Int
| UnfocusTag Int
| Unkown String -- to be implemented

Now I want to create a simple ReadP parser which looks like this:

= parser code 
instance Read WmiiEvent where
  readsPrec _ = readP_to_S (foldr1 takeFirst
[ rp FocusTag FocusTag
, rp UnfocusTag UnfocusTag
, rpUnkown ])
where rp str f = fmap f $ string str  skipSpaces  liftM read (many get)
  rp :: (Read a) = String - (a - WmiiEvent) - ReadP WmiiEvent
  rpUnkown = (many get) = return . Unkown
  rpUnkown :: ReadP WmiiEvent

But I'm getting an ambiguous parse. (because UnfocusTag 3 makes two
parsers of the choice list succeed.

How is this done?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] QuickCheck's co-arbitrary

2007-04-04 Thread Joel Reymont

Folks,

I understand that arbitrary defines the possible values.

How do I generally come up with co-arbitrary, though?

Would someone kindly explain the choice of co-arbitrary in the  
following cases, specially the very last bit with variant 1 .  
coarbitrary a?


instance Arbitrary Char where
arbitrary = elements ([' ', '\n', '\0'] ++ ['a'..'h'])
coarbitrary c = variant (fromEnum c `rem` 4)

instance Arbitrary Ordering where
arbitrary  = elements [LT, EQ, GT]
coarbitrary LT = variant 0
coarbitrary EQ = variant 1
coarbitrary GT = variant 2

instance Arbitrary a = Arbitrary (Maybe a) where
arbitrary= frequency [ (1, return Nothing)
 , (3, liftM Just arbitrary) ]
coarbitrary Nothing  = variant 0
coarbitrary (Just a) = variant 1 . coarbitrary a

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] QuickCheck's co-arbitrary

2007-04-04 Thread Fawzi Mohamed
Let's see, I am quite new to it, so this is a check to see if I 
understood the things correctly ;)


Joel Reymont wrote:

Folks,

I understand that arbitrary defines the possible values.

How do I generally come up with co-arbitrary, though?

you need to change a generator depending on the value of your type.

variant changes the seed of the generator adding an integer to it, so if 
you can map your object to mostly different integers (like the hash 
function) you can modify the generators using something like

   coarbitrary a = variant (hash a)

then
variant 1 . coarbitrary a
is simply modify a little (variant 1) the modification that coarbitrary 
a would do.


as to why you need this, it is to generate functions that have as 
starting domain your type.


Fawzi
Would someone kindly explain the choice of co-arbitrary in the 
following cases, specially the very last bit with variant 1 . 
coarbitrary a?


instance Arbitrary Char where
arbitrary = elements ([' ', '\n', '\0'] ++ ['a'..'h'])
coarbitrary c = variant (fromEnum c `rem` 4)

instance Arbitrary Ordering where
arbitrary  = elements [LT, EQ, GT]
coarbitrary LT = variant 0
coarbitrary EQ = variant 1
coarbitrary GT = variant 2

instance Arbitrary a = Arbitrary (Maybe a) where
arbitrary= frequency [ (1, return Nothing)
 , (3, liftM Just arbitrary) ]
coarbitrary Nothing  = variant 0
coarbitrary (Just a) = variant 1 . coarbitrary a

Thanks, Joel

--
http://wagerlabs.com/





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


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


Re: [Haskell-cafe] `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-04 Thread Scott Bell

Bulat,


one possible solution: use Streams library and establish a stream
transformer that adds an error call on timeout. something like this:

data StreamWithTimeout s = StreamWithTimeout s Timeout

instance Stream s = Stream (StreamWithTimeout s) where
  vGetChar (StreamWithTimeout s t) = do
 timeout t (vGetChar s)
   (error Timed out!)


If possible, I would like to try and use lazy [Char]s -- this would greatly
simplify my usage of the Parsec parser.


or, even simple, you can make your own variant of hGetContents which
adds a timeout checks before each next call to hGetChar or hGetBuf


Can this be as simple as applying the parser against a string returned
by the (modified) hGetContents, which will read all that is possible given
a certain time constraint?

Thanks,

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


[Haskell-cafe] QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Joel Reymont
Suppose I have a type describing a statement and that I'm trying to  
make it an instance of arbitrary. The type looks like this:


data Statement
= InputDecs [InputDecl]
| VarDecs [VarDecl]
| ArrayDecs [ArrayDecl]
| Compound [Statement]
| Assign (VarIdent, Expr)
| ArrayAssign (VarIdent, [Expr], Expr)

Assuming that other types involved were instances of arbitrary, how  
do I write arbitrary for Statement?


Poking around various bits of source code I think that for a type  
like the following


data Style
= StyleValue Expr
| Solid
| Dashed
| Dotted
| Dashed2
| Dashed3
deriving Show

I can write

instance Arbitrary Style where
arbitrary = oneOf [ StyleValue . arbitrary,
elements [ Solid
 , Dashed
 , Dotted
 , Dashed2
 , Dashed3
 ]
  ]

I'm not sure if this is correct, though, so any help is appreciated!

Thanks in advance, Joel

--
http://wagerlabs.com/





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


Re[2]: [Haskell-cafe] `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-04 Thread Bulat Ziganshin
Hello Scott,

Wednesday, April 4, 2007, 6:39:22 PM, you wrote:

   vGetChar (StreamWithTimeout s t) = do
  timeout t (vGetChar s)
(error Timed out!)

 If possible, I would like to try and use lazy [Char]s -- this would greatly
 simplify my usage of the Parsec parser.

 or, even simple, you can make your own variant of hGetContents which
 adds a timeout checks before each next call to hGetChar or hGetBuf

 Can this be as simple as applying the parser against a string returned
 by the (modified) hGetContents, which will read all that is possible given
 a certain time constraint?

yes, with both variants. actually, second one should be easier to
implement and understand. you should look into unsafeInterleaveIO
section of http://haskell.org/haskellwiki/IO_inside

feel free to ask me if you need more help


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] ReadP - take first succesful parser ? -solved

2007-04-04 Thread Marc Weber
I think I've solved the problem.

The Text.Read.Lex does contain the missing parts.
I had two problems. The one is solved by using ++ ( use the first
parser, falback to the second), the second was: parse till EOF.
This is solved by using the functions defined in Lex itself.

Thanks for listening :)

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


[Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Joel Reymont
I got this simple example working so I think I have my question  
answered.


Now I just have to learn to write generators of my own to produce  
valid and invalid input for my parser.


module Foo where

import Control.Monad
import System.Random
import Test.QuickCheck

data Foo
= Foo Int
| Bar
| Baz
  deriving Show

instance Arbitrary Foo where
coarbitrary = undefined
arbitrary   = oneof [ return Bar
, return Baz
, liftM Foo arbitrary
]

gen' rnd = generate 1 rnd $ vector 5 :: [Foo]

gen =
do { rnd - newStdGen
   ; return $ gen' rnd
   }

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Fawzi Mohamed

Joel Reymont wrote:

I got this simple example working so I think I have my question answered.
Great, just one thing that could be important : when you have recursive 
structures (like your Statement through Compound) be sure to use

sized (\mySize - ...)
as generator for arbitrary so that you can avoid infinite looping.
Look at
 http://www.cs.chalmers.se/~rjmh/QuickCheck/manual_body.html#15
for an example.

Fawzi


Now I just have to learn to write generators of my own to produce 
valid and invalid input for my parser.


module Foo where

import Control.Monad
import System.Random
import Test.QuickCheck

data Foo
= Foo Int
| Bar
| Baz
  deriving Show

instance Arbitrary Foo where
coarbitrary = undefined
arbitrary   = oneof [ return Bar
, return Baz
, liftM Foo arbitrary
]

gen' rnd = generate 1 rnd $ vector 5 :: [Foo]

gen =
do { rnd - newStdGen
   ; return $ gen' rnd
   }

--
http://wagerlabs.com/





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


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


[Haskell-cafe] Tracking characters and a timestamp ?

2007-04-04 Thread Marc Weber
=  ===
{-
 This program should read characters from stdin, stop on 's' and print the 
character along with a timestamp
 You need ghc-6.6 because of Date.Time.
 When not using mapM addTimeCode I'll get the lines printed on stdout instantly
-}

import Data.Time.Clock
import Data.Time
import Control.Monad

handleChar :: Show a = (Char, a) - IO ()
handleChar ('s', _) = exitWith (ExitFailure 1)
handleChar tuple = print tuple

addTimeCode a = liftM ( (,) a) getCurrentTime

main = do
  hSetBuffering stdin NoBuffering
  hGetContents stdin = mapM addTimeCode = mapM_ handleChar


=  ==

When running and typing a b c it should print
('a', timestamp)
('b', timestamp)
('c', timestamp)

It seems to wait till the end of the infinite list. Why?

When using a take 10  I'll get those 10 events after having typed the
10th character.

Do I need continuation passing style?
Would unsafeInterleaveIO help?

The final goal is writing a timetracker which sums up the time you've
spent on different wmii tags (= you can think of them beeing different screens )

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


[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Stefan Holdermans

Edsko,

(Moved to Haskell Cafe.)


It is well-known that negative datatypes can be used to encode
recursion, without actually explicitly using recursion. As a little
exercise, I set out to define the fixpoint combinator using negative
datatypes. I think the result is kinda cool :) Comments are welcome :)


Yeah, it's rather cool. IIRC, this style of encoding of recursion  
operators is attributed to Morris.


Before the advent of equality coercions, GHC typically had problems  
generating code for these kinds of definitions. Did you test this  
with a release version? If so, how did you get around the code- 
generation problem? Is it the NOINLINE pragma that does the trick?


Cheers,

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


[Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Paul Berg

Ok, so I decided to implement an algorithm to build Strongly Typed Genetic
Programming trees in Haskell, in an effort to learn Haskell,
and I'm way over my head on this unification problem.

The unification seems to work well, as long as I include the occurs check.
growFullTree returns a lazy list of all possible syntax trees in random
order that are well typed. So, with the occurs check:

head $ growFullTree 4 TInt 0 [] (mkStdGen 5)

Gives me a nice, random, well typed tree.  So far so good, although
I am wary of the efficiency... perhaps I need some applySubst calls
in there somewhere to keep the constraint list down?

Anyway now, we comment out the occurs check in the unify function and
do the same thing again.  Now we get what appears to be an infinite
constraint!  The unify is supposed to be terminating without the occurs
check, so something is very wrong here!

Worse, now we run:

head $ growFullTree 5 TInt 0 [] (mkStdGen 7)

This one never even begins printing!  Although it appears the bug is
tail recursive in this case.  Other random number seeds will cause it
to blow stack.

I have gone over and over this code and cannot find the issue due to my
lack of experience with both Haskell and Unification algorithms in general.

I was hoping someone here could give pointers on where the bug might lie, eg.
what is my algorithm doing wrong that makes it a mostly, but not completely
correct unification algorithm, as well as give me pointers on how this
code could be
made cleaner and/or more concise, as I'm trying very hard to get my brain around
this language, and this problem.

Here's the basic code, which should be fully runnable:

module Evaluator
 where

import Maybe
import Random
import Monad

-- | Expressions.
data Exp = Prim String-- A Primitive Function
| App Exp Exp-- An un-evaluated application
| Func (Exp - Exp)  -- A partially applied function
| LitInt Integer
| LitReal Double
  deriving Show

-- | We name type variables by uniquely picking values of this type.
type TVName = Int

-- | Describes possible types in our language
data Type = TInt
 | TReal
 | TVar TVName
 | Type :- Type
   deriving (Eq, Show)

-- | Type arrows are right associative to match Haskell's native type arrows.
infixr 9 :-

-- | Constraints are simply a pair of Types which are equal.
type Constraint = (Type, Type)

-- | Returns a new type variable name, given an old one.
getNextName :: TVName - TVName
getNextName n = n + 1

-- | Evaluate an expression.
eval :: Exp - Exp
eval (Prim s)  = fst . fromJust $ lookup s primitives
eval (App f x) = apply f x
eval x = x


-- | Apply a function.
apply :: Exp - Exp - Exp
apply a@(App _ _) x = eval $ App (eval a) x
apply p@(Prim _)  x = eval $ App (eval p) x
apply (Func f)x = eval $ f x
apply f   x = error $ (show f) ++  was applied to  ++ (show
x) ++  and is not a valid function.


-- | Given a set of constraints (possibly empty), the next available
variable name and an expression,
-- return a triple which consists of the inferred type of the
expression, the next available variable name,
-- and a list of constraints for the new type.
infer :: [Constraint] - TVName - Exp - (Type, TVName, [Constraint])
infer _ nvar (LitInt _)  = (TInt, nvar, [])
infer _ nvar (LitReal _) = (TReal, nvar, [])
infer _ nvar (Prim s)= (t, nvar', [])
 where (nvar', t, _) = substvars nvar (snd . fromJust $ lookup s primitives) []

infer ctx nvar (App t1 t2) = (TVar nvar'', getNextName nvar'',
newconstr : (ctx' ++ ctx''))
 where (tyT1, nvar', ctx')   = infer ctx nvar t1
   (tyT2, nvar'', ctx'') = infer ctx nvar' t2
   newconstr = (tyT1, tyT2 :- TVar nvar'')

infer _ _ (Func _) = error Type Inferrence of partially applied
functions not supported


-- | Given a unified constraint list and a type, return a simplified type
applySubst :: Type - [Constraint] - Type
applySubst tyT ctx = foldl (\tyS (tyX,tyC) - substinty tyX tyC tyS)
tyT (reverse ctx)


-- | We need to substitute all the type variables in a primitive with new
-- ones that do not clash with the variables already defined in our
-- constraint set.  This function does that, by taking the next available
-- variable name and creating a set of substitutions over a type that
-- replace the old variable names with newly generated ones
substvars :: TVName - Type - [(TVName, TVName)] - (TVName, Type,
[(TVName, TVName)])
substvars nvar (TVar n) ctx =
 case lookup n ctx of
(Just n') - (nvar, TVar n', ctx)
Nothing   - (getNextName nvar, TVar nvar, (n, nvar) : ctx)

substvars nvar (t1 :- t2) ctx =
 (nvar'', t1' :- t2', ctx'')
   where (nvar', t1', ctx')   = substvars nvar t1 ctx
 (nvar'', t2', ctx'') = substvars nvar' t2 ctx'

substvars nvar t ctx = (nvar, t, ctx)


-- | returns the type of an expression if it has one
typeof :: Exp - Maybe Type
typeof e = fmap (applySubst t) (unify ctx)
 where (t, _, ctx) = infer [] 

[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Stefan Holdermans

Mike,

For those of us who aren't type theorists: What's a negative  
datatype?


A type that has a recursive call in negative position. Negative  
positions are the argument positions in function types. (But if a  
function type appears in a negative position, then its own argument  
position is denoted positive and its result position negative.)


Cheers,

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


[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Edsko de Vries
 Yeah, it's rather cool. IIRC, this style of encoding of recursion  
 operators is attributed to Morris.

Do you have a reference?

 Before the advent of equality coercions, GHC typically had problems  
 generating code for these kinds of definitions. Did you test this  
 with a release version? If so, how did you get around the code- 
 generation problem? Is it the NOINLINE pragma that does the trick?

Yep. Without the NOINLINE pragma, ghc tries to inline the definition of
fac, expanding it ad infinitum (this is a known bug in ghc and mentioned
in the ghc manual). Hugs doesn't have a problem though.

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


[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Stefan Holdermans

Edsko,


Yeah, it's rather cool. IIRC, this style of encoding of recursion
operators is attributed to Morris.


Do you have a reference?


James H. Morris. Lambda calculus models of programming languages.  
Technical Report MIT-LCS//MIT/LCS/TR-57, Massachusetts Institute of  
Technology, 1968.


Cheers,

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


[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Edsko de Vries
On Wed, Apr 04, 2007 at 11:05:51PM +0200, Stefan Holdermans wrote:
 Edsko,
 
 Yeah, it's rather cool. IIRC, this style of encoding of recursion
 operators is attributed to Morris.
 
 Do you have a reference?
 
 James H. Morris. Lambda calculus models of programming languages.  
 Technical Report MIT-LCS//MIT/LCS/TR-57, Massachusetts Institute of  
 Technology, 1968.

Aah, I guess that's a bit old to be avaiable online :) Does he talk
about negative datatypes though? The Y combinator itself isn't really
the point of my little exercise; it's more that I can code the Y
combinator without making any recursive calls (in fact, there aren't any
recursive calls in that program at all).

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


Re: [Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Stefan O'Rear
I received the file with seriously damaged layout; in case anyone else
has the same issue, I've hosted a cleaned up version:

http://members.cox.net/stefanor/Procyon.hs

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


[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Stefan Holdermans

Edsko,


James H. Morris. Lambda calculus models of programming languages.
Technical Report MIT-LCS//MIT/LCS/TR-57, Massachusetts Institute of
Technology, 1968.


Aah, I guess that's a bit old to be avaiable online :) Does he talk
about negative datatypes though? The Y combinator itself isn't really
the point of my little exercise; it's more that I can code the Y
combinator without making any recursive calls (in fact, there  
aren't any

recursive calls in that program at all).


If I recall correctly that's exactly what he demonstrates, i.e., that  
fixed-point combinators can be encoded without value-level recursion,  
but by instead making use of types that are contravariantly recursive.


Cheers,

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


Re: [Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Stefan O'Rear
I seem to have did an accidental reply-to-sender at first:

On Wed, Apr 04, 2007 at 01:37:44PM -0700, Paul Berg wrote:
 Ok, so I decided to implement an algorithm to build Strongly Typed Genetic
 Programming trees in Haskell, in an effort to learn Haskell,
 and I'm way over my head on this unification problem.
 
 The unification seems to work well, as long as I include the occurs check.
 growFullTree returns a lazy list of all possible syntax trees in random
 order that are well typed. So, with the occurs check:
 
 head $ growFullTree 4 TInt 0 [] (mkStdGen 5)
 
 Gives me a nice, random, well typed tree.  So far so good, although
 I am wary of the efficiency... perhaps I need some applySubst calls
 in there somewhere to keep the constraint list down?
 
 Anyway now, we comment out the occurs check in the unify function and
 do the same thing again.  Now we get what appears to be an infinite
 constraint!  The unify is supposed to be terminating without the occurs
 check, so something is very wrong here!
 
 Worse, now we run:
 
 head $ growFullTree 5 TInt 0 [] (mkStdGen 7)
 
 This one never even begins printing!  Although it appears the bug is
 tail recursive in this case.  Other random number seeds will cause it
 to blow stack.
 
 I have gone over and over this code and cannot find the issue due to my
 lack of experience with both Haskell and Unification algorithms in general.
 
 I was hoping someone here could give pointers on where the bug might lie, 
 eg.
 what is my algorithm doing wrong that makes it a mostly, but not completely
 correct unification algorithm, as well as give me pointers on how this
 code could be
 made cleaner and/or more concise, as I'm trying very hard to get my brain 
 around
 this language, and this problem.
 
 Here's the basic code, which should be fully runnable:

The problem is with this type:

data Type = TInt
  | TReal
  | TVar TVName
  | Type :- Type

Because it is impossible to observe sharing in Haskell values, we are
forced to explore the entire type; but without the occurs check the
type can be infinite! 

In my infinite-types unifier, I used this:

data Bin = Sum | Fun | Prod deriving (Eq, Show, Ord)
data Zen = ZTup deriving (Eq,Show,Ord)
data DictElt = EZen Zen | EBin Bin Type Type deriving (Eq, Show, Ord)
type Dict = M.Map Int DictElt

Changing to use Paul's set of types:

data DictElt = TInt | TReal | TVar | Int :- Int
type Dict = M.Map Int DictElt

IE, we use Ints explicitly as pointers.  However this representation
costs a lot in terms of clarity, since everything must be explicitly
indirected through the 'heap'.  Also fixtypes was a very old project
of mine; were I to do it again I would probably use explicit mutable
references:

data Tinfo s = TInt | TReal | TVar | Type s :- Type s
type Type s = STRef s (Tinfo s)

This may conflict with your method of backtracking tree generation; I
haven't read that far in the code yet. 

Stefan

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


[Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Edsko de Vries
On Wed, Apr 04, 2007 at 11:15:25PM +0200, Stefan Holdermans wrote:
 Edsko,
 
 James H. Morris. Lambda calculus models of programming languages.
 Technical Report MIT-LCS//MIT/LCS/TR-57, Massachusetts Institute of
 Technology, 1968.
 
 Aah, I guess that's a bit old to be avaiable online :) Does he talk
 about negative datatypes though? The Y combinator itself isn't really
 the point of my little exercise; it's more that I can code the Y
 combinator without making any recursive calls (in fact, there  
 aren't any
 recursive calls in that program at all).
 
 If I recall correctly that's exactly what he demonstrates, i.e., that  
 fixed-point combinators can be encoded without value-level recursion,  
 but by instead making use of types that are contravariantly recursive.

I see. Thanks for the reference! Must try to dig that up (the MIT
publication database appears to be offline at the moment).

Thanks again,

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


Re: [Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Joel Reymont

One last bit then...

My identifiers should start with letter | char '_' and the tail  
should be alphaNum | char '_'.


I guess I can use choose and oneof to produce the right set of  
characters but how do I combine  the two into a single identifier of  
a given length (up to 20 chars, say)?


Thanks, Joel

On Apr 4, 2007, at 5:27 PM, Fawzi Mohamed wrote:

Great, just one thing that could be important : when you have  
recursive structures (like your Statement through Compound) be sure  
to use

sized (\mySize - ...)
as generator for arbitrary so that you can avoid infinite looping.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-04 Thread Matthew Brecknell
Marc Weber:
 main = do
   hSetBuffering stdin NoBuffering
   hGetContents stdin = mapM addTimeCode = mapM_ handleChar
 
 It seems to wait till the end of the infinite list. Why?

The sequencing imposed by the IO monad means that the first mapM must
complete before the second can start. To see this, you can try the
following:

 main = do
   hSetBuffering stdin NoBuffering
   hGetContents stdin = mapM_ (\c - addTimeCode c = handleChar)

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


Re: [Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Stefan O'Rear
On Wed, Apr 04, 2007 at 10:59:45PM +0100, Joel Reymont wrote:
 One last bit then...
 
 My identifiers should start with letter | char '_' and the tail  
 should be alphaNum | char '_'.
 
 I guess I can use choose and oneof to produce the right set of  
 characters but how do I combine  the two into a single identifier of  
 a given length (up to 20 chars, say)?
 
   Thanks, Joel
 
 On Apr 4, 2007, at 5:27 PM, Fawzi Mohamed wrote:
 
 Great, just one thing that could be important : when you have  
 recursive structures (like your Statement through Compound) be sure  
 to use
 sized (\mySize - ...)
 as generator for arbitrary so that you can avoid infinite looping.

quickcheck is a monad so you can just do:

do first - elements $ '_' : ['a' .. 'z']
   len   - elements $ [5..19]
   rest  - replicateM len $ elements $ '_' : ['a' .. 'z'] ++ ['0' .. '9']
   return (first : rest)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-04 Thread Bulat Ziganshin
Hello Matthew,

Thursday, April 5, 2007, 2:00:03 AM, you wrote:

 main = do
   hSetBuffering stdin NoBuffering
   hGetContents stdin = mapM addTimeCode = mapM_ handleChar
 
 It seems to wait till the end of the infinite list. Why?

 The sequencing imposed by the IO monad means that the first mapM must
 complete before the second can start. To see this, you can try the
 following:

or, alternatively, replace first mapM_ with unsafeInterleavedMapM:

unsafeInterleavedMapM f (x:xs) = do a - f x
as - unsafeInterleaveIO 
(unsafeInterleavedMapM f xs)
return (a:as)

(not tested)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] What I learned from my first serious attempt low-level Haskell programming

2007-04-04 Thread Stefan O'Rear
As a learning excersize, I re-wrote and re-optimized
Data.Binary.Builder yesterday.

1. Intuition is NOT your friend.  Most obvious pessimizations I made
   were actually wins, and vice versa.

2. Parameters are very expensive.  Our type of functions that build
   (ignoring CPS for the time being) was MBA# - Int# - [ByteString],
   where the Int# is the current write pointer.  Adding an extra Int#
   to cache the size of the array (rather than calling sMBA# each
   time) slowed the code down ~2x.  Conversely, moving the write
   pointer into the byte array (storing it in bytes 0#, 1#, 2#, and
   3#) sped the code by 4x.

3. MBA# is just as fast as Addr#, and garbage collected to boot.

4. You can't keep track of which version of the code is which, what is
   a regression, and what is an enhancement.  Don't even try.  Next
   time I try something like this I will make as much use of darcs as
   possible.

5. State# threads clog the optimizer quite effectively.  Replacing
   st(n-1)# with realWorld# everywhere I could count on data
   dependencies to do the same job doubled performance.

6. The inliner is a bit too greedy.  Removing the slow-path code from
   singleton doesn't help because popSingleton is only used once; but
   if I explicitly {-# NOINLINE popSingleton #-}, the code for
   singleton itself becomes much smaller, and inlinable (15% perf
   gain).  Plus the new singleton doesn't allocate memory, so I can
   use even MORE realWorld#s.

And probably a few more I forgot about because of #4.

The code is online at http://members.cox.net/stefanor/hackedbuilder if anyone 
cares (but see #4).

Some parting numbers: (Builder7 is my current version, Builder1 is the
 unmodified rossp/kolmodin builder)

[EMAIL PROTECTED]:~/hackedbuilder$ ghc -v0 --make -O2 -fforce-recomp 
-DBUILDER=Builder7 Bench.hs ; time ./Bench 2 1000
33000

real0m5.580s
user0m5.540s
sys 0m0.032s
[EMAIL PROTECTED]:~/hackedbuilder$ ghc -v0 --make -O2 -fforce-recomp 
-DBUILDER=Builder7 -DUNROLL Bench.hs ; time ./Bench 2 1000
33000

real0m2.948s
user0m2.908s
sys 0m0.036s
[EMAIL PROTECTED]:~/hackedbuilder$ ghc -v0 --make -O2 -fforce-recomp 
-DBUILDER=Builder1 Bench.hs ; time ./Bench 2 1000
33000

real0m55.708s
user0m54.695s
sys 0m0.208s
[EMAIL PROTECTED]:~/hackedbuilder$ ghc -v0 --make -O2 -fforce-recomp 
-DBUILDER=Builder1 -DUNROLL Bench.hs ; time ./Bench 2 1000
33000

real0m25.888s
user0m25.546s
sys 0m0.156s
[EMAIL PROTECTED]:~/hackedbuilder$ gcc -O2 -march=pentium4 CBuilder.c -o 
CBuilder ; time ./CBuilder 1000

real0m0.861s
user0m0.860s
sys 0m0.000s

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


[Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-04 Thread Joel Reymont

Folks,

I have very uniform Parsec code like this and I'm wondering if I can  
derive it using TemplateHaskell or DrIFT or some other tool. Any ideas?


Note that

1) The reserved word matches the constructor

2) No arguments equals no parens

3) More than one argument is separated with a comma

4) For every invocation of numExpr, strExpr or boolExpr, the type of  
the constructor argument is NumExpr, StrExpr and BoolExpr respectively.


This is just a handful of functions and I have to tackle about 100  
more, thus my asking :-).


Thanks, Joel

---

strCall =
choice [ do { reserved NewLine
; return NewLine
}
   , do { reserved GetSymbolName
; return GetSymbolName
}
   , do { reserved ELDateToString
; arg1 - parens numExpr
; return $ ELDateToString arg1
}
   , do { reserved TextGetString
; arg1 - parens numExpr
; return $ TextGetString arg1
}
   , do { reserved Description
; return Description
}
   , do { reserved GetExchangeName
; return GetExchangeName
}
   , do { reserved LeftStr
; parens $ do { arg1 - strExpr
  ; comma
  ; arg2 - numExpr
  ; return $ LeftStr arg1 arg2
  }
}
   , do { reserved RightStr
; parens $ do { arg1 - strExpr
  ; comma
  ; arg2 - numExpr
  ; return $ RightStr arg1 arg2
  }
}
   , do { reserved LowerStr
; arg1 - parens strExpr
; return $ LowerStr arg1
}
   , do { reserved UpperStr
; arg1 - parens strExpr
; return $ UpperStr arg1
}
   , do { reserved Spaces
; arg1 - parens numExpr
; return $ Spaces arg1
}
   , do { reserved SymbolRoot
; return SymbolRoot
}
   , do { reserved MidStr
; parens $ do { arg1 - strExpr
  ; comma
  ; arg2 - numExpr
  ; comma
  ; arg3 - numExpr
  ; return $ MidStr arg1 arg2 arg3
  }
}
   , do { reserved NumToStr
; parens $ do { arg1 - numExpr
  ; comma
  ; arg2 - numExpr
  ; return $ NumToStr arg1 arg2
  }
}
   ]

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-04 Thread Stefan O'Rear
On Thu, Apr 05, 2007 at 12:14:52AM +0100, Joel Reymont wrote:
 Folks,
 
 I have very uniform Parsec code like this and I'm wondering if I can  
 derive it using TemplateHaskell or DrIFT or some other tool. Any ideas?
 
 Note that
 
 1) The reserved word matches the constructor
 
 2) No arguments equals no parens
 
 3) More than one argument is separated with a comma
 
 4) For every invocation of numExpr, strExpr or boolExpr, the type of  
 the constructor argument is NumExpr, StrExpr and BoolExpr respectively.
 
 This is just a handful of functions and I have to tackle about 100  
 more, thus my asking :-).
 
   Thanks, Joel

Data.Derive can do this.  In an attempt to avoid munging the relevent
files they are attached. 


[EMAIL PROTECTED]:/tmp$ ghci -fth -v0 -i/usr/local/src/derive -e '$( 
_derive_print_instance makeJoelR Foo )' Sample.hs
instance JoelR Main.Foo
where parse = choice [() (reserved ['A']) (() (char '(') ((=) parse 
(\a0 - () (char ')') (return (Main.A a1),
  () (reserved ['B']) (() (char '(') ((=) parse 
(\a0 - () (char ',') ((=) parse (\a1 - ()
(char ')') (return (Main.B a1 a2))),
  () (reserved ['C']) (return Main.C)]

Not pretty code, but it will work.  (Future plans include adding a
prefix - infix translator to the optimizer.)

http://www.cs.york.ac.uk/fp/darcs/derive

Stefan
import Text.ParserCombinators.Parsec
import Data.Derive.JoelR
import Data.Derive.TH

class JoelR a where parse :: CharParser s a

data NumExpr = Dummy_ -- I don't know the constr
numExpr = undefined

instance JoelR NumExpr where parse = numExpr

data Foo = A NumExpr | B Foo Foo | C
module Data.Derive.JoelR where

import Data.Derive
import Data.Derive.Peephole
import Data.List

makeJoelR = Derivation drv JoelR

drv dat@(DataDef name arity ctors) =
simple_instance JoelR dat [funN parse [ sclause [] body ] ]
where
body = l1 choice $ lst [ clause con | con - ctors ]

clause con = l1 reserved (lit (trim (ctorName con))) : args con (ctorArity con)

trim = reverse . takeWhile (/= '.') . reverse

args ct 0 = return' (ctp ct 'a')
args ct k = l1 char (lit '(') : args' ct k 0

args'  ct remn seen = l0 parse =: (('a' : show seen) -: args'' ct (remn-1) (seen+1))
args'' ct 0 seen = l1 char (lit ')') : return' (ctp ct 'a')
args'' ct k seen = l1 char (lit ',') : args' ct k seen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Fixpoint combinator without recursion

2007-04-04 Thread Jan-Willem Maessen


On Apr 4, 2007, at 5:01 PM, Edsko de Vries wrote:


Yeah, it's rather cool. IIRC, this style of encoding of recursion
operators is attributed to Morris.


Do you have a reference?


Before the advent of equality coercions, GHC typically had problems
generating code for these kinds of definitions. Did you test this
with a release version? If so, how did you get around the code-
generation problem? Is it the NOINLINE pragma that does the trick?


Yep. Without the NOINLINE pragma, ghc tries to inline the  
definition of
fac, expanding it ad infinitum (this is a known bug in ghc and  
mentioned

in the ghc manual). Hugs doesn't have a problem though.


I keep waiting for someone to use this fact to cook up a poor man's  
partial evaluation---use fix for static recursion, and ordinary  
recursive definitions for dynamic recursion.  I fiddled with this a  
bit in the pH days (it had the same bug, for much the same reason).


-Jan-Willem Maessen



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




smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Paul Berg

I believe I may have found a solution (I *think* it's correct):

The occurs check needs to stay, but be modified for infinite types.
When the occurs check is true, instead of failing, we should keep the
constraint, but skip performing substitution on the rest of the list
of constraints.  This allows us to not fall into the trap of an
infinite substitution loop.  So, unify becomes, in the case of
infinite types:

-- | Given a list of constraints, unify those constraints,
-- finding values for the type variables
unify :: (Monad m, Functor m) = [Constraint] - m [Constraint]
unify []   = return []
unify ((t1 ,  t2)   :rest)
 | t1 == t2   = unify rest
unify ((tyS,  tyX@(TVar _)) :rest)
-- | tyX `occursIn` tyS = fail Infinite Type
 | tyX `occursIn` tyS = fmap ((tyX,tyS):) (unify rest)
 | otherwise  = fmap ((tyX,tyS):) (unify
$ substinconstr tyX tyS rest)
unify ((tyX@(TVar _), tyT)  :rest) = unify $ (tyT,tyX) : rest
unify ((tyS1 :- tyS2,tyT1 :- tyT2):rest) = unify $ (tyS1,tyT1) :
(tyS2,tyT2) : rest
unify _= fail Unsolvable
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Stefan O'Rear
On Wed, Apr 04, 2007 at 07:16:35PM -0700, Paul Berg wrote:
 I believe I may have found a solution (I *think* it's correct):
 
 The occurs check needs to stay, but be modified for infinite types.
 When the occurs check is true, instead of failing, we should keep the
 constraint, but skip performing substitution on the rest of the list
 of constraints.  This allows us to not fall into the trap of an
 infinite substitution loop.  So, unify becomes, in the case of
 infinite types:
 
 -- | Given a list of constraints, unify those constraints,
 -- finding values for the type variables
 unify :: (Monad m, Functor m) = [Constraint] - m [Constraint]
 unify []   = return []
 unify ((t1 ,  t2)   :rest)
  | t1 == t2   = unify rest
 unify ((tyS,  tyX@(TVar _)) :rest)
 -- | tyX `occursIn` tyS = fail Infinite Type
  | tyX `occursIn` tyS = fmap ((tyX,tyS):) (unify rest)
  | otherwise  = fmap ((tyX,tyS):) (unify
 $ substinconstr tyX tyS rest)
 unify ((tyX@(TVar _), tyT)  :rest) = unify $ (tyT,tyX) : rest
 unify ((tyS1 :- tyS2,tyT1 :- tyT2):rest) = unify $ (tyS1,tyT1) :
 (tyS2,tyT2) : rest
 unify _= fail Unsolvable

I honestly don't understand the algorithm.  (And I don't have tapl!!)
So, ... quickcheck!  You've seen my occurs-free unifier; now write an
Arbitrary instance for trees and check that they always give the same
result.  The chance of a common bug is neglible.. 

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


[Haskell-cafe] 25k lines of ASP to 4.2k lines of Haskell, with considerably more functionality

2007-04-04 Thread Adam Peacock

Haskell in the real world: http://braintreehemp.com.au/

Source available from:

darcs get http://braintreehemp.com.au/www.braintreehemp.com.au-WASH/

The site features:

- Written in Haskell, using WASH
http://www.informatik.uni-freiburg.de/~thiemann/WASH/
- Shopping basket and checkout
- Google Maps
- Google Analytics
- Google Webmaster tools
- Template Haskell for HaskellDB description (describe a table or a
field in one line)
- GPL, execpt where stated otherwise.

- Heavyweight Content Management System (CMS)
-- Froogle RSS generator
-- Configurable help for each page
-- Concept of inventory levels
-- Concept of users and permissions
-- Naive-user management of products, users, and page content
-- XML import tool and wizard for inventory level reconciliation
between warehouse and site database

CMS screen shots at:

http://braintreehemp.com.au/screenshots/index.html

Why did I write the site in Haskell? First, I was ask to fix the site
that was selling products they didn't have in stock. Once I looked at
the source code, 25000 lines of ASP, I reckoned it would be easier to
rewrite it in a real language. Second, I couldn't find any commercial
sites written in Haskell, and I thought this would be a good chance.

The new site has considerably more functionality and is a little over
4200 lines of Haskell. The original site could only display and sell
products, without any consideration of whether any were currently in
stock. Furthermore, the site content could only be maintained by an
expert user. See the old site at
http://web.archive.org/web/20060503232646/www.braintreehemp.com.au/retail/
.

If anyone wants to have a play with the CMS, email me privately, and
I'll give you a nobody login.

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


Re: [Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Paul Berg

This solution is invalid for some edge cases.

Better than quickcheck, I can map eval across all possible trees of
depth n, since growFullTree returns a lazy list of all trees.

On 4/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Wed, Apr 04, 2007 at 07:16:35PM -0700, Paul Berg wrote:
 I believe I may have found a solution (I *think* it's correct):

 The occurs check needs to stay, but be modified for infinite types.
 When the occurs check is true, instead of failing, we should keep the
 constraint, but skip performing substitution on the rest of the list
 of constraints.  This allows us to not fall into the trap of an
 infinite substitution loop.  So, unify becomes, in the case of
 infinite types:

 -- | Given a list of constraints, unify those constraints,
 -- finding values for the type variables
 unify :: (Monad m, Functor m) = [Constraint] - m [Constraint]
 unify []   = return []
 unify ((t1 ,  t2)   :rest)
  | t1 == t2   = unify rest
 unify ((tyS,  tyX@(TVar _)) :rest)
 -- | tyX `occursIn` tyS = fail Infinite Type
  | tyX `occursIn` tyS = fmap ((tyX,tyS):) (unify rest)
  | otherwise  = fmap ((tyX,tyS):) (unify
 $ substinconstr tyX tyS rest)
 unify ((tyX@(TVar _), tyT)  :rest) = unify $ (tyT,tyX) : rest
 unify ((tyS1 :- tyS2,tyT1 :- tyT2):rest) = unify $ (tyS1,tyT1) :
 (tyS2,tyT2) : rest
 unify _= fail Unsolvable

I honestly don't understand the algorithm.  (And I don't have tapl!!)
So, ... quickcheck!  You've seen my occurs-free unifier; now write an
Arbitrary instance for trees and check that they always give the same
result.  The chance of a common bug is neglible..

Stefan


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


Re: [Haskell-cafe] My Unification Sorrows

2007-04-04 Thread Paul Berg

Also, the random backtracker isn't truly random.. it clusters
solutions.  the head should be completely random each time though.

On 4/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Wed, Apr 04, 2007 at 07:16:35PM -0700, Paul Berg wrote:
 I believe I may have found a solution (I *think* it's correct):

 The occurs check needs to stay, but be modified for infinite types.
 When the occurs check is true, instead of failing, we should keep the
 constraint, but skip performing substitution on the rest of the list
 of constraints.  This allows us to not fall into the trap of an
 infinite substitution loop.  So, unify becomes, in the case of
 infinite types:

 -- | Given a list of constraints, unify those constraints,
 -- finding values for the type variables
 unify :: (Monad m, Functor m) = [Constraint] - m [Constraint]
 unify []   = return []
 unify ((t1 ,  t2)   :rest)
  | t1 == t2   = unify rest
 unify ((tyS,  tyX@(TVar _)) :rest)
 -- | tyX `occursIn` tyS = fail Infinite Type
  | tyX `occursIn` tyS = fmap ((tyX,tyS):) (unify rest)
  | otherwise  = fmap ((tyX,tyS):) (unify
 $ substinconstr tyX tyS rest)
 unify ((tyX@(TVar _), tyT)  :rest) = unify $ (tyT,tyX) : rest
 unify ((tyS1 :- tyS2,tyT1 :- tyT2):rest) = unify $ (tyS1,tyT1) :
 (tyS2,tyT2) : rest
 unify _= fail Unsolvable

I honestly don't understand the algorithm.  (And I don't have tapl!!)
So, ... quickcheck!  You've seen my occurs-free unifier; now write an
Arbitrary instance for trees and check that they always give the same
result.  The chance of a common bug is neglible..

Stefan


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


Re: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-04 Thread Matthew Brecknell
Marc Weber:
 main = do
   lines - liftM lines getContents
   mapM_ print lines -- *
 
 So this example should hang, as well, shouldn't it?

It would, except for the magic of unsafeInterleaveIO.

It doesn't hang because getContents uses unsafeInterleaveIO internally
to return the file contents lazily. If you took the unsafeInterleaveIO
out of getContents, your program would wait for EOF on input before
printing anything to output, as you had been expecting.

Bulat's post showed how to add the same kind of magic into your use of
mapM.

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